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