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