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