Use a squashfs attached as /dev/sdd during the C API tests.
[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   launch,
28   wait_ready,
29   kill_subprocess,
30   add_drive,
31   add_cdrom,
32   config,
33   set_qemu,
34   set_path,
35   set_append,
36   set_busy,
37   set_ready,
38   end_busy,
39   mount,
40   sync,
41   touch,
42   aug_close,
43   aug_set,
44   aug_mv,
45   aug_save,
46   aug_load,
47   rm,
48   rmdir,
49   rm_rf,
50   mkdir,
51   mkdir_p,
52   pvcreate,
53   vgcreate,
54   mkfs,
55   umount,
56   umount_all,
57   lvm_remove_all,
58   blockdev_setro,
59   blockdev_setrw,
60   blockdev_flushbufs,
61   blockdev_rereadpt,
62   upload,
63   download,
64   tar_in,
65   tar_out,
66   tgz_in,
67   tgz_out,
68   mount_ro,
69   mount_options,
70   mount_vfs,
71   lvremove,
72   vgremove,
73   pvremove,
74   set_e2label,
75   set_e2uuid,
76   zero,
77   grub_install,
78   cp,
79   cp_a,
80   mv,
81   ping_daemon,
82   zerofree,
83   pvresize,
84   resize2fs,
85   e2fsck_f
86   ) where
87 import Foreign
88 import Foreign.C
89 import IO
90 import Control.Exception
91 import Data.Typeable
92
93 data GuestfsS = GuestfsS            -- represents the opaque C struct
94 type GuestfsP = Ptr GuestfsS        -- guestfs_h *
95 type GuestfsH = ForeignPtr GuestfsS -- guestfs_h * with attached finalizer
96
97 -- XXX define properly later XXX
98 data PV = PV
99 data VG = VG
100 data LV = LV
101 data IntBool = IntBool
102 data Stat = Stat
103 data StatVFS = StatVFS
104 data Hashtable = Hashtable
105
106 foreign import ccall unsafe "guestfs_create" c_create
107   :: IO GuestfsP
108 foreign import ccall unsafe "&guestfs_close" c_close
109   :: FunPtr (GuestfsP -> IO ())
110 foreign import ccall unsafe "guestfs_set_error_handler" c_set_error_handler
111   :: GuestfsP -> Ptr CInt -> Ptr CInt -> IO ()
112
113 create :: IO GuestfsH
114 create = do
115   p <- c_create
116   c_set_error_handler p nullPtr nullPtr
117   h <- newForeignPtr c_close p
118   return h
119
120 foreign import ccall unsafe "guestfs_last_error" c_last_error
121   :: GuestfsP -> IO CString
122
123 -- last_error :: GuestfsH -> IO (Maybe String)
124 -- last_error h = do
125 --   str <- withForeignPtr h (\p -> c_last_error p)
126 --   maybePeek peekCString str
127
128 last_error :: GuestfsH -> IO (String)
129 last_error h = do
130   str <- withForeignPtr h (\p -> c_last_error p)
131   if (str == nullPtr)
132     then return "no error"
133     else peekCString str
134
135 foreign import ccall unsafe "guestfs_launch" c_launch
136   :: GuestfsP -> IO (CInt)
137
138 launch :: GuestfsH -> IO ()
139 launch h = do
140   r <- withForeignPtr h (\p -> c_launch p)
141   if (r == -1)
142     then do
143       err <- last_error h
144       fail err
145     else return ()
146
147 foreign import ccall unsafe "guestfs_wait_ready" c_wait_ready
148   :: GuestfsP -> IO (CInt)
149
150 wait_ready :: GuestfsH -> IO ()
151 wait_ready h = do
152   r <- withForeignPtr h (\p -> c_wait_ready p)
153   if (r == -1)
154     then do
155       err <- last_error h
156       fail err
157     else return ()
158
159 foreign import ccall unsafe "guestfs_kill_subprocess" c_kill_subprocess
160   :: GuestfsP -> IO (CInt)
161
162 kill_subprocess :: GuestfsH -> IO ()
163 kill_subprocess h = do
164   r <- withForeignPtr h (\p -> c_kill_subprocess p)
165   if (r == -1)
166     then do
167       err <- last_error h
168       fail err
169     else return ()
170
171 foreign import ccall unsafe "guestfs_add_drive" c_add_drive
172   :: GuestfsP -> CString -> IO (CInt)
173
174 add_drive :: GuestfsH -> String -> IO ()
175 add_drive h filename = do
176   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_drive p filename)
177   if (r == -1)
178     then do
179       err <- last_error h
180       fail err
181     else return ()
182
183 foreign import ccall unsafe "guestfs_add_cdrom" c_add_cdrom
184   :: GuestfsP -> CString -> IO (CInt)
185
186 add_cdrom :: GuestfsH -> String -> IO ()
187 add_cdrom h filename = do
188   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_cdrom p filename)
189   if (r == -1)
190     then do
191       err <- last_error h
192       fail err
193     else return ()
194
195 foreign import ccall unsafe "guestfs_config" c_config
196   :: GuestfsP -> CString -> CString -> IO (CInt)
197
198 config :: GuestfsH -> String -> Maybe String -> IO ()
199 config h qemuparam qemuvalue = do
200   r <- withCString qemuparam $ \qemuparam -> maybeWith withCString qemuvalue $ \qemuvalue -> withForeignPtr h (\p -> c_config p qemuparam qemuvalue)
201   if (r == -1)
202     then do
203       err <- last_error h
204       fail err
205     else return ()
206
207 foreign import ccall unsafe "guestfs_set_qemu" c_set_qemu
208   :: GuestfsP -> CString -> IO (CInt)
209
210 set_qemu :: GuestfsH -> String -> IO ()
211 set_qemu h qemu = do
212   r <- withCString qemu $ \qemu -> withForeignPtr h (\p -> c_set_qemu p qemu)
213   if (r == -1)
214     then do
215       err <- last_error h
216       fail err
217     else return ()
218
219 foreign import ccall unsafe "guestfs_set_path" c_set_path
220   :: GuestfsP -> CString -> IO (CInt)
221
222 set_path :: GuestfsH -> String -> IO ()
223 set_path h path = do
224   r <- withCString path $ \path -> withForeignPtr h (\p -> c_set_path p path)
225   if (r == -1)
226     then do
227       err <- last_error h
228       fail err
229     else return ()
230
231 foreign import ccall unsafe "guestfs_set_append" c_set_append
232   :: GuestfsP -> CString -> IO (CInt)
233
234 set_append :: GuestfsH -> String -> IO ()
235 set_append h append = do
236   r <- withCString append $ \append -> withForeignPtr h (\p -> c_set_append p append)
237   if (r == -1)
238     then do
239       err <- last_error h
240       fail err
241     else return ()
242
243 foreign import ccall unsafe "guestfs_set_busy" c_set_busy
244   :: GuestfsP -> IO (CInt)
245
246 set_busy :: GuestfsH -> IO ()
247 set_busy h = do
248   r <- withForeignPtr h (\p -> c_set_busy p)
249   if (r == -1)
250     then do
251       err <- last_error h
252       fail err
253     else return ()
254
255 foreign import ccall unsafe "guestfs_set_ready" c_set_ready
256   :: GuestfsP -> IO (CInt)
257
258 set_ready :: GuestfsH -> IO ()
259 set_ready h = do
260   r <- withForeignPtr h (\p -> c_set_ready p)
261   if (r == -1)
262     then do
263       err <- last_error h
264       fail err
265     else return ()
266
267 foreign import ccall unsafe "guestfs_end_busy" c_end_busy
268   :: GuestfsP -> IO (CInt)
269
270 end_busy :: GuestfsH -> IO ()
271 end_busy h = do
272   r <- withForeignPtr h (\p -> c_end_busy p)
273   if (r == -1)
274     then do
275       err <- last_error h
276       fail err
277     else return ()
278
279 foreign import ccall unsafe "guestfs_mount" c_mount
280   :: GuestfsP -> CString -> CString -> IO (CInt)
281
282 mount :: GuestfsH -> String -> String -> IO ()
283 mount h device mountpoint = do
284   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount p device mountpoint)
285   if (r == -1)
286     then do
287       err <- last_error h
288       fail err
289     else return ()
290
291 foreign import ccall unsafe "guestfs_sync" c_sync
292   :: GuestfsP -> IO (CInt)
293
294 sync :: GuestfsH -> IO ()
295 sync h = do
296   r <- withForeignPtr h (\p -> c_sync p)
297   if (r == -1)
298     then do
299       err <- last_error h
300       fail err
301     else return ()
302
303 foreign import ccall unsafe "guestfs_touch" c_touch
304   :: GuestfsP -> CString -> IO (CInt)
305
306 touch :: GuestfsH -> String -> IO ()
307 touch h path = do
308   r <- withCString path $ \path -> withForeignPtr h (\p -> c_touch p path)
309   if (r == -1)
310     then do
311       err <- last_error h
312       fail err
313     else return ()
314
315 foreign import ccall unsafe "guestfs_aug_close" c_aug_close
316   :: GuestfsP -> IO (CInt)
317
318 aug_close :: GuestfsH -> IO ()
319 aug_close h = do
320   r <- withForeignPtr h (\p -> c_aug_close p)
321   if (r == -1)
322     then do
323       err <- last_error h
324       fail err
325     else return ()
326
327 foreign import ccall unsafe "guestfs_aug_set" c_aug_set
328   :: GuestfsP -> CString -> CString -> IO (CInt)
329
330 aug_set :: GuestfsH -> String -> String -> IO ()
331 aug_set h path val = do
332   r <- withCString path $ \path -> withCString val $ \val -> withForeignPtr h (\p -> c_aug_set p path val)
333   if (r == -1)
334     then do
335       err <- last_error h
336       fail err
337     else return ()
338
339 foreign import ccall unsafe "guestfs_aug_mv" c_aug_mv
340   :: GuestfsP -> CString -> CString -> IO (CInt)
341
342 aug_mv :: GuestfsH -> String -> String -> IO ()
343 aug_mv h src dest = do
344   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_aug_mv p src dest)
345   if (r == -1)
346     then do
347       err <- last_error h
348       fail err
349     else return ()
350
351 foreign import ccall unsafe "guestfs_aug_save" c_aug_save
352   :: GuestfsP -> IO (CInt)
353
354 aug_save :: GuestfsH -> IO ()
355 aug_save h = do
356   r <- withForeignPtr h (\p -> c_aug_save p)
357   if (r == -1)
358     then do
359       err <- last_error h
360       fail err
361     else return ()
362
363 foreign import ccall unsafe "guestfs_aug_load" c_aug_load
364   :: GuestfsP -> IO (CInt)
365
366 aug_load :: GuestfsH -> IO ()
367 aug_load h = do
368   r <- withForeignPtr h (\p -> c_aug_load p)
369   if (r == -1)
370     then do
371       err <- last_error h
372       fail err
373     else return ()
374
375 foreign import ccall unsafe "guestfs_rm" c_rm
376   :: GuestfsP -> CString -> IO (CInt)
377
378 rm :: GuestfsH -> String -> IO ()
379 rm h path = do
380   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm p path)
381   if (r == -1)
382     then do
383       err <- last_error h
384       fail err
385     else return ()
386
387 foreign import ccall unsafe "guestfs_rmdir" c_rmdir
388   :: GuestfsP -> CString -> IO (CInt)
389
390 rmdir :: GuestfsH -> String -> IO ()
391 rmdir h path = do
392   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rmdir p path)
393   if (r == -1)
394     then do
395       err <- last_error h
396       fail err
397     else return ()
398
399 foreign import ccall unsafe "guestfs_rm_rf" c_rm_rf
400   :: GuestfsP -> CString -> IO (CInt)
401
402 rm_rf :: GuestfsH -> String -> IO ()
403 rm_rf h path = do
404   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm_rf p path)
405   if (r == -1)
406     then do
407       err <- last_error h
408       fail err
409     else return ()
410
411 foreign import ccall unsafe "guestfs_mkdir" c_mkdir
412   :: GuestfsP -> CString -> IO (CInt)
413
414 mkdir :: GuestfsH -> String -> IO ()
415 mkdir h path = do
416   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir p path)
417   if (r == -1)
418     then do
419       err <- last_error h
420       fail err
421     else return ()
422
423 foreign import ccall unsafe "guestfs_mkdir_p" c_mkdir_p
424   :: GuestfsP -> CString -> IO (CInt)
425
426 mkdir_p :: GuestfsH -> String -> IO ()
427 mkdir_p h path = do
428   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir_p p path)
429   if (r == -1)
430     then do
431       err <- last_error h
432       fail err
433     else return ()
434
435 foreign import ccall unsafe "guestfs_pvcreate" c_pvcreate
436   :: GuestfsP -> CString -> IO (CInt)
437
438 pvcreate :: GuestfsH -> String -> IO ()
439 pvcreate h device = do
440   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvcreate p device)
441   if (r == -1)
442     then do
443       err <- last_error h
444       fail err
445     else return ()
446
447 foreign import ccall unsafe "guestfs_vgcreate" c_vgcreate
448   :: GuestfsP -> CString -> Ptr CString -> IO (CInt)
449
450 vgcreate :: GuestfsH -> String -> [String] -> IO ()
451 vgcreate h volgroup physvols = do
452   r <- withCString volgroup $ \volgroup -> withMany withCString physvols $ \physvols -> withArray0 nullPtr physvols $ \physvols -> withForeignPtr h (\p -> c_vgcreate p volgroup physvols)
453   if (r == -1)
454     then do
455       err <- last_error h
456       fail err
457     else return ()
458
459 foreign import ccall unsafe "guestfs_mkfs" c_mkfs
460   :: GuestfsP -> CString -> CString -> IO (CInt)
461
462 mkfs :: GuestfsH -> String -> String -> IO ()
463 mkfs h fstype device = do
464   r <- withCString fstype $ \fstype -> withCString device $ \device -> withForeignPtr h (\p -> c_mkfs p fstype device)
465   if (r == -1)
466     then do
467       err <- last_error h
468       fail err
469     else return ()
470
471 foreign import ccall unsafe "guestfs_umount" c_umount
472   :: GuestfsP -> CString -> IO (CInt)
473
474 umount :: GuestfsH -> String -> IO ()
475 umount h pathordevice = do
476   r <- withCString pathordevice $ \pathordevice -> withForeignPtr h (\p -> c_umount p pathordevice)
477   if (r == -1)
478     then do
479       err <- last_error h
480       fail err
481     else return ()
482
483 foreign import ccall unsafe "guestfs_umount_all" c_umount_all
484   :: GuestfsP -> IO (CInt)
485
486 umount_all :: GuestfsH -> IO ()
487 umount_all h = do
488   r <- withForeignPtr h (\p -> c_umount_all p)
489   if (r == -1)
490     then do
491       err <- last_error h
492       fail err
493     else return ()
494
495 foreign import ccall unsafe "guestfs_lvm_remove_all" c_lvm_remove_all
496   :: GuestfsP -> IO (CInt)
497
498 lvm_remove_all :: GuestfsH -> IO ()
499 lvm_remove_all h = do
500   r <- withForeignPtr h (\p -> c_lvm_remove_all p)
501   if (r == -1)
502     then do
503       err <- last_error h
504       fail err
505     else return ()
506
507 foreign import ccall unsafe "guestfs_blockdev_setro" c_blockdev_setro
508   :: GuestfsP -> CString -> IO (CInt)
509
510 blockdev_setro :: GuestfsH -> String -> IO ()
511 blockdev_setro h device = do
512   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setro p device)
513   if (r == -1)
514     then do
515       err <- last_error h
516       fail err
517     else return ()
518
519 foreign import ccall unsafe "guestfs_blockdev_setrw" c_blockdev_setrw
520   :: GuestfsP -> CString -> IO (CInt)
521
522 blockdev_setrw :: GuestfsH -> String -> IO ()
523 blockdev_setrw h device = do
524   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setrw p device)
525   if (r == -1)
526     then do
527       err <- last_error h
528       fail err
529     else return ()
530
531 foreign import ccall unsafe "guestfs_blockdev_flushbufs" c_blockdev_flushbufs
532   :: GuestfsP -> CString -> IO (CInt)
533
534 blockdev_flushbufs :: GuestfsH -> String -> IO ()
535 blockdev_flushbufs h device = do
536   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_flushbufs p device)
537   if (r == -1)
538     then do
539       err <- last_error h
540       fail err
541     else return ()
542
543 foreign import ccall unsafe "guestfs_blockdev_rereadpt" c_blockdev_rereadpt
544   :: GuestfsP -> CString -> IO (CInt)
545
546 blockdev_rereadpt :: GuestfsH -> String -> IO ()
547 blockdev_rereadpt h device = do
548   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_rereadpt p device)
549   if (r == -1)
550     then do
551       err <- last_error h
552       fail err
553     else return ()
554
555 foreign import ccall unsafe "guestfs_upload" c_upload
556   :: GuestfsP -> CString -> CString -> IO (CInt)
557
558 upload :: GuestfsH -> String -> String -> IO ()
559 upload h filename remotefilename = do
560   r <- withCString filename $ \filename -> withCString remotefilename $ \remotefilename -> withForeignPtr h (\p -> c_upload p filename remotefilename)
561   if (r == -1)
562     then do
563       err <- last_error h
564       fail err
565     else return ()
566
567 foreign import ccall unsafe "guestfs_download" c_download
568   :: GuestfsP -> CString -> CString -> IO (CInt)
569
570 download :: GuestfsH -> String -> String -> IO ()
571 download h remotefilename filename = do
572   r <- withCString remotefilename $ \remotefilename -> withCString filename $ \filename -> withForeignPtr h (\p -> c_download p remotefilename filename)
573   if (r == -1)
574     then do
575       err <- last_error h
576       fail err
577     else return ()
578
579 foreign import ccall unsafe "guestfs_tar_in" c_tar_in
580   :: GuestfsP -> CString -> CString -> IO (CInt)
581
582 tar_in :: GuestfsH -> String -> String -> IO ()
583 tar_in h tarfile directory = do
584   r <- withCString tarfile $ \tarfile -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tar_in p tarfile directory)
585   if (r == -1)
586     then do
587       err <- last_error h
588       fail err
589     else return ()
590
591 foreign import ccall unsafe "guestfs_tar_out" c_tar_out
592   :: GuestfsP -> CString -> CString -> IO (CInt)
593
594 tar_out :: GuestfsH -> String -> String -> IO ()
595 tar_out h directory tarfile = do
596   r <- withCString directory $ \directory -> withCString tarfile $ \tarfile -> withForeignPtr h (\p -> c_tar_out p directory tarfile)
597   if (r == -1)
598     then do
599       err <- last_error h
600       fail err
601     else return ()
602
603 foreign import ccall unsafe "guestfs_tgz_in" c_tgz_in
604   :: GuestfsP -> CString -> CString -> IO (CInt)
605
606 tgz_in :: GuestfsH -> String -> String -> IO ()
607 tgz_in h tarball directory = do
608   r <- withCString tarball $ \tarball -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tgz_in p tarball directory)
609   if (r == -1)
610     then do
611       err <- last_error h
612       fail err
613     else return ()
614
615 foreign import ccall unsafe "guestfs_tgz_out" c_tgz_out
616   :: GuestfsP -> CString -> CString -> IO (CInt)
617
618 tgz_out :: GuestfsH -> String -> String -> IO ()
619 tgz_out h directory tarball = do
620   r <- withCString directory $ \directory -> withCString tarball $ \tarball -> withForeignPtr h (\p -> c_tgz_out p directory tarball)
621   if (r == -1)
622     then do
623       err <- last_error h
624       fail err
625     else return ()
626
627 foreign import ccall unsafe "guestfs_mount_ro" c_mount_ro
628   :: GuestfsP -> CString -> CString -> IO (CInt)
629
630 mount_ro :: GuestfsH -> String -> String -> IO ()
631 mount_ro h device mountpoint = do
632   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_ro p device mountpoint)
633   if (r == -1)
634     then do
635       err <- last_error h
636       fail err
637     else return ()
638
639 foreign import ccall unsafe "guestfs_mount_options" c_mount_options
640   :: GuestfsP -> CString -> CString -> CString -> IO (CInt)
641
642 mount_options :: GuestfsH -> String -> String -> String -> IO ()
643 mount_options h options device mountpoint = do
644   r <- withCString options $ \options -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_options p options device mountpoint)
645   if (r == -1)
646     then do
647       err <- last_error h
648       fail err
649     else return ()
650
651 foreign import ccall unsafe "guestfs_mount_vfs" c_mount_vfs
652   :: GuestfsP -> CString -> CString -> CString -> CString -> IO (CInt)
653
654 mount_vfs :: GuestfsH -> String -> String -> String -> String -> IO ()
655 mount_vfs h options vfstype device mountpoint = do
656   r <- withCString options $ \options -> withCString vfstype $ \vfstype -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_vfs p options vfstype device mountpoint)
657   if (r == -1)
658     then do
659       err <- last_error h
660       fail err
661     else return ()
662
663 foreign import ccall unsafe "guestfs_lvremove" c_lvremove
664   :: GuestfsP -> CString -> IO (CInt)
665
666 lvremove :: GuestfsH -> String -> IO ()
667 lvremove h device = do
668   r <- withCString device $ \device -> withForeignPtr h (\p -> c_lvremove p device)
669   if (r == -1)
670     then do
671       err <- last_error h
672       fail err
673     else return ()
674
675 foreign import ccall unsafe "guestfs_vgremove" c_vgremove
676   :: GuestfsP -> CString -> IO (CInt)
677
678 vgremove :: GuestfsH -> String -> IO ()
679 vgremove h vgname = do
680   r <- withCString vgname $ \vgname -> withForeignPtr h (\p -> c_vgremove p vgname)
681   if (r == -1)
682     then do
683       err <- last_error h
684       fail err
685     else return ()
686
687 foreign import ccall unsafe "guestfs_pvremove" c_pvremove
688   :: GuestfsP -> CString -> IO (CInt)
689
690 pvremove :: GuestfsH -> String -> IO ()
691 pvremove h device = do
692   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvremove p device)
693   if (r == -1)
694     then do
695       err <- last_error h
696       fail err
697     else return ()
698
699 foreign import ccall unsafe "guestfs_set_e2label" c_set_e2label
700   :: GuestfsP -> CString -> CString -> IO (CInt)
701
702 set_e2label :: GuestfsH -> String -> String -> IO ()
703 set_e2label h device label = do
704   r <- withCString device $ \device -> withCString label $ \label -> withForeignPtr h (\p -> c_set_e2label p device label)
705   if (r == -1)
706     then do
707       err <- last_error h
708       fail err
709     else return ()
710
711 foreign import ccall unsafe "guestfs_set_e2uuid" c_set_e2uuid
712   :: GuestfsP -> CString -> CString -> IO (CInt)
713
714 set_e2uuid :: GuestfsH -> String -> String -> IO ()
715 set_e2uuid h device uuid = do
716   r <- withCString device $ \device -> withCString uuid $ \uuid -> withForeignPtr h (\p -> c_set_e2uuid p device uuid)
717   if (r == -1)
718     then do
719       err <- last_error h
720       fail err
721     else return ()
722
723 foreign import ccall unsafe "guestfs_zero" c_zero
724   :: GuestfsP -> CString -> IO (CInt)
725
726 zero :: GuestfsH -> String -> IO ()
727 zero h device = do
728   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zero p device)
729   if (r == -1)
730     then do
731       err <- last_error h
732       fail err
733     else return ()
734
735 foreign import ccall unsafe "guestfs_grub_install" c_grub_install
736   :: GuestfsP -> CString -> CString -> IO (CInt)
737
738 grub_install :: GuestfsH -> String -> String -> IO ()
739 grub_install h root device = do
740   r <- withCString root $ \root -> withCString device $ \device -> withForeignPtr h (\p -> c_grub_install p root device)
741   if (r == -1)
742     then do
743       err <- last_error h
744       fail err
745     else return ()
746
747 foreign import ccall unsafe "guestfs_cp" c_cp
748   :: GuestfsP -> CString -> CString -> IO (CInt)
749
750 cp :: GuestfsH -> String -> String -> IO ()
751 cp h src dest = do
752   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp p src dest)
753   if (r == -1)
754     then do
755       err <- last_error h
756       fail err
757     else return ()
758
759 foreign import ccall unsafe "guestfs_cp_a" c_cp_a
760   :: GuestfsP -> CString -> CString -> IO (CInt)
761
762 cp_a :: GuestfsH -> String -> String -> IO ()
763 cp_a h src dest = do
764   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp_a p src dest)
765   if (r == -1)
766     then do
767       err <- last_error h
768       fail err
769     else return ()
770
771 foreign import ccall unsafe "guestfs_mv" c_mv
772   :: GuestfsP -> CString -> CString -> IO (CInt)
773
774 mv :: GuestfsH -> String -> String -> IO ()
775 mv h src dest = do
776   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_mv p src dest)
777   if (r == -1)
778     then do
779       err <- last_error h
780       fail err
781     else return ()
782
783 foreign import ccall unsafe "guestfs_ping_daemon" c_ping_daemon
784   :: GuestfsP -> IO (CInt)
785
786 ping_daemon :: GuestfsH -> IO ()
787 ping_daemon h = do
788   r <- withForeignPtr h (\p -> c_ping_daemon p)
789   if (r == -1)
790     then do
791       err <- last_error h
792       fail err
793     else return ()
794
795 foreign import ccall unsafe "guestfs_zerofree" c_zerofree
796   :: GuestfsP -> CString -> IO (CInt)
797
798 zerofree :: GuestfsH -> String -> IO ()
799 zerofree h device = do
800   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zerofree p device)
801   if (r == -1)
802     then do
803       err <- last_error h
804       fail err
805     else return ()
806
807 foreign import ccall unsafe "guestfs_pvresize" c_pvresize
808   :: GuestfsP -> CString -> IO (CInt)
809
810 pvresize :: GuestfsH -> String -> IO ()
811 pvresize h device = do
812   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvresize p device)
813   if (r == -1)
814     then do
815       err <- last_error h
816       fail err
817     else return ()
818
819 foreign import ccall unsafe "guestfs_resize2fs" c_resize2fs
820   :: GuestfsP -> CString -> IO (CInt)
821
822 resize2fs :: GuestfsH -> String -> IO ()
823 resize2fs h device = do
824   r <- withCString device $ \device -> withForeignPtr h (\p -> c_resize2fs p device)
825   if (r == -1)
826     then do
827       err <- last_error h
828       fail err
829     else return ()
830
831 foreign import ccall unsafe "guestfs_e2fsck_f" c_e2fsck_f
832   :: GuestfsP -> CString -> IO (CInt)
833
834 e2fsck_f :: GuestfsH -> String -> IO ()
835 e2fsck_f h device = do
836   r <- withCString device $ \device -> withForeignPtr h (\p -> c_e2fsck_f p device)
837   if (r == -1)
838     then do
839       err <- last_error h
840       fail err
841     else return ()
842