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