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