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