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