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