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