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