94152d2531010c4da760274c84fd34d146e7b70d
[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   test0,
28   test0rint,
29   test0rinterr,
30   test0rint64,
31   test0rint64err,
32   launch,
33   wait_ready,
34   kill_subprocess,
35   add_drive,
36   add_cdrom,
37   add_drive_ro,
38   config,
39   set_qemu,
40   set_path,
41   set_append,
42   set_autosync,
43   set_verbose,
44   get_state,
45   set_busy,
46   set_ready,
47   end_busy,
48   mount,
49   sync,
50   touch,
51   aug_init,
52   aug_close,
53   aug_defvar,
54   aug_set,
55   aug_insert,
56   aug_rm,
57   aug_mv,
58   aug_save,
59   aug_load,
60   rm,
61   rmdir,
62   rm_rf,
63   mkdir,
64   mkdir_p,
65   chmod,
66   chown,
67   pvcreate,
68   vgcreate,
69   lvcreate,
70   mkfs,
71   sfdisk,
72   write_file,
73   umount,
74   umount_all,
75   lvm_remove_all,
76   blockdev_setro,
77   blockdev_setrw,
78   blockdev_getss,
79   blockdev_getbsz,
80   blockdev_setbsz,
81   blockdev_getsz,
82   blockdev_getsize64,
83   blockdev_flushbufs,
84   blockdev_rereadpt,
85   upload,
86   download,
87   tar_in,
88   tar_out,
89   tgz_in,
90   tgz_out,
91   mount_ro,
92   mount_options,
93   mount_vfs,
94   lvremove,
95   vgremove,
96   pvremove,
97   set_e2label,
98   set_e2uuid,
99   fsck,
100   zero,
101   grub_install,
102   cp,
103   cp_a,
104   mv,
105   drop_caches,
106   ping_daemon,
107   zerofree,
108   pvresize,
109   sfdisk_N,
110   vg_activate_all,
111   vg_activate,
112   lvresize,
113   resize2fs,
114   e2fsck_f,
115   sleep,
116   ntfs_3g_probe,
117   scrub_device,
118   scrub_file,
119   scrub_freespace
120   ) where
121 import Foreign
122 import Foreign.C
123 import Foreign.C.Types
124 import IO
125 import Control.Exception
126 import Data.Typeable
127
128 data GuestfsS = GuestfsS            -- represents the opaque C struct
129 type GuestfsP = Ptr GuestfsS        -- guestfs_h *
130 type GuestfsH = ForeignPtr GuestfsS -- guestfs_h * with attached finalizer
131
132 -- XXX define properly later XXX
133 data PV = PV
134 data VG = VG
135 data LV = LV
136 data IntBool = IntBool
137 data Stat = Stat
138 data StatVFS = StatVFS
139 data Hashtable = Hashtable
140
141 foreign import ccall unsafe "guestfs_create" c_create
142   :: IO GuestfsP
143 foreign import ccall unsafe "&guestfs_close" c_close
144   :: FunPtr (GuestfsP -> IO ())
145 foreign import ccall unsafe "guestfs_set_error_handler" c_set_error_handler
146   :: GuestfsP -> Ptr CInt -> Ptr CInt -> IO ()
147
148 create :: IO GuestfsH
149 create = do
150   p <- c_create
151   c_set_error_handler p nullPtr nullPtr
152   h <- newForeignPtr c_close p
153   return h
154
155 foreign import ccall unsafe "guestfs_last_error" c_last_error
156   :: GuestfsP -> IO CString
157
158 -- last_error :: GuestfsH -> IO (Maybe String)
159 -- last_error h = do
160 --   str <- withForeignPtr h (\p -> c_last_error p)
161 --   maybePeek peekCString str
162
163 last_error :: GuestfsH -> IO (String)
164 last_error h = do
165   str <- withForeignPtr h (\p -> c_last_error p)
166   if (str == nullPtr)
167     then return "no error"
168     else peekCString str
169
170 foreign import ccall unsafe "guestfs_test0" c_test0
171   :: GuestfsP -> CString -> CString -> Ptr CString -> CInt -> CInt -> CString -> CString -> IO (CInt)
172
173 test0 :: GuestfsH -> String -> Maybe String -> [String] -> Bool -> Int -> String -> String -> IO ()
174 test0 h str optstr strlist b integer filein fileout = do
175   r <- withCString str $ \str -> maybeWith withCString optstr $ \optstr -> withMany withCString strlist $ \strlist -> withArray0 nullPtr strlist $ \strlist -> withCString filein $ \filein -> withCString fileout $ \fileout -> withForeignPtr h (\p -> c_test0 p str optstr strlist (fromBool b) (fromIntegral integer) filein fileout)
176   if (r == -1)
177     then do
178       err <- last_error h
179       fail err
180     else return ()
181
182 foreign import ccall unsafe "guestfs_test0rint" c_test0rint
183   :: GuestfsP -> CString -> IO (CInt)
184
185 test0rint :: GuestfsH -> String -> IO (Int)
186 test0rint h val = do
187   r <- withCString val $ \val -> withForeignPtr h (\p -> c_test0rint p val)
188   if (r == -1)
189     then do
190       err <- last_error h
191       fail err
192     else return (fromIntegral r)
193
194 foreign import ccall unsafe "guestfs_test0rinterr" c_test0rinterr
195   :: GuestfsP -> IO (CInt)
196
197 test0rinterr :: GuestfsH -> IO (Int)
198 test0rinterr h = do
199   r <- withForeignPtr h (\p -> c_test0rinterr p)
200   if (r == -1)
201     then do
202       err <- last_error h
203       fail err
204     else return (fromIntegral r)
205
206 foreign import ccall unsafe "guestfs_test0rint64" c_test0rint64
207   :: GuestfsP -> CString -> IO (Int64)
208
209 test0rint64 :: GuestfsH -> String -> IO (Integer)
210 test0rint64 h val = do
211   r <- withCString val $ \val -> withForeignPtr h (\p -> c_test0rint64 p val)
212   if (r == -1)
213     then do
214       err <- last_error h
215       fail err
216     else return (fromIntegral r)
217
218 foreign import ccall unsafe "guestfs_test0rint64err" c_test0rint64err
219   :: GuestfsP -> IO (Int64)
220
221 test0rint64err :: GuestfsH -> IO (Integer)
222 test0rint64err h = do
223   r <- withForeignPtr h (\p -> c_test0rint64err p)
224   if (r == -1)
225     then do
226       err <- last_error h
227       fail err
228     else return (fromIntegral r)
229
230 foreign import ccall unsafe "guestfs_launch" c_launch
231   :: GuestfsP -> IO (CInt)
232
233 launch :: GuestfsH -> IO ()
234 launch h = do
235   r <- withForeignPtr h (\p -> c_launch p)
236   if (r == -1)
237     then do
238       err <- last_error h
239       fail err
240     else return ()
241
242 foreign import ccall unsafe "guestfs_wait_ready" c_wait_ready
243   :: GuestfsP -> IO (CInt)
244
245 wait_ready :: GuestfsH -> IO ()
246 wait_ready h = do
247   r <- withForeignPtr h (\p -> c_wait_ready p)
248   if (r == -1)
249     then do
250       err <- last_error h
251       fail err
252     else return ()
253
254 foreign import ccall unsafe "guestfs_kill_subprocess" c_kill_subprocess
255   :: GuestfsP -> IO (CInt)
256
257 kill_subprocess :: GuestfsH -> IO ()
258 kill_subprocess h = do
259   r <- withForeignPtr h (\p -> c_kill_subprocess p)
260   if (r == -1)
261     then do
262       err <- last_error h
263       fail err
264     else return ()
265
266 foreign import ccall unsafe "guestfs_add_drive" c_add_drive
267   :: GuestfsP -> CString -> IO (CInt)
268
269 add_drive :: GuestfsH -> String -> IO ()
270 add_drive h filename = do
271   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_drive p filename)
272   if (r == -1)
273     then do
274       err <- last_error h
275       fail err
276     else return ()
277
278 foreign import ccall unsafe "guestfs_add_cdrom" c_add_cdrom
279   :: GuestfsP -> CString -> IO (CInt)
280
281 add_cdrom :: GuestfsH -> String -> IO ()
282 add_cdrom h filename = do
283   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_cdrom p filename)
284   if (r == -1)
285     then do
286       err <- last_error h
287       fail err
288     else return ()
289
290 foreign import ccall unsafe "guestfs_add_drive_ro" c_add_drive_ro
291   :: GuestfsP -> CString -> IO (CInt)
292
293 add_drive_ro :: GuestfsH -> String -> IO ()
294 add_drive_ro h filename = do
295   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_drive_ro p filename)
296   if (r == -1)
297     then do
298       err <- last_error h
299       fail err
300     else return ()
301
302 foreign import ccall unsafe "guestfs_config" c_config
303   :: GuestfsP -> CString -> CString -> IO (CInt)
304
305 config :: GuestfsH -> String -> Maybe String -> IO ()
306 config h qemuparam qemuvalue = do
307   r <- withCString qemuparam $ \qemuparam -> maybeWith withCString qemuvalue $ \qemuvalue -> withForeignPtr h (\p -> c_config p qemuparam qemuvalue)
308   if (r == -1)
309     then do
310       err <- last_error h
311       fail err
312     else return ()
313
314 foreign import ccall unsafe "guestfs_set_qemu" c_set_qemu
315   :: GuestfsP -> CString -> IO (CInt)
316
317 set_qemu :: GuestfsH -> String -> IO ()
318 set_qemu h qemu = do
319   r <- withCString qemu $ \qemu -> withForeignPtr h (\p -> c_set_qemu p qemu)
320   if (r == -1)
321     then do
322       err <- last_error h
323       fail err
324     else return ()
325
326 foreign import ccall unsafe "guestfs_set_path" c_set_path
327   :: GuestfsP -> CString -> IO (CInt)
328
329 set_path :: GuestfsH -> String -> IO ()
330 set_path h path = do
331   r <- withCString path $ \path -> withForeignPtr h (\p -> c_set_path p path)
332   if (r == -1)
333     then do
334       err <- last_error h
335       fail err
336     else return ()
337
338 foreign import ccall unsafe "guestfs_set_append" c_set_append
339   :: GuestfsP -> CString -> IO (CInt)
340
341 set_append :: GuestfsH -> String -> IO ()
342 set_append h append = do
343   r <- withCString append $ \append -> withForeignPtr h (\p -> c_set_append p append)
344   if (r == -1)
345     then do
346       err <- last_error h
347       fail err
348     else return ()
349
350 foreign import ccall unsafe "guestfs_set_autosync" c_set_autosync
351   :: GuestfsP -> CInt -> IO (CInt)
352
353 set_autosync :: GuestfsH -> Bool -> IO ()
354 set_autosync h autosync = do
355   r <- withForeignPtr h (\p -> c_set_autosync p (fromBool autosync))
356   if (r == -1)
357     then do
358       err <- last_error h
359       fail err
360     else return ()
361
362 foreign import ccall unsafe "guestfs_set_verbose" c_set_verbose
363   :: GuestfsP -> CInt -> IO (CInt)
364
365 set_verbose :: GuestfsH -> Bool -> IO ()
366 set_verbose h verbose = do
367   r <- withForeignPtr h (\p -> c_set_verbose p (fromBool verbose))
368   if (r == -1)
369     then do
370       err <- last_error h
371       fail err
372     else return ()
373
374 foreign import ccall unsafe "guestfs_get_state" c_get_state
375   :: GuestfsP -> IO (CInt)
376
377 get_state :: GuestfsH -> IO (Int)
378 get_state h = do
379   r <- withForeignPtr h (\p -> c_get_state p)
380   if (r == -1)
381     then do
382       err <- last_error h
383       fail err
384     else return (fromIntegral r)
385
386 foreign import ccall unsafe "guestfs_set_busy" c_set_busy
387   :: GuestfsP -> IO (CInt)
388
389 set_busy :: GuestfsH -> IO ()
390 set_busy h = do
391   r <- withForeignPtr h (\p -> c_set_busy p)
392   if (r == -1)
393     then do
394       err <- last_error h
395       fail err
396     else return ()
397
398 foreign import ccall unsafe "guestfs_set_ready" c_set_ready
399   :: GuestfsP -> IO (CInt)
400
401 set_ready :: GuestfsH -> IO ()
402 set_ready h = do
403   r <- withForeignPtr h (\p -> c_set_ready p)
404   if (r == -1)
405     then do
406       err <- last_error h
407       fail err
408     else return ()
409
410 foreign import ccall unsafe "guestfs_end_busy" c_end_busy
411   :: GuestfsP -> IO (CInt)
412
413 end_busy :: GuestfsH -> IO ()
414 end_busy h = do
415   r <- withForeignPtr h (\p -> c_end_busy p)
416   if (r == -1)
417     then do
418       err <- last_error h
419       fail err
420     else return ()
421
422 foreign import ccall unsafe "guestfs_mount" c_mount
423   :: GuestfsP -> CString -> CString -> IO (CInt)
424
425 mount :: GuestfsH -> String -> String -> IO ()
426 mount h device mountpoint = do
427   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount p device mountpoint)
428   if (r == -1)
429     then do
430       err <- last_error h
431       fail err
432     else return ()
433
434 foreign import ccall unsafe "guestfs_sync" c_sync
435   :: GuestfsP -> IO (CInt)
436
437 sync :: GuestfsH -> IO ()
438 sync h = do
439   r <- withForeignPtr h (\p -> c_sync p)
440   if (r == -1)
441     then do
442       err <- last_error h
443       fail err
444     else return ()
445
446 foreign import ccall unsafe "guestfs_touch" c_touch
447   :: GuestfsP -> CString -> IO (CInt)
448
449 touch :: GuestfsH -> String -> IO ()
450 touch h path = do
451   r <- withCString path $ \path -> withForeignPtr h (\p -> c_touch p path)
452   if (r == -1)
453     then do
454       err <- last_error h
455       fail err
456     else return ()
457
458 foreign import ccall unsafe "guestfs_aug_init" c_aug_init
459   :: GuestfsP -> CString -> CInt -> IO (CInt)
460
461 aug_init :: GuestfsH -> String -> Int -> IO ()
462 aug_init h root flags = do
463   r <- withCString root $ \root -> withForeignPtr h (\p -> c_aug_init p root (fromIntegral flags))
464   if (r == -1)
465     then do
466       err <- last_error h
467       fail err
468     else return ()
469
470 foreign import ccall unsafe "guestfs_aug_close" c_aug_close
471   :: GuestfsP -> IO (CInt)
472
473 aug_close :: GuestfsH -> IO ()
474 aug_close h = do
475   r <- withForeignPtr h (\p -> c_aug_close p)
476   if (r == -1)
477     then do
478       err <- last_error h
479       fail err
480     else return ()
481
482 foreign import ccall unsafe "guestfs_aug_defvar" c_aug_defvar
483   :: GuestfsP -> CString -> CString -> IO (CInt)
484
485 aug_defvar :: GuestfsH -> String -> Maybe String -> IO (Int)
486 aug_defvar h name expr = do
487   r <- withCString name $ \name -> maybeWith withCString expr $ \expr -> withForeignPtr h (\p -> c_aug_defvar p name expr)
488   if (r == -1)
489     then do
490       err <- last_error h
491       fail err
492     else return (fromIntegral r)
493
494 foreign import ccall unsafe "guestfs_aug_set" c_aug_set
495   :: GuestfsP -> CString -> CString -> IO (CInt)
496
497 aug_set :: GuestfsH -> String -> String -> IO ()
498 aug_set h path val = do
499   r <- withCString path $ \path -> withCString val $ \val -> withForeignPtr h (\p -> c_aug_set p path val)
500   if (r == -1)
501     then do
502       err <- last_error h
503       fail err
504     else return ()
505
506 foreign import ccall unsafe "guestfs_aug_insert" c_aug_insert
507   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
508
509 aug_insert :: GuestfsH -> String -> String -> Bool -> IO ()
510 aug_insert h path label before = do
511   r <- withCString path $ \path -> withCString label $ \label -> withForeignPtr h (\p -> c_aug_insert p path label (fromBool before))
512   if (r == -1)
513     then do
514       err <- last_error h
515       fail err
516     else return ()
517
518 foreign import ccall unsafe "guestfs_aug_rm" c_aug_rm
519   :: GuestfsP -> CString -> IO (CInt)
520
521 aug_rm :: GuestfsH -> String -> IO (Int)
522 aug_rm h path = do
523   r <- withCString path $ \path -> withForeignPtr h (\p -> c_aug_rm p path)
524   if (r == -1)
525     then do
526       err <- last_error h
527       fail err
528     else return (fromIntegral r)
529
530 foreign import ccall unsafe "guestfs_aug_mv" c_aug_mv
531   :: GuestfsP -> CString -> CString -> IO (CInt)
532
533 aug_mv :: GuestfsH -> String -> String -> IO ()
534 aug_mv h src dest = do
535   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_aug_mv p src dest)
536   if (r == -1)
537     then do
538       err <- last_error h
539       fail err
540     else return ()
541
542 foreign import ccall unsafe "guestfs_aug_save" c_aug_save
543   :: GuestfsP -> IO (CInt)
544
545 aug_save :: GuestfsH -> IO ()
546 aug_save h = do
547   r <- withForeignPtr h (\p -> c_aug_save p)
548   if (r == -1)
549     then do
550       err <- last_error h
551       fail err
552     else return ()
553
554 foreign import ccall unsafe "guestfs_aug_load" c_aug_load
555   :: GuestfsP -> IO (CInt)
556
557 aug_load :: GuestfsH -> IO ()
558 aug_load h = do
559   r <- withForeignPtr h (\p -> c_aug_load p)
560   if (r == -1)
561     then do
562       err <- last_error h
563       fail err
564     else return ()
565
566 foreign import ccall unsafe "guestfs_rm" c_rm
567   :: GuestfsP -> CString -> IO (CInt)
568
569 rm :: GuestfsH -> String -> IO ()
570 rm h path = do
571   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm p path)
572   if (r == -1)
573     then do
574       err <- last_error h
575       fail err
576     else return ()
577
578 foreign import ccall unsafe "guestfs_rmdir" c_rmdir
579   :: GuestfsP -> CString -> IO (CInt)
580
581 rmdir :: GuestfsH -> String -> IO ()
582 rmdir h path = do
583   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rmdir p path)
584   if (r == -1)
585     then do
586       err <- last_error h
587       fail err
588     else return ()
589
590 foreign import ccall unsafe "guestfs_rm_rf" c_rm_rf
591   :: GuestfsP -> CString -> IO (CInt)
592
593 rm_rf :: GuestfsH -> String -> IO ()
594 rm_rf h path = do
595   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm_rf p path)
596   if (r == -1)
597     then do
598       err <- last_error h
599       fail err
600     else return ()
601
602 foreign import ccall unsafe "guestfs_mkdir" c_mkdir
603   :: GuestfsP -> CString -> IO (CInt)
604
605 mkdir :: GuestfsH -> String -> IO ()
606 mkdir h path = do
607   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir p path)
608   if (r == -1)
609     then do
610       err <- last_error h
611       fail err
612     else return ()
613
614 foreign import ccall unsafe "guestfs_mkdir_p" c_mkdir_p
615   :: GuestfsP -> CString -> IO (CInt)
616
617 mkdir_p :: GuestfsH -> String -> IO ()
618 mkdir_p h path = do
619   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir_p p path)
620   if (r == -1)
621     then do
622       err <- last_error h
623       fail err
624     else return ()
625
626 foreign import ccall unsafe "guestfs_chmod" c_chmod
627   :: GuestfsP -> CInt -> CString -> IO (CInt)
628
629 chmod :: GuestfsH -> Int -> String -> IO ()
630 chmod h mode path = do
631   r <- withCString path $ \path -> withForeignPtr h (\p -> c_chmod p (fromIntegral mode) path)
632   if (r == -1)
633     then do
634       err <- last_error h
635       fail err
636     else return ()
637
638 foreign import ccall unsafe "guestfs_chown" c_chown
639   :: GuestfsP -> CInt -> CInt -> CString -> IO (CInt)
640
641 chown :: GuestfsH -> Int -> Int -> String -> IO ()
642 chown h owner group path = do
643   r <- withCString path $ \path -> withForeignPtr h (\p -> c_chown p (fromIntegral owner) (fromIntegral group) path)
644   if (r == -1)
645     then do
646       err <- last_error h
647       fail err
648     else return ()
649
650 foreign import ccall unsafe "guestfs_pvcreate" c_pvcreate
651   :: GuestfsP -> CString -> IO (CInt)
652
653 pvcreate :: GuestfsH -> String -> IO ()
654 pvcreate h device = do
655   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvcreate p device)
656   if (r == -1)
657     then do
658       err <- last_error h
659       fail err
660     else return ()
661
662 foreign import ccall unsafe "guestfs_vgcreate" c_vgcreate
663   :: GuestfsP -> CString -> Ptr CString -> IO (CInt)
664
665 vgcreate :: GuestfsH -> String -> [String] -> IO ()
666 vgcreate h volgroup physvols = do
667   r <- withCString volgroup $ \volgroup -> withMany withCString physvols $ \physvols -> withArray0 nullPtr physvols $ \physvols -> withForeignPtr h (\p -> c_vgcreate p volgroup physvols)
668   if (r == -1)
669     then do
670       err <- last_error h
671       fail err
672     else return ()
673
674 foreign import ccall unsafe "guestfs_lvcreate" c_lvcreate
675   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
676
677 lvcreate :: GuestfsH -> String -> String -> Int -> IO ()
678 lvcreate h logvol volgroup mbytes = do
679   r <- withCString logvol $ \logvol -> withCString volgroup $ \volgroup -> withForeignPtr h (\p -> c_lvcreate p logvol volgroup (fromIntegral mbytes))
680   if (r == -1)
681     then do
682       err <- last_error h
683       fail err
684     else return ()
685
686 foreign import ccall unsafe "guestfs_mkfs" c_mkfs
687   :: GuestfsP -> CString -> CString -> IO (CInt)
688
689 mkfs :: GuestfsH -> String -> String -> IO ()
690 mkfs h fstype device = do
691   r <- withCString fstype $ \fstype -> withCString device $ \device -> withForeignPtr h (\p -> c_mkfs p fstype device)
692   if (r == -1)
693     then do
694       err <- last_error h
695       fail err
696     else return ()
697
698 foreign import ccall unsafe "guestfs_sfdisk" c_sfdisk
699   :: GuestfsP -> CString -> CInt -> CInt -> CInt -> Ptr CString -> IO (CInt)
700
701 sfdisk :: GuestfsH -> String -> Int -> Int -> Int -> [String] -> IO ()
702 sfdisk h device cyls heads sectors lines = do
703   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)
704   if (r == -1)
705     then do
706       err <- last_error h
707       fail err
708     else return ()
709
710 foreign import ccall unsafe "guestfs_write_file" c_write_file
711   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
712
713 write_file :: GuestfsH -> String -> String -> Int -> IO ()
714 write_file h path content size = do
715   r <- withCString path $ \path -> withCString content $ \content -> withForeignPtr h (\p -> c_write_file p path content (fromIntegral size))
716   if (r == -1)
717     then do
718       err <- last_error h
719       fail err
720     else return ()
721
722 foreign import ccall unsafe "guestfs_umount" c_umount
723   :: GuestfsP -> CString -> IO (CInt)
724
725 umount :: GuestfsH -> String -> IO ()
726 umount h pathordevice = do
727   r <- withCString pathordevice $ \pathordevice -> withForeignPtr h (\p -> c_umount p pathordevice)
728   if (r == -1)
729     then do
730       err <- last_error h
731       fail err
732     else return ()
733
734 foreign import ccall unsafe "guestfs_umount_all" c_umount_all
735   :: GuestfsP -> IO (CInt)
736
737 umount_all :: GuestfsH -> IO ()
738 umount_all h = do
739   r <- withForeignPtr h (\p -> c_umount_all p)
740   if (r == -1)
741     then do
742       err <- last_error h
743       fail err
744     else return ()
745
746 foreign import ccall unsafe "guestfs_lvm_remove_all" c_lvm_remove_all
747   :: GuestfsP -> IO (CInt)
748
749 lvm_remove_all :: GuestfsH -> IO ()
750 lvm_remove_all h = do
751   r <- withForeignPtr h (\p -> c_lvm_remove_all p)
752   if (r == -1)
753     then do
754       err <- last_error h
755       fail err
756     else return ()
757
758 foreign import ccall unsafe "guestfs_blockdev_setro" c_blockdev_setro
759   :: GuestfsP -> CString -> IO (CInt)
760
761 blockdev_setro :: GuestfsH -> String -> IO ()
762 blockdev_setro h device = do
763   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setro p device)
764   if (r == -1)
765     then do
766       err <- last_error h
767       fail err
768     else return ()
769
770 foreign import ccall unsafe "guestfs_blockdev_setrw" c_blockdev_setrw
771   :: GuestfsP -> CString -> IO (CInt)
772
773 blockdev_setrw :: GuestfsH -> String -> IO ()
774 blockdev_setrw h device = do
775   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setrw p device)
776   if (r == -1)
777     then do
778       err <- last_error h
779       fail err
780     else return ()
781
782 foreign import ccall unsafe "guestfs_blockdev_getss" c_blockdev_getss
783   :: GuestfsP -> CString -> IO (CInt)
784
785 blockdev_getss :: GuestfsH -> String -> IO (Int)
786 blockdev_getss h device = do
787   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getss p device)
788   if (r == -1)
789     then do
790       err <- last_error h
791       fail err
792     else return (fromIntegral r)
793
794 foreign import ccall unsafe "guestfs_blockdev_getbsz" c_blockdev_getbsz
795   :: GuestfsP -> CString -> IO (CInt)
796
797 blockdev_getbsz :: GuestfsH -> String -> IO (Int)
798 blockdev_getbsz h device = do
799   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getbsz p device)
800   if (r == -1)
801     then do
802       err <- last_error h
803       fail err
804     else return (fromIntegral r)
805
806 foreign import ccall unsafe "guestfs_blockdev_setbsz" c_blockdev_setbsz
807   :: GuestfsP -> CString -> CInt -> IO (CInt)
808
809 blockdev_setbsz :: GuestfsH -> String -> Int -> IO ()
810 blockdev_setbsz h device blocksize = do
811   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setbsz p device (fromIntegral blocksize))
812   if (r == -1)
813     then do
814       err <- last_error h
815       fail err
816     else return ()
817
818 foreign import ccall unsafe "guestfs_blockdev_getsz" c_blockdev_getsz
819   :: GuestfsP -> CString -> IO (Int64)
820
821 blockdev_getsz :: GuestfsH -> String -> IO (Integer)
822 blockdev_getsz h device = do
823   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getsz p device)
824   if (r == -1)
825     then do
826       err <- last_error h
827       fail err
828     else return (fromIntegral r)
829
830 foreign import ccall unsafe "guestfs_blockdev_getsize64" c_blockdev_getsize64
831   :: GuestfsP -> CString -> IO (Int64)
832
833 blockdev_getsize64 :: GuestfsH -> String -> IO (Integer)
834 blockdev_getsize64 h device = do
835   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getsize64 p device)
836   if (r == -1)
837     then do
838       err <- last_error h
839       fail err
840     else return (fromIntegral r)
841
842 foreign import ccall unsafe "guestfs_blockdev_flushbufs" c_blockdev_flushbufs
843   :: GuestfsP -> CString -> IO (CInt)
844
845 blockdev_flushbufs :: GuestfsH -> String -> IO ()
846 blockdev_flushbufs h device = do
847   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_flushbufs p device)
848   if (r == -1)
849     then do
850       err <- last_error h
851       fail err
852     else return ()
853
854 foreign import ccall unsafe "guestfs_blockdev_rereadpt" c_blockdev_rereadpt
855   :: GuestfsP -> CString -> IO (CInt)
856
857 blockdev_rereadpt :: GuestfsH -> String -> IO ()
858 blockdev_rereadpt h device = do
859   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_rereadpt p device)
860   if (r == -1)
861     then do
862       err <- last_error h
863       fail err
864     else return ()
865
866 foreign import ccall unsafe "guestfs_upload" c_upload
867   :: GuestfsP -> CString -> CString -> IO (CInt)
868
869 upload :: GuestfsH -> String -> String -> IO ()
870 upload h filename remotefilename = do
871   r <- withCString filename $ \filename -> withCString remotefilename $ \remotefilename -> withForeignPtr h (\p -> c_upload p filename remotefilename)
872   if (r == -1)
873     then do
874       err <- last_error h
875       fail err
876     else return ()
877
878 foreign import ccall unsafe "guestfs_download" c_download
879   :: GuestfsP -> CString -> CString -> IO (CInt)
880
881 download :: GuestfsH -> String -> String -> IO ()
882 download h remotefilename filename = do
883   r <- withCString remotefilename $ \remotefilename -> withCString filename $ \filename -> withForeignPtr h (\p -> c_download p remotefilename filename)
884   if (r == -1)
885     then do
886       err <- last_error h
887       fail err
888     else return ()
889
890 foreign import ccall unsafe "guestfs_tar_in" c_tar_in
891   :: GuestfsP -> CString -> CString -> IO (CInt)
892
893 tar_in :: GuestfsH -> String -> String -> IO ()
894 tar_in h tarfile directory = do
895   r <- withCString tarfile $ \tarfile -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tar_in p tarfile directory)
896   if (r == -1)
897     then do
898       err <- last_error h
899       fail err
900     else return ()
901
902 foreign import ccall unsafe "guestfs_tar_out" c_tar_out
903   :: GuestfsP -> CString -> CString -> IO (CInt)
904
905 tar_out :: GuestfsH -> String -> String -> IO ()
906 tar_out h directory tarfile = do
907   r <- withCString directory $ \directory -> withCString tarfile $ \tarfile -> withForeignPtr h (\p -> c_tar_out p directory tarfile)
908   if (r == -1)
909     then do
910       err <- last_error h
911       fail err
912     else return ()
913
914 foreign import ccall unsafe "guestfs_tgz_in" c_tgz_in
915   :: GuestfsP -> CString -> CString -> IO (CInt)
916
917 tgz_in :: GuestfsH -> String -> String -> IO ()
918 tgz_in h tarball directory = do
919   r <- withCString tarball $ \tarball -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tgz_in p tarball directory)
920   if (r == -1)
921     then do
922       err <- last_error h
923       fail err
924     else return ()
925
926 foreign import ccall unsafe "guestfs_tgz_out" c_tgz_out
927   :: GuestfsP -> CString -> CString -> IO (CInt)
928
929 tgz_out :: GuestfsH -> String -> String -> IO ()
930 tgz_out h directory tarball = do
931   r <- withCString directory $ \directory -> withCString tarball $ \tarball -> withForeignPtr h (\p -> c_tgz_out p directory tarball)
932   if (r == -1)
933     then do
934       err <- last_error h
935       fail err
936     else return ()
937
938 foreign import ccall unsafe "guestfs_mount_ro" c_mount_ro
939   :: GuestfsP -> CString -> CString -> IO (CInt)
940
941 mount_ro :: GuestfsH -> String -> String -> IO ()
942 mount_ro h device mountpoint = do
943   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_ro p device mountpoint)
944   if (r == -1)
945     then do
946       err <- last_error h
947       fail err
948     else return ()
949
950 foreign import ccall unsafe "guestfs_mount_options" c_mount_options
951   :: GuestfsP -> CString -> CString -> CString -> IO (CInt)
952
953 mount_options :: GuestfsH -> String -> String -> String -> IO ()
954 mount_options h options device mountpoint = do
955   r <- withCString options $ \options -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_options p options device mountpoint)
956   if (r == -1)
957     then do
958       err <- last_error h
959       fail err
960     else return ()
961
962 foreign import ccall unsafe "guestfs_mount_vfs" c_mount_vfs
963   :: GuestfsP -> CString -> CString -> CString -> CString -> IO (CInt)
964
965 mount_vfs :: GuestfsH -> String -> String -> String -> String -> IO ()
966 mount_vfs h options vfstype device mountpoint = do
967   r <- withCString options $ \options -> withCString vfstype $ \vfstype -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_vfs p options vfstype device mountpoint)
968   if (r == -1)
969     then do
970       err <- last_error h
971       fail err
972     else return ()
973
974 foreign import ccall unsafe "guestfs_lvremove" c_lvremove
975   :: GuestfsP -> CString -> IO (CInt)
976
977 lvremove :: GuestfsH -> String -> IO ()
978 lvremove h device = do
979   r <- withCString device $ \device -> withForeignPtr h (\p -> c_lvremove p device)
980   if (r == -1)
981     then do
982       err <- last_error h
983       fail err
984     else return ()
985
986 foreign import ccall unsafe "guestfs_vgremove" c_vgremove
987   :: GuestfsP -> CString -> IO (CInt)
988
989 vgremove :: GuestfsH -> String -> IO ()
990 vgremove h vgname = do
991   r <- withCString vgname $ \vgname -> withForeignPtr h (\p -> c_vgremove p vgname)
992   if (r == -1)
993     then do
994       err <- last_error h
995       fail err
996     else return ()
997
998 foreign import ccall unsafe "guestfs_pvremove" c_pvremove
999   :: GuestfsP -> CString -> IO (CInt)
1000
1001 pvremove :: GuestfsH -> String -> IO ()
1002 pvremove h device = do
1003   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvremove p device)
1004   if (r == -1)
1005     then do
1006       err <- last_error h
1007       fail err
1008     else return ()
1009
1010 foreign import ccall unsafe "guestfs_set_e2label" c_set_e2label
1011   :: GuestfsP -> CString -> CString -> IO (CInt)
1012
1013 set_e2label :: GuestfsH -> String -> String -> IO ()
1014 set_e2label h device label = do
1015   r <- withCString device $ \device -> withCString label $ \label -> withForeignPtr h (\p -> c_set_e2label p device label)
1016   if (r == -1)
1017     then do
1018       err <- last_error h
1019       fail err
1020     else return ()
1021
1022 foreign import ccall unsafe "guestfs_set_e2uuid" c_set_e2uuid
1023   :: GuestfsP -> CString -> CString -> IO (CInt)
1024
1025 set_e2uuid :: GuestfsH -> String -> String -> IO ()
1026 set_e2uuid h device uuid = do
1027   r <- withCString device $ \device -> withCString uuid $ \uuid -> withForeignPtr h (\p -> c_set_e2uuid p device uuid)
1028   if (r == -1)
1029     then do
1030       err <- last_error h
1031       fail err
1032     else return ()
1033
1034 foreign import ccall unsafe "guestfs_fsck" c_fsck
1035   :: GuestfsP -> CString -> CString -> IO (CInt)
1036
1037 fsck :: GuestfsH -> String -> String -> IO (Int)
1038 fsck h fstype device = do
1039   r <- withCString fstype $ \fstype -> withCString device $ \device -> withForeignPtr h (\p -> c_fsck p fstype device)
1040   if (r == -1)
1041     then do
1042       err <- last_error h
1043       fail err
1044     else return (fromIntegral r)
1045
1046 foreign import ccall unsafe "guestfs_zero" c_zero
1047   :: GuestfsP -> CString -> IO (CInt)
1048
1049 zero :: GuestfsH -> String -> IO ()
1050 zero h device = do
1051   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zero p device)
1052   if (r == -1)
1053     then do
1054       err <- last_error h
1055       fail err
1056     else return ()
1057
1058 foreign import ccall unsafe "guestfs_grub_install" c_grub_install
1059   :: GuestfsP -> CString -> CString -> IO (CInt)
1060
1061 grub_install :: GuestfsH -> String -> String -> IO ()
1062 grub_install h root device = do
1063   r <- withCString root $ \root -> withCString device $ \device -> withForeignPtr h (\p -> c_grub_install p root device)
1064   if (r == -1)
1065     then do
1066       err <- last_error h
1067       fail err
1068     else return ()
1069
1070 foreign import ccall unsafe "guestfs_cp" c_cp
1071   :: GuestfsP -> CString -> CString -> IO (CInt)
1072
1073 cp :: GuestfsH -> String -> String -> IO ()
1074 cp h src dest = do
1075   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp p src dest)
1076   if (r == -1)
1077     then do
1078       err <- last_error h
1079       fail err
1080     else return ()
1081
1082 foreign import ccall unsafe "guestfs_cp_a" c_cp_a
1083   :: GuestfsP -> CString -> CString -> IO (CInt)
1084
1085 cp_a :: GuestfsH -> String -> String -> IO ()
1086 cp_a h src dest = do
1087   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp_a p src dest)
1088   if (r == -1)
1089     then do
1090       err <- last_error h
1091       fail err
1092     else return ()
1093
1094 foreign import ccall unsafe "guestfs_mv" c_mv
1095   :: GuestfsP -> CString -> CString -> IO (CInt)
1096
1097 mv :: GuestfsH -> String -> String -> IO ()
1098 mv h src dest = do
1099   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_mv p src dest)
1100   if (r == -1)
1101     then do
1102       err <- last_error h
1103       fail err
1104     else return ()
1105
1106 foreign import ccall unsafe "guestfs_drop_caches" c_drop_caches
1107   :: GuestfsP -> CInt -> IO (CInt)
1108
1109 drop_caches :: GuestfsH -> Int -> IO ()
1110 drop_caches h whattodrop = do
1111   r <- withForeignPtr h (\p -> c_drop_caches p (fromIntegral whattodrop))
1112   if (r == -1)
1113     then do
1114       err <- last_error h
1115       fail err
1116     else return ()
1117
1118 foreign import ccall unsafe "guestfs_ping_daemon" c_ping_daemon
1119   :: GuestfsP -> IO (CInt)
1120
1121 ping_daemon :: GuestfsH -> IO ()
1122 ping_daemon h = do
1123   r <- withForeignPtr h (\p -> c_ping_daemon p)
1124   if (r == -1)
1125     then do
1126       err <- last_error h
1127       fail err
1128     else return ()
1129
1130 foreign import ccall unsafe "guestfs_zerofree" c_zerofree
1131   :: GuestfsP -> CString -> IO (CInt)
1132
1133 zerofree :: GuestfsH -> String -> IO ()
1134 zerofree h device = do
1135   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zerofree p device)
1136   if (r == -1)
1137     then do
1138       err <- last_error h
1139       fail err
1140     else return ()
1141
1142 foreign import ccall unsafe "guestfs_pvresize" c_pvresize
1143   :: GuestfsP -> CString -> IO (CInt)
1144
1145 pvresize :: GuestfsH -> String -> IO ()
1146 pvresize h device = do
1147   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvresize p device)
1148   if (r == -1)
1149     then do
1150       err <- last_error h
1151       fail err
1152     else return ()
1153
1154 foreign import ccall unsafe "guestfs_sfdisk_N" c_sfdisk_N
1155   :: GuestfsP -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (CInt)
1156
1157 sfdisk_N :: GuestfsH -> String -> Int -> Int -> Int -> Int -> String -> IO ()
1158 sfdisk_N h device n cyls heads sectors line = do
1159   r <- withCString device $ \device -> withCString line $ \line -> withForeignPtr h (\p -> c_sfdisk_N p device (fromIntegral n) (fromIntegral cyls) (fromIntegral heads) (fromIntegral sectors) line)
1160   if (r == -1)
1161     then do
1162       err <- last_error h
1163       fail err
1164     else return ()
1165
1166 foreign import ccall unsafe "guestfs_vg_activate_all" c_vg_activate_all
1167   :: GuestfsP -> CInt -> IO (CInt)
1168
1169 vg_activate_all :: GuestfsH -> Bool -> IO ()
1170 vg_activate_all h activate = do
1171   r <- withForeignPtr h (\p -> c_vg_activate_all p (fromBool activate))
1172   if (r == -1)
1173     then do
1174       err <- last_error h
1175       fail err
1176     else return ()
1177
1178 foreign import ccall unsafe "guestfs_vg_activate" c_vg_activate
1179   :: GuestfsP -> CInt -> Ptr CString -> IO (CInt)
1180
1181 vg_activate :: GuestfsH -> Bool -> [String] -> IO ()
1182 vg_activate h activate volgroups = do
1183   r <- withMany withCString volgroups $ \volgroups -> withArray0 nullPtr volgroups $ \volgroups -> withForeignPtr h (\p -> c_vg_activate p (fromBool activate) volgroups)
1184   if (r == -1)
1185     then do
1186       err <- last_error h
1187       fail err
1188     else return ()
1189
1190 foreign import ccall unsafe "guestfs_lvresize" c_lvresize
1191   :: GuestfsP -> CString -> CInt -> IO (CInt)
1192
1193 lvresize :: GuestfsH -> String -> Int -> IO ()
1194 lvresize h device mbytes = do
1195   r <- withCString device $ \device -> withForeignPtr h (\p -> c_lvresize p device (fromIntegral mbytes))
1196   if (r == -1)
1197     then do
1198       err <- last_error h
1199       fail err
1200     else return ()
1201
1202 foreign import ccall unsafe "guestfs_resize2fs" c_resize2fs
1203   :: GuestfsP -> CString -> IO (CInt)
1204
1205 resize2fs :: GuestfsH -> String -> IO ()
1206 resize2fs h device = do
1207   r <- withCString device $ \device -> withForeignPtr h (\p -> c_resize2fs p device)
1208   if (r == -1)
1209     then do
1210       err <- last_error h
1211       fail err
1212     else return ()
1213
1214 foreign import ccall unsafe "guestfs_e2fsck_f" c_e2fsck_f
1215   :: GuestfsP -> CString -> IO (CInt)
1216
1217 e2fsck_f :: GuestfsH -> String -> IO ()
1218 e2fsck_f h device = do
1219   r <- withCString device $ \device -> withForeignPtr h (\p -> c_e2fsck_f p device)
1220   if (r == -1)
1221     then do
1222       err <- last_error h
1223       fail err
1224     else return ()
1225
1226 foreign import ccall unsafe "guestfs_sleep" c_sleep
1227   :: GuestfsP -> CInt -> IO (CInt)
1228
1229 sleep :: GuestfsH -> Int -> IO ()
1230 sleep h secs = do
1231   r <- withForeignPtr h (\p -> c_sleep p (fromIntegral secs))
1232   if (r == -1)
1233     then do
1234       err <- last_error h
1235       fail err
1236     else return ()
1237
1238 foreign import ccall unsafe "guestfs_ntfs_3g_probe" c_ntfs_3g_probe
1239   :: GuestfsP -> CInt -> CString -> IO (CInt)
1240
1241 ntfs_3g_probe :: GuestfsH -> Bool -> String -> IO (Int)
1242 ntfs_3g_probe h rw device = do
1243   r <- withCString device $ \device -> withForeignPtr h (\p -> c_ntfs_3g_probe p (fromBool rw) device)
1244   if (r == -1)
1245     then do
1246       err <- last_error h
1247       fail err
1248     else return (fromIntegral r)
1249
1250 foreign import ccall unsafe "guestfs_scrub_device" c_scrub_device
1251   :: GuestfsP -> CString -> IO (CInt)
1252
1253 scrub_device :: GuestfsH -> String -> IO ()
1254 scrub_device h device = do
1255   r <- withCString device $ \device -> withForeignPtr h (\p -> c_scrub_device p device)
1256   if (r == -1)
1257     then do
1258       err <- last_error h
1259       fail err
1260     else return ()
1261
1262 foreign import ccall unsafe "guestfs_scrub_file" c_scrub_file
1263   :: GuestfsP -> CString -> IO (CInt)
1264
1265 scrub_file :: GuestfsH -> String -> IO ()
1266 scrub_file h file = do
1267   r <- withCString file $ \file -> withForeignPtr h (\p -> c_scrub_file p file)
1268   if (r == -1)
1269     then do
1270       err <- last_error h
1271       fail err
1272     else return ()
1273
1274 foreign import ccall unsafe "guestfs_scrub_freespace" c_scrub_freespace
1275   :: GuestfsP -> CString -> IO (CInt)
1276
1277 scrub_freespace :: GuestfsH -> String -> IO ()
1278 scrub_freespace h dir = do
1279   r <- withCString dir $ \dir -> withForeignPtr h (\p -> c_scrub_freespace p dir)
1280   if (r == -1)
1281     then do
1282       err <- last_error h
1283       fail err
1284     else return ()
1285