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