Haskell bindings: Fix integer arguments.
[libguestfs.git] / haskell / Guestfs.hs
1 {- libguestfs generated file
2    WARNING: THIS FILE IS GENERATED BY 'src/generator.ml'.
3    ANY CHANGES YOU MAKE TO THIS FILE WILL BE LOST.
4   
5    Copyright (C) 2009 Red Hat Inc.
6   
7    This library is free software; you can redistribute it and/or
8    modify it under the terms of the GNU Lesser General Public
9    License as published by the Free Software Foundation; either
10    version 2 of the License, or (at your option) any later version.
11   
12    This library is distributed in the hope that it will be useful,
13    but WITHOUT ANY WARRANTY; without even the implied warranty of
14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15    Lesser General Public License for more details.
16   
17    You should have received a copy of the GNU Lesser General Public
18    License along with this library; if not, write to the Free Software
19    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
20 -}
21
22 {-# INCLUDE <guestfs.h> #-}
23 {-# LANGUAGE ForeignFunctionInterface #-}
24
25 module Guestfs (
26   create,
27   launch,
28   wait_ready,
29   kill_subprocess,
30   add_drive,
31   add_cdrom,
32   add_drive_ro,
33   config,
34   set_qemu,
35   set_path,
36   set_append,
37   set_busy,
38   set_ready,
39   end_busy,
40   mount,
41   sync,
42   touch,
43   aug_init,
44   aug_close,
45   aug_set,
46   aug_mv,
47   aug_save,
48   aug_load,
49   rm,
50   rmdir,
51   rm_rf,
52   mkdir,
53   mkdir_p,
54   chmod,
55   chown,
56   pvcreate,
57   vgcreate,
58   lvcreate,
59   mkfs,
60   sfdisk,
61   write_file,
62   umount,
63   umount_all,
64   lvm_remove_all,
65   blockdev_setro,
66   blockdev_setrw,
67   blockdev_setbsz,
68   blockdev_flushbufs,
69   blockdev_rereadpt,
70   upload,
71   download,
72   tar_in,
73   tar_out,
74   tgz_in,
75   tgz_out,
76   mount_ro,
77   mount_options,
78   mount_vfs,
79   lvremove,
80   vgremove,
81   pvremove,
82   set_e2label,
83   set_e2uuid,
84   zero,
85   grub_install,
86   cp,
87   cp_a,
88   mv,
89   drop_caches,
90   ping_daemon,
91   zerofree,
92   pvresize,
93   sfdisk_N,
94   lvresize,
95   resize2fs,
96   e2fsck_f,
97   sleep,
98   scrub_device,
99   scrub_file,
100   scrub_freespace
101   ) where
102 import Foreign
103 import Foreign.C
104 import Foreign.C.Types
105 import IO
106 import Control.Exception
107 import Data.Typeable
108
109 data GuestfsS = GuestfsS            -- represents the opaque C struct
110 type GuestfsP = Ptr GuestfsS        -- guestfs_h *
111 type GuestfsH = ForeignPtr GuestfsS -- guestfs_h * with attached finalizer
112
113 -- XXX define properly later XXX
114 data PV = PV
115 data VG = VG
116 data LV = LV
117 data IntBool = IntBool
118 data Stat = Stat
119 data StatVFS = StatVFS
120 data Hashtable = Hashtable
121
122 foreign import ccall unsafe "guestfs_create" c_create
123   :: IO GuestfsP
124 foreign import ccall unsafe "&guestfs_close" c_close
125   :: FunPtr (GuestfsP -> IO ())
126 foreign import ccall unsafe "guestfs_set_error_handler" c_set_error_handler
127   :: GuestfsP -> Ptr CInt -> Ptr CInt -> IO ()
128
129 create :: IO GuestfsH
130 create = do
131   p <- c_create
132   c_set_error_handler p nullPtr nullPtr
133   h <- newForeignPtr c_close p
134   return h
135
136 foreign import ccall unsafe "guestfs_last_error" c_last_error
137   :: GuestfsP -> IO CString
138
139 -- last_error :: GuestfsH -> IO (Maybe String)
140 -- last_error h = do
141 --   str <- withForeignPtr h (\p -> c_last_error p)
142 --   maybePeek peekCString str
143
144 last_error :: GuestfsH -> IO (String)
145 last_error h = do
146   str <- withForeignPtr h (\p -> c_last_error p)
147   if (str == nullPtr)
148     then return "no error"
149     else peekCString str
150
151 foreign import ccall unsafe "guestfs_launch" c_launch
152   :: GuestfsP -> IO (CInt)
153
154 launch :: GuestfsH -> IO ()
155 launch h = do
156   r <- withForeignPtr h (\p -> c_launch p)
157   if (r == -1)
158     then do
159       err <- last_error h
160       fail err
161     else return ()
162
163 foreign import ccall unsafe "guestfs_wait_ready" c_wait_ready
164   :: GuestfsP -> IO (CInt)
165
166 wait_ready :: GuestfsH -> IO ()
167 wait_ready h = do
168   r <- withForeignPtr h (\p -> c_wait_ready p)
169   if (r == -1)
170     then do
171       err <- last_error h
172       fail err
173     else return ()
174
175 foreign import ccall unsafe "guestfs_kill_subprocess" c_kill_subprocess
176   :: GuestfsP -> IO (CInt)
177
178 kill_subprocess :: GuestfsH -> IO ()
179 kill_subprocess h = do
180   r <- withForeignPtr h (\p -> c_kill_subprocess p)
181   if (r == -1)
182     then do
183       err <- last_error h
184       fail err
185     else return ()
186
187 foreign import ccall unsafe "guestfs_add_drive" c_add_drive
188   :: GuestfsP -> CString -> IO (CInt)
189
190 add_drive :: GuestfsH -> String -> IO ()
191 add_drive h filename = do
192   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_drive p filename)
193   if (r == -1)
194     then do
195       err <- last_error h
196       fail err
197     else return ()
198
199 foreign import ccall unsafe "guestfs_add_cdrom" c_add_cdrom
200   :: GuestfsP -> CString -> IO (CInt)
201
202 add_cdrom :: GuestfsH -> String -> IO ()
203 add_cdrom h filename = do
204   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_cdrom p filename)
205   if (r == -1)
206     then do
207       err <- last_error h
208       fail err
209     else return ()
210
211 foreign import ccall unsafe "guestfs_add_drive_ro" c_add_drive_ro
212   :: GuestfsP -> CString -> IO (CInt)
213
214 add_drive_ro :: GuestfsH -> String -> IO ()
215 add_drive_ro h filename = do
216   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_drive_ro p filename)
217   if (r == -1)
218     then do
219       err <- last_error h
220       fail err
221     else return ()
222
223 foreign import ccall unsafe "guestfs_config" c_config
224   :: GuestfsP -> CString -> CString -> IO (CInt)
225
226 config :: GuestfsH -> String -> Maybe String -> IO ()
227 config h qemuparam qemuvalue = do
228   r <- withCString qemuparam $ \qemuparam -> maybeWith withCString qemuvalue $ \qemuvalue -> withForeignPtr h (\p -> c_config p qemuparam qemuvalue)
229   if (r == -1)
230     then do
231       err <- last_error h
232       fail err
233     else return ()
234
235 foreign import ccall unsafe "guestfs_set_qemu" c_set_qemu
236   :: GuestfsP -> CString -> IO (CInt)
237
238 set_qemu :: GuestfsH -> String -> IO ()
239 set_qemu h qemu = do
240   r <- withCString qemu $ \qemu -> withForeignPtr h (\p -> c_set_qemu p qemu)
241   if (r == -1)
242     then do
243       err <- last_error h
244       fail err
245     else return ()
246
247 foreign import ccall unsafe "guestfs_set_path" c_set_path
248   :: GuestfsP -> CString -> IO (CInt)
249
250 set_path :: GuestfsH -> String -> IO ()
251 set_path h path = do
252   r <- withCString path $ \path -> withForeignPtr h (\p -> c_set_path p path)
253   if (r == -1)
254     then do
255       err <- last_error h
256       fail err
257     else return ()
258
259 foreign import ccall unsafe "guestfs_set_append" c_set_append
260   :: GuestfsP -> CString -> IO (CInt)
261
262 set_append :: GuestfsH -> String -> IO ()
263 set_append h append = do
264   r <- withCString append $ \append -> withForeignPtr h (\p -> c_set_append p append)
265   if (r == -1)
266     then do
267       err <- last_error h
268       fail err
269     else return ()
270
271 foreign import ccall unsafe "guestfs_set_busy" c_set_busy
272   :: GuestfsP -> IO (CInt)
273
274 set_busy :: GuestfsH -> IO ()
275 set_busy h = do
276   r <- withForeignPtr h (\p -> c_set_busy p)
277   if (r == -1)
278     then do
279       err <- last_error h
280       fail err
281     else return ()
282
283 foreign import ccall unsafe "guestfs_set_ready" c_set_ready
284   :: GuestfsP -> IO (CInt)
285
286 set_ready :: GuestfsH -> IO ()
287 set_ready h = do
288   r <- withForeignPtr h (\p -> c_set_ready p)
289   if (r == -1)
290     then do
291       err <- last_error h
292       fail err
293     else return ()
294
295 foreign import ccall unsafe "guestfs_end_busy" c_end_busy
296   :: GuestfsP -> IO (CInt)
297
298 end_busy :: GuestfsH -> IO ()
299 end_busy h = do
300   r <- withForeignPtr h (\p -> c_end_busy p)
301   if (r == -1)
302     then do
303       err <- last_error h
304       fail err
305     else return ()
306
307 foreign import ccall unsafe "guestfs_mount" c_mount
308   :: GuestfsP -> CString -> CString -> IO (CInt)
309
310 mount :: GuestfsH -> String -> String -> IO ()
311 mount h device mountpoint = do
312   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount p device mountpoint)
313   if (r == -1)
314     then do
315       err <- last_error h
316       fail err
317     else return ()
318
319 foreign import ccall unsafe "guestfs_sync" c_sync
320   :: GuestfsP -> IO (CInt)
321
322 sync :: GuestfsH -> IO ()
323 sync h = do
324   r <- withForeignPtr h (\p -> c_sync p)
325   if (r == -1)
326     then do
327       err <- last_error h
328       fail err
329     else return ()
330
331 foreign import ccall unsafe "guestfs_touch" c_touch
332   :: GuestfsP -> CString -> IO (CInt)
333
334 touch :: GuestfsH -> String -> IO ()
335 touch h path = do
336   r <- withCString path $ \path -> withForeignPtr h (\p -> c_touch p path)
337   if (r == -1)
338     then do
339       err <- last_error h
340       fail err
341     else return ()
342
343 foreign import ccall unsafe "guestfs_aug_init" c_aug_init
344   :: GuestfsP -> CString -> CInt -> IO (CInt)
345
346 aug_init :: GuestfsH -> String -> Int -> IO ()
347 aug_init h root flags = do
348   r <- withCString root $ \root -> withForeignPtr h (\p -> c_aug_init p root (fromIntegral flags))
349   if (r == -1)
350     then do
351       err <- last_error h
352       fail err
353     else return ()
354
355 foreign import ccall unsafe "guestfs_aug_close" c_aug_close
356   :: GuestfsP -> IO (CInt)
357
358 aug_close :: GuestfsH -> IO ()
359 aug_close h = do
360   r <- withForeignPtr h (\p -> c_aug_close p)
361   if (r == -1)
362     then do
363       err <- last_error h
364       fail err
365     else return ()
366
367 foreign import ccall unsafe "guestfs_aug_set" c_aug_set
368   :: GuestfsP -> CString -> CString -> IO (CInt)
369
370 aug_set :: GuestfsH -> String -> String -> IO ()
371 aug_set h path val = do
372   r <- withCString path $ \path -> withCString val $ \val -> withForeignPtr h (\p -> c_aug_set p path val)
373   if (r == -1)
374     then do
375       err <- last_error h
376       fail err
377     else return ()
378
379 foreign import ccall unsafe "guestfs_aug_mv" c_aug_mv
380   :: GuestfsP -> CString -> CString -> IO (CInt)
381
382 aug_mv :: GuestfsH -> String -> String -> IO ()
383 aug_mv h src dest = do
384   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_aug_mv p src dest)
385   if (r == -1)
386     then do
387       err <- last_error h
388       fail err
389     else return ()
390
391 foreign import ccall unsafe "guestfs_aug_save" c_aug_save
392   :: GuestfsP -> IO (CInt)
393
394 aug_save :: GuestfsH -> IO ()
395 aug_save h = do
396   r <- withForeignPtr h (\p -> c_aug_save p)
397   if (r == -1)
398     then do
399       err <- last_error h
400       fail err
401     else return ()
402
403 foreign import ccall unsafe "guestfs_aug_load" c_aug_load
404   :: GuestfsP -> IO (CInt)
405
406 aug_load :: GuestfsH -> IO ()
407 aug_load h = do
408   r <- withForeignPtr h (\p -> c_aug_load p)
409   if (r == -1)
410     then do
411       err <- last_error h
412       fail err
413     else return ()
414
415 foreign import ccall unsafe "guestfs_rm" c_rm
416   :: GuestfsP -> CString -> IO (CInt)
417
418 rm :: GuestfsH -> String -> IO ()
419 rm h path = do
420   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm p path)
421   if (r == -1)
422     then do
423       err <- last_error h
424       fail err
425     else return ()
426
427 foreign import ccall unsafe "guestfs_rmdir" c_rmdir
428   :: GuestfsP -> CString -> IO (CInt)
429
430 rmdir :: GuestfsH -> String -> IO ()
431 rmdir h path = do
432   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rmdir p path)
433   if (r == -1)
434     then do
435       err <- last_error h
436       fail err
437     else return ()
438
439 foreign import ccall unsafe "guestfs_rm_rf" c_rm_rf
440   :: GuestfsP -> CString -> IO (CInt)
441
442 rm_rf :: GuestfsH -> String -> IO ()
443 rm_rf h path = do
444   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm_rf p path)
445   if (r == -1)
446     then do
447       err <- last_error h
448       fail err
449     else return ()
450
451 foreign import ccall unsafe "guestfs_mkdir" c_mkdir
452   :: GuestfsP -> CString -> IO (CInt)
453
454 mkdir :: GuestfsH -> String -> IO ()
455 mkdir h path = do
456   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir p path)
457   if (r == -1)
458     then do
459       err <- last_error h
460       fail err
461     else return ()
462
463 foreign import ccall unsafe "guestfs_mkdir_p" c_mkdir_p
464   :: GuestfsP -> CString -> IO (CInt)
465
466 mkdir_p :: GuestfsH -> String -> IO ()
467 mkdir_p h path = do
468   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir_p p path)
469   if (r == -1)
470     then do
471       err <- last_error h
472       fail err
473     else return ()
474
475 foreign import ccall unsafe "guestfs_chmod" c_chmod
476   :: GuestfsP -> CInt -> CString -> IO (CInt)
477
478 chmod :: GuestfsH -> Int -> String -> IO ()
479 chmod h mode path = do
480   r <- withCString path $ \path -> withForeignPtr h (\p -> c_chmod p (fromIntegral mode) path)
481   if (r == -1)
482     then do
483       err <- last_error h
484       fail err
485     else return ()
486
487 foreign import ccall unsafe "guestfs_chown" c_chown
488   :: GuestfsP -> CInt -> CInt -> CString -> IO (CInt)
489
490 chown :: GuestfsH -> Int -> Int -> String -> IO ()
491 chown h owner group path = do
492   r <- withCString path $ \path -> withForeignPtr h (\p -> c_chown p (fromIntegral owner) (fromIntegral group) path)
493   if (r == -1)
494     then do
495       err <- last_error h
496       fail err
497     else return ()
498
499 foreign import ccall unsafe "guestfs_pvcreate" c_pvcreate
500   :: GuestfsP -> CString -> IO (CInt)
501
502 pvcreate :: GuestfsH -> String -> IO ()
503 pvcreate h device = do
504   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvcreate p device)
505   if (r == -1)
506     then do
507       err <- last_error h
508       fail err
509     else return ()
510
511 foreign import ccall unsafe "guestfs_vgcreate" c_vgcreate
512   :: GuestfsP -> CString -> Ptr CString -> IO (CInt)
513
514 vgcreate :: GuestfsH -> String -> [String] -> IO ()
515 vgcreate h volgroup physvols = do
516   r <- withCString volgroup $ \volgroup -> withMany withCString physvols $ \physvols -> withArray0 nullPtr physvols $ \physvols -> withForeignPtr h (\p -> c_vgcreate p volgroup physvols)
517   if (r == -1)
518     then do
519       err <- last_error h
520       fail err
521     else return ()
522
523 foreign import ccall unsafe "guestfs_lvcreate" c_lvcreate
524   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
525
526 lvcreate :: GuestfsH -> String -> String -> Int -> IO ()
527 lvcreate h logvol volgroup mbytes = do
528   r <- withCString logvol $ \logvol -> withCString volgroup $ \volgroup -> withForeignPtr h (\p -> c_lvcreate p logvol volgroup (fromIntegral mbytes))
529   if (r == -1)
530     then do
531       err <- last_error h
532       fail err
533     else return ()
534
535 foreign import ccall unsafe "guestfs_mkfs" c_mkfs
536   :: GuestfsP -> CString -> CString -> IO (CInt)
537
538 mkfs :: GuestfsH -> String -> String -> IO ()
539 mkfs h fstype device = do
540   r <- withCString fstype $ \fstype -> withCString device $ \device -> withForeignPtr h (\p -> c_mkfs p fstype device)
541   if (r == -1)
542     then do
543       err <- last_error h
544       fail err
545     else return ()
546
547 foreign import ccall unsafe "guestfs_sfdisk" c_sfdisk
548   :: GuestfsP -> CString -> CInt -> CInt -> CInt -> Ptr CString -> IO (CInt)
549
550 sfdisk :: GuestfsH -> String -> Int -> Int -> Int -> [String] -> IO ()
551 sfdisk h device cyls heads sectors lines = do
552   r <- withCString device $ \device -> withMany withCString lines $ \lines -> withArray0 nullPtr lines $ \lines -> withForeignPtr h (\p -> c_sfdisk p device (fromIntegral cyls) (fromIntegral heads) (fromIntegral sectors) lines)
553   if (r == -1)
554     then do
555       err <- last_error h
556       fail err
557     else return ()
558
559 foreign import ccall unsafe "guestfs_write_file" c_write_file
560   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
561
562 write_file :: GuestfsH -> String -> String -> Int -> IO ()
563 write_file h path content size = do
564   r <- withCString path $ \path -> withCString content $ \content -> withForeignPtr h (\p -> c_write_file p path content (fromIntegral size))
565   if (r == -1)
566     then do
567       err <- last_error h
568       fail err
569     else return ()
570
571 foreign import ccall unsafe "guestfs_umount" c_umount
572   :: GuestfsP -> CString -> IO (CInt)
573
574 umount :: GuestfsH -> String -> IO ()
575 umount h pathordevice = do
576   r <- withCString pathordevice $ \pathordevice -> withForeignPtr h (\p -> c_umount p pathordevice)
577   if (r == -1)
578     then do
579       err <- last_error h
580       fail err
581     else return ()
582
583 foreign import ccall unsafe "guestfs_umount_all" c_umount_all
584   :: GuestfsP -> IO (CInt)
585
586 umount_all :: GuestfsH -> IO ()
587 umount_all h = do
588   r <- withForeignPtr h (\p -> c_umount_all p)
589   if (r == -1)
590     then do
591       err <- last_error h
592       fail err
593     else return ()
594
595 foreign import ccall unsafe "guestfs_lvm_remove_all" c_lvm_remove_all
596   :: GuestfsP -> IO (CInt)
597
598 lvm_remove_all :: GuestfsH -> IO ()
599 lvm_remove_all h = do
600   r <- withForeignPtr h (\p -> c_lvm_remove_all p)
601   if (r == -1)
602     then do
603       err <- last_error h
604       fail err
605     else return ()
606
607 foreign import ccall unsafe "guestfs_blockdev_setro" c_blockdev_setro
608   :: GuestfsP -> CString -> IO (CInt)
609
610 blockdev_setro :: GuestfsH -> String -> IO ()
611 blockdev_setro h device = do
612   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setro p device)
613   if (r == -1)
614     then do
615       err <- last_error h
616       fail err
617     else return ()
618
619 foreign import ccall unsafe "guestfs_blockdev_setrw" c_blockdev_setrw
620   :: GuestfsP -> CString -> IO (CInt)
621
622 blockdev_setrw :: GuestfsH -> String -> IO ()
623 blockdev_setrw h device = do
624   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setrw p device)
625   if (r == -1)
626     then do
627       err <- last_error h
628       fail err
629     else return ()
630
631 foreign import ccall unsafe "guestfs_blockdev_setbsz" c_blockdev_setbsz
632   :: GuestfsP -> CString -> CInt -> IO (CInt)
633
634 blockdev_setbsz :: GuestfsH -> String -> Int -> IO ()
635 blockdev_setbsz h device blocksize = do
636   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setbsz p device (fromIntegral blocksize))
637   if (r == -1)
638     then do
639       err <- last_error h
640       fail err
641     else return ()
642
643 foreign import ccall unsafe "guestfs_blockdev_flushbufs" c_blockdev_flushbufs
644   :: GuestfsP -> CString -> IO (CInt)
645
646 blockdev_flushbufs :: GuestfsH -> String -> IO ()
647 blockdev_flushbufs h device = do
648   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_flushbufs p device)
649   if (r == -1)
650     then do
651       err <- last_error h
652       fail err
653     else return ()
654
655 foreign import ccall unsafe "guestfs_blockdev_rereadpt" c_blockdev_rereadpt
656   :: GuestfsP -> CString -> IO (CInt)
657
658 blockdev_rereadpt :: GuestfsH -> String -> IO ()
659 blockdev_rereadpt h device = do
660   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_rereadpt p device)
661   if (r == -1)
662     then do
663       err <- last_error h
664       fail err
665     else return ()
666
667 foreign import ccall unsafe "guestfs_upload" c_upload
668   :: GuestfsP -> CString -> CString -> IO (CInt)
669
670 upload :: GuestfsH -> String -> String -> IO ()
671 upload h filename remotefilename = do
672   r <- withCString filename $ \filename -> withCString remotefilename $ \remotefilename -> withForeignPtr h (\p -> c_upload p filename remotefilename)
673   if (r == -1)
674     then do
675       err <- last_error h
676       fail err
677     else return ()
678
679 foreign import ccall unsafe "guestfs_download" c_download
680   :: GuestfsP -> CString -> CString -> IO (CInt)
681
682 download :: GuestfsH -> String -> String -> IO ()
683 download h remotefilename filename = do
684   r <- withCString remotefilename $ \remotefilename -> withCString filename $ \filename -> withForeignPtr h (\p -> c_download p remotefilename filename)
685   if (r == -1)
686     then do
687       err <- last_error h
688       fail err
689     else return ()
690
691 foreign import ccall unsafe "guestfs_tar_in" c_tar_in
692   :: GuestfsP -> CString -> CString -> IO (CInt)
693
694 tar_in :: GuestfsH -> String -> String -> IO ()
695 tar_in h tarfile directory = do
696   r <- withCString tarfile $ \tarfile -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tar_in p tarfile directory)
697   if (r == -1)
698     then do
699       err <- last_error h
700       fail err
701     else return ()
702
703 foreign import ccall unsafe "guestfs_tar_out" c_tar_out
704   :: GuestfsP -> CString -> CString -> IO (CInt)
705
706 tar_out :: GuestfsH -> String -> String -> IO ()
707 tar_out h directory tarfile = do
708   r <- withCString directory $ \directory -> withCString tarfile $ \tarfile -> withForeignPtr h (\p -> c_tar_out p directory tarfile)
709   if (r == -1)
710     then do
711       err <- last_error h
712       fail err
713     else return ()
714
715 foreign import ccall unsafe "guestfs_tgz_in" c_tgz_in
716   :: GuestfsP -> CString -> CString -> IO (CInt)
717
718 tgz_in :: GuestfsH -> String -> String -> IO ()
719 tgz_in h tarball directory = do
720   r <- withCString tarball $ \tarball -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tgz_in p tarball directory)
721   if (r == -1)
722     then do
723       err <- last_error h
724       fail err
725     else return ()
726
727 foreign import ccall unsafe "guestfs_tgz_out" c_tgz_out
728   :: GuestfsP -> CString -> CString -> IO (CInt)
729
730 tgz_out :: GuestfsH -> String -> String -> IO ()
731 tgz_out h directory tarball = do
732   r <- withCString directory $ \directory -> withCString tarball $ \tarball -> withForeignPtr h (\p -> c_tgz_out p directory tarball)
733   if (r == -1)
734     then do
735       err <- last_error h
736       fail err
737     else return ()
738
739 foreign import ccall unsafe "guestfs_mount_ro" c_mount_ro
740   :: GuestfsP -> CString -> CString -> IO (CInt)
741
742 mount_ro :: GuestfsH -> String -> String -> IO ()
743 mount_ro h device mountpoint = do
744   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_ro p device mountpoint)
745   if (r == -1)
746     then do
747       err <- last_error h
748       fail err
749     else return ()
750
751 foreign import ccall unsafe "guestfs_mount_options" c_mount_options
752   :: GuestfsP -> CString -> CString -> CString -> IO (CInt)
753
754 mount_options :: GuestfsH -> String -> String -> String -> IO ()
755 mount_options h options device mountpoint = do
756   r <- withCString options $ \options -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_options p options device mountpoint)
757   if (r == -1)
758     then do
759       err <- last_error h
760       fail err
761     else return ()
762
763 foreign import ccall unsafe "guestfs_mount_vfs" c_mount_vfs
764   :: GuestfsP -> CString -> CString -> CString -> CString -> IO (CInt)
765
766 mount_vfs :: GuestfsH -> String -> String -> String -> String -> IO ()
767 mount_vfs h options vfstype device mountpoint = do
768   r <- withCString options $ \options -> withCString vfstype $ \vfstype -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_vfs p options vfstype device mountpoint)
769   if (r == -1)
770     then do
771       err <- last_error h
772       fail err
773     else return ()
774
775 foreign import ccall unsafe "guestfs_lvremove" c_lvremove
776   :: GuestfsP -> CString -> IO (CInt)
777
778 lvremove :: GuestfsH -> String -> IO ()
779 lvremove h device = do
780   r <- withCString device $ \device -> withForeignPtr h (\p -> c_lvremove p device)
781   if (r == -1)
782     then do
783       err <- last_error h
784       fail err
785     else return ()
786
787 foreign import ccall unsafe "guestfs_vgremove" c_vgremove
788   :: GuestfsP -> CString -> IO (CInt)
789
790 vgremove :: GuestfsH -> String -> IO ()
791 vgremove h vgname = do
792   r <- withCString vgname $ \vgname -> withForeignPtr h (\p -> c_vgremove p vgname)
793   if (r == -1)
794     then do
795       err <- last_error h
796       fail err
797     else return ()
798
799 foreign import ccall unsafe "guestfs_pvremove" c_pvremove
800   :: GuestfsP -> CString -> IO (CInt)
801
802 pvremove :: GuestfsH -> String -> IO ()
803 pvremove h device = do
804   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvremove p device)
805   if (r == -1)
806     then do
807       err <- last_error h
808       fail err
809     else return ()
810
811 foreign import ccall unsafe "guestfs_set_e2label" c_set_e2label
812   :: GuestfsP -> CString -> CString -> IO (CInt)
813
814 set_e2label :: GuestfsH -> String -> String -> IO ()
815 set_e2label h device label = do
816   r <- withCString device $ \device -> withCString label $ \label -> withForeignPtr h (\p -> c_set_e2label p device label)
817   if (r == -1)
818     then do
819       err <- last_error h
820       fail err
821     else return ()
822
823 foreign import ccall unsafe "guestfs_set_e2uuid" c_set_e2uuid
824   :: GuestfsP -> CString -> CString -> IO (CInt)
825
826 set_e2uuid :: GuestfsH -> String -> String -> IO ()
827 set_e2uuid h device uuid = do
828   r <- withCString device $ \device -> withCString uuid $ \uuid -> withForeignPtr h (\p -> c_set_e2uuid p device uuid)
829   if (r == -1)
830     then do
831       err <- last_error h
832       fail err
833     else return ()
834
835 foreign import ccall unsafe "guestfs_zero" c_zero
836   :: GuestfsP -> CString -> IO (CInt)
837
838 zero :: GuestfsH -> String -> IO ()
839 zero h device = do
840   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zero p device)
841   if (r == -1)
842     then do
843       err <- last_error h
844       fail err
845     else return ()
846
847 foreign import ccall unsafe "guestfs_grub_install" c_grub_install
848   :: GuestfsP -> CString -> CString -> IO (CInt)
849
850 grub_install :: GuestfsH -> String -> String -> IO ()
851 grub_install h root device = do
852   r <- withCString root $ \root -> withCString device $ \device -> withForeignPtr h (\p -> c_grub_install p root device)
853   if (r == -1)
854     then do
855       err <- last_error h
856       fail err
857     else return ()
858
859 foreign import ccall unsafe "guestfs_cp" c_cp
860   :: GuestfsP -> CString -> CString -> IO (CInt)
861
862 cp :: GuestfsH -> String -> String -> IO ()
863 cp h src dest = do
864   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp p src dest)
865   if (r == -1)
866     then do
867       err <- last_error h
868       fail err
869     else return ()
870
871 foreign import ccall unsafe "guestfs_cp_a" c_cp_a
872   :: GuestfsP -> CString -> CString -> IO (CInt)
873
874 cp_a :: GuestfsH -> String -> String -> IO ()
875 cp_a h src dest = do
876   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp_a p src dest)
877   if (r == -1)
878     then do
879       err <- last_error h
880       fail err
881     else return ()
882
883 foreign import ccall unsafe "guestfs_mv" c_mv
884   :: GuestfsP -> CString -> CString -> IO (CInt)
885
886 mv :: GuestfsH -> String -> String -> IO ()
887 mv h src dest = do
888   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_mv p src dest)
889   if (r == -1)
890     then do
891       err <- last_error h
892       fail err
893     else return ()
894
895 foreign import ccall unsafe "guestfs_drop_caches" c_drop_caches
896   :: GuestfsP -> CInt -> IO (CInt)
897
898 drop_caches :: GuestfsH -> Int -> IO ()
899 drop_caches h whattodrop = do
900   r <- withForeignPtr h (\p -> c_drop_caches p (fromIntegral whattodrop))
901   if (r == -1)
902     then do
903       err <- last_error h
904       fail err
905     else return ()
906
907 foreign import ccall unsafe "guestfs_ping_daemon" c_ping_daemon
908   :: GuestfsP -> IO (CInt)
909
910 ping_daemon :: GuestfsH -> IO ()
911 ping_daemon h = do
912   r <- withForeignPtr h (\p -> c_ping_daemon p)
913   if (r == -1)
914     then do
915       err <- last_error h
916       fail err
917     else return ()
918
919 foreign import ccall unsafe "guestfs_zerofree" c_zerofree
920   :: GuestfsP -> CString -> IO (CInt)
921
922 zerofree :: GuestfsH -> String -> IO ()
923 zerofree h device = do
924   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zerofree p device)
925   if (r == -1)
926     then do
927       err <- last_error h
928       fail err
929     else return ()
930
931 foreign import ccall unsafe "guestfs_pvresize" c_pvresize
932   :: GuestfsP -> CString -> IO (CInt)
933
934 pvresize :: GuestfsH -> String -> IO ()
935 pvresize h device = do
936   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvresize p device)
937   if (r == -1)
938     then do
939       err <- last_error h
940       fail err
941     else return ()
942
943 foreign import ccall unsafe "guestfs_sfdisk_N" c_sfdisk_N
944   :: GuestfsP -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (CInt)
945
946 sfdisk_N :: GuestfsH -> String -> Int -> Int -> Int -> Int -> String -> IO ()
947 sfdisk_N h device n cyls heads sectors line = do
948   r <- withCString device $ \device -> withCString line $ \line -> withForeignPtr h (\p -> c_sfdisk_N p device (fromIntegral n) (fromIntegral cyls) (fromIntegral heads) (fromIntegral sectors) line)
949   if (r == -1)
950     then do
951       err <- last_error h
952       fail err
953     else return ()
954
955 foreign import ccall unsafe "guestfs_lvresize" c_lvresize
956   :: GuestfsP -> CString -> CInt -> IO (CInt)
957
958 lvresize :: GuestfsH -> String -> Int -> IO ()
959 lvresize h device mbytes = do
960   r <- withCString device $ \device -> withForeignPtr h (\p -> c_lvresize p device (fromIntegral mbytes))
961   if (r == -1)
962     then do
963       err <- last_error h
964       fail err
965     else return ()
966
967 foreign import ccall unsafe "guestfs_resize2fs" c_resize2fs
968   :: GuestfsP -> CString -> IO (CInt)
969
970 resize2fs :: GuestfsH -> String -> IO ()
971 resize2fs h device = do
972   r <- withCString device $ \device -> withForeignPtr h (\p -> c_resize2fs p device)
973   if (r == -1)
974     then do
975       err <- last_error h
976       fail err
977     else return ()
978
979 foreign import ccall unsafe "guestfs_e2fsck_f" c_e2fsck_f
980   :: GuestfsP -> CString -> IO (CInt)
981
982 e2fsck_f :: GuestfsH -> String -> IO ()
983 e2fsck_f h device = do
984   r <- withCString device $ \device -> withForeignPtr h (\p -> c_e2fsck_f p device)
985   if (r == -1)
986     then do
987       err <- last_error h
988       fail err
989     else return ()
990
991 foreign import ccall unsafe "guestfs_sleep" c_sleep
992   :: GuestfsP -> CInt -> IO (CInt)
993
994 sleep :: GuestfsH -> Int -> IO ()
995 sleep h secs = do
996   r <- withForeignPtr h (\p -> c_sleep p (fromIntegral secs))
997   if (r == -1)
998     then do
999       err <- last_error h
1000       fail err
1001     else return ()
1002
1003 foreign import ccall unsafe "guestfs_scrub_device" c_scrub_device
1004   :: GuestfsP -> CString -> IO (CInt)
1005
1006 scrub_device :: GuestfsH -> String -> IO ()
1007 scrub_device h device = do
1008   r <- withCString device $ \device -> withForeignPtr h (\p -> c_scrub_device p device)
1009   if (r == -1)
1010     then do
1011       err <- last_error h
1012       fail err
1013     else return ()
1014
1015 foreign import ccall unsafe "guestfs_scrub_file" c_scrub_file
1016   :: GuestfsP -> CString -> IO (CInt)
1017
1018 scrub_file :: GuestfsH -> String -> IO ()
1019 scrub_file h file = do
1020   r <- withCString file $ \file -> withForeignPtr h (\p -> c_scrub_file p file)
1021   if (r == -1)
1022     then do
1023       err <- last_error h
1024       fail err
1025     else return ()
1026
1027 foreign import ccall unsafe "guestfs_scrub_freespace" c_scrub_freespace
1028   :: GuestfsP -> CString -> IO (CInt)
1029
1030 scrub_freespace :: GuestfsH -> String -> IO ()
1031 scrub_freespace h dir = do
1032   r <- withCString dir $ \dir -> withForeignPtr h (\p -> c_scrub_freespace p dir)
1033   if (r == -1)
1034     then do
1035       err <- last_error h
1036       fail err
1037     else return ()
1038