8101b526981091942707980db5566cc7acd47fbc
[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   test0,
28   test0rint,
29   test0rinterr,
30   test0rint64,
31   test0rint64err,
32   launch,
33   wait_ready,
34   kill_subprocess,
35   add_drive,
36   add_cdrom,
37   add_drive_ro,
38   config,
39   set_qemu,
40   set_path,
41   set_append,
42   set_autosync,
43   set_verbose,
44   get_state,
45   set_busy,
46   set_ready,
47   end_busy,
48   mount,
49   sync,
50   touch,
51   aug_init,
52   aug_close,
53   aug_defvar,
54   aug_set,
55   aug_insert,
56   aug_rm,
57   aug_mv,
58   aug_save,
59   aug_load,
60   rm,
61   rmdir,
62   rm_rf,
63   mkdir,
64   mkdir_p,
65   chmod,
66   chown,
67   pvcreate,
68   vgcreate,
69   lvcreate,
70   mkfs,
71   sfdisk,
72   write_file,
73   umount,
74   umount_all,
75   lvm_remove_all,
76   blockdev_setro,
77   blockdev_setrw,
78   blockdev_getss,
79   blockdev_getbsz,
80   blockdev_setbsz,
81   blockdev_getsz,
82   blockdev_getsize64,
83   blockdev_flushbufs,
84   blockdev_rereadpt,
85   upload,
86   download,
87   tar_in,
88   tar_out,
89   tgz_in,
90   tgz_out,
91   mount_ro,
92   mount_options,
93   mount_vfs,
94   lvremove,
95   vgremove,
96   pvremove,
97   set_e2label,
98   set_e2uuid,
99   fsck,
100   zero,
101   grub_install,
102   cp,
103   cp_a,
104   mv,
105   drop_caches,
106   ping_daemon,
107   zerofree,
108   pvresize,
109   sfdisk_N,
110   vg_activate_all,
111   vg_activate,
112   lvresize,
113   resize2fs,
114   e2fsck_f,
115   sleep,
116   ntfs_3g_probe,
117   scrub_device,
118   scrub_file,
119   scrub_freespace,
120   wc_l,
121   wc_w,
122   wc_c
123   ) where
124 import Foreign
125 import Foreign.C
126 import Foreign.C.Types
127 import IO
128 import Control.Exception
129 import Data.Typeable
130
131 data GuestfsS = GuestfsS            -- represents the opaque C struct
132 type GuestfsP = Ptr GuestfsS        -- guestfs_h *
133 type GuestfsH = ForeignPtr GuestfsS -- guestfs_h * with attached finalizer
134
135 -- XXX define properly later XXX
136 data PV = PV
137 data VG = VG
138 data LV = LV
139 data IntBool = IntBool
140 data Stat = Stat
141 data StatVFS = StatVFS
142 data Hashtable = Hashtable
143
144 foreign import ccall unsafe "guestfs_create" c_create
145   :: IO GuestfsP
146 foreign import ccall unsafe "&guestfs_close" c_close
147   :: FunPtr (GuestfsP -> IO ())
148 foreign import ccall unsafe "guestfs_set_error_handler" c_set_error_handler
149   :: GuestfsP -> Ptr CInt -> Ptr CInt -> IO ()
150
151 create :: IO GuestfsH
152 create = do
153   p <- c_create
154   c_set_error_handler p nullPtr nullPtr
155   h <- newForeignPtr c_close p
156   return h
157
158 foreign import ccall unsafe "guestfs_last_error" c_last_error
159   :: GuestfsP -> IO CString
160
161 -- last_error :: GuestfsH -> IO (Maybe String)
162 -- last_error h = do
163 --   str <- withForeignPtr h (\p -> c_last_error p)
164 --   maybePeek peekCString str
165
166 last_error :: GuestfsH -> IO (String)
167 last_error h = do
168   str <- withForeignPtr h (\p -> c_last_error p)
169   if (str == nullPtr)
170     then return "no error"
171     else peekCString str
172
173 foreign import ccall unsafe "guestfs_test0" c_test0
174   :: GuestfsP -> CString -> CString -> Ptr CString -> CInt -> CInt -> CString -> CString -> IO (CInt)
175
176 test0 :: GuestfsH -> String -> Maybe String -> [String] -> Bool -> Int -> String -> String -> IO ()
177 test0 h str optstr strlist b integer filein fileout = do
178   r <- withCString str $ \str -> maybeWith withCString optstr $ \optstr -> withMany withCString strlist $ \strlist -> withArray0 nullPtr strlist $ \strlist -> withCString filein $ \filein -> withCString fileout $ \fileout -> withForeignPtr h (\p -> c_test0 p str optstr strlist (fromBool b) (fromIntegral integer) filein fileout)
179   if (r == -1)
180     then do
181       err <- last_error h
182       fail err
183     else return ()
184
185 foreign import ccall unsafe "guestfs_test0rint" c_test0rint
186   :: GuestfsP -> CString -> IO (CInt)
187
188 test0rint :: GuestfsH -> String -> IO (Int)
189 test0rint h val = do
190   r <- withCString val $ \val -> withForeignPtr h (\p -> c_test0rint p val)
191   if (r == -1)
192     then do
193       err <- last_error h
194       fail err
195     else return (fromIntegral r)
196
197 foreign import ccall unsafe "guestfs_test0rinterr" c_test0rinterr
198   :: GuestfsP -> IO (CInt)
199
200 test0rinterr :: GuestfsH -> IO (Int)
201 test0rinterr h = do
202   r <- withForeignPtr h (\p -> c_test0rinterr p)
203   if (r == -1)
204     then do
205       err <- last_error h
206       fail err
207     else return (fromIntegral r)
208
209 foreign import ccall unsafe "guestfs_test0rint64" c_test0rint64
210   :: GuestfsP -> CString -> IO (Int64)
211
212 test0rint64 :: GuestfsH -> String -> IO (Integer)
213 test0rint64 h val = do
214   r <- withCString val $ \val -> withForeignPtr h (\p -> c_test0rint64 p val)
215   if (r == -1)
216     then do
217       err <- last_error h
218       fail err
219     else return (fromIntegral r)
220
221 foreign import ccall unsafe "guestfs_test0rint64err" c_test0rint64err
222   :: GuestfsP -> IO (Int64)
223
224 test0rint64err :: GuestfsH -> IO (Integer)
225 test0rint64err h = do
226   r <- withForeignPtr h (\p -> c_test0rint64err p)
227   if (r == -1)
228     then do
229       err <- last_error h
230       fail err
231     else return (fromIntegral r)
232
233 foreign import ccall unsafe "guestfs_launch" c_launch
234   :: GuestfsP -> IO (CInt)
235
236 launch :: GuestfsH -> IO ()
237 launch h = do
238   r <- withForeignPtr h (\p -> c_launch p)
239   if (r == -1)
240     then do
241       err <- last_error h
242       fail err
243     else return ()
244
245 foreign import ccall unsafe "guestfs_wait_ready" c_wait_ready
246   :: GuestfsP -> IO (CInt)
247
248 wait_ready :: GuestfsH -> IO ()
249 wait_ready h = do
250   r <- withForeignPtr h (\p -> c_wait_ready p)
251   if (r == -1)
252     then do
253       err <- last_error h
254       fail err
255     else return ()
256
257 foreign import ccall unsafe "guestfs_kill_subprocess" c_kill_subprocess
258   :: GuestfsP -> IO (CInt)
259
260 kill_subprocess :: GuestfsH -> IO ()
261 kill_subprocess h = do
262   r <- withForeignPtr h (\p -> c_kill_subprocess p)
263   if (r == -1)
264     then do
265       err <- last_error h
266       fail err
267     else return ()
268
269 foreign import ccall unsafe "guestfs_add_drive" c_add_drive
270   :: GuestfsP -> CString -> IO (CInt)
271
272 add_drive :: GuestfsH -> String -> IO ()
273 add_drive h filename = do
274   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_drive p filename)
275   if (r == -1)
276     then do
277       err <- last_error h
278       fail err
279     else return ()
280
281 foreign import ccall unsafe "guestfs_add_cdrom" c_add_cdrom
282   :: GuestfsP -> CString -> IO (CInt)
283
284 add_cdrom :: GuestfsH -> String -> IO ()
285 add_cdrom h filename = do
286   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_cdrom p filename)
287   if (r == -1)
288     then do
289       err <- last_error h
290       fail err
291     else return ()
292
293 foreign import ccall unsafe "guestfs_add_drive_ro" c_add_drive_ro
294   :: GuestfsP -> CString -> IO (CInt)
295
296 add_drive_ro :: GuestfsH -> String -> IO ()
297 add_drive_ro h filename = do
298   r <- withCString filename $ \filename -> withForeignPtr h (\p -> c_add_drive_ro p filename)
299   if (r == -1)
300     then do
301       err <- last_error h
302       fail err
303     else return ()
304
305 foreign import ccall unsafe "guestfs_config" c_config
306   :: GuestfsP -> CString -> CString -> IO (CInt)
307
308 config :: GuestfsH -> String -> Maybe String -> IO ()
309 config h qemuparam qemuvalue = do
310   r <- withCString qemuparam $ \qemuparam -> maybeWith withCString qemuvalue $ \qemuvalue -> withForeignPtr h (\p -> c_config p qemuparam qemuvalue)
311   if (r == -1)
312     then do
313       err <- last_error h
314       fail err
315     else return ()
316
317 foreign import ccall unsafe "guestfs_set_qemu" c_set_qemu
318   :: GuestfsP -> CString -> IO (CInt)
319
320 set_qemu :: GuestfsH -> String -> IO ()
321 set_qemu h qemu = do
322   r <- withCString qemu $ \qemu -> withForeignPtr h (\p -> c_set_qemu p qemu)
323   if (r == -1)
324     then do
325       err <- last_error h
326       fail err
327     else return ()
328
329 foreign import ccall unsafe "guestfs_set_path" c_set_path
330   :: GuestfsP -> CString -> IO (CInt)
331
332 set_path :: GuestfsH -> String -> IO ()
333 set_path h path = do
334   r <- withCString path $ \path -> withForeignPtr h (\p -> c_set_path p path)
335   if (r == -1)
336     then do
337       err <- last_error h
338       fail err
339     else return ()
340
341 foreign import ccall unsafe "guestfs_set_append" c_set_append
342   :: GuestfsP -> CString -> IO (CInt)
343
344 set_append :: GuestfsH -> String -> IO ()
345 set_append h append = do
346   r <- withCString append $ \append -> withForeignPtr h (\p -> c_set_append p append)
347   if (r == -1)
348     then do
349       err <- last_error h
350       fail err
351     else return ()
352
353 foreign import ccall unsafe "guestfs_set_autosync" c_set_autosync
354   :: GuestfsP -> CInt -> IO (CInt)
355
356 set_autosync :: GuestfsH -> Bool -> IO ()
357 set_autosync h autosync = do
358   r <- withForeignPtr h (\p -> c_set_autosync p (fromBool autosync))
359   if (r == -1)
360     then do
361       err <- last_error h
362       fail err
363     else return ()
364
365 foreign import ccall unsafe "guestfs_set_verbose" c_set_verbose
366   :: GuestfsP -> CInt -> IO (CInt)
367
368 set_verbose :: GuestfsH -> Bool -> IO ()
369 set_verbose h verbose = do
370   r <- withForeignPtr h (\p -> c_set_verbose p (fromBool verbose))
371   if (r == -1)
372     then do
373       err <- last_error h
374       fail err
375     else return ()
376
377 foreign import ccall unsafe "guestfs_get_state" c_get_state
378   :: GuestfsP -> IO (CInt)
379
380 get_state :: GuestfsH -> IO (Int)
381 get_state h = do
382   r <- withForeignPtr h (\p -> c_get_state p)
383   if (r == -1)
384     then do
385       err <- last_error h
386       fail err
387     else return (fromIntegral r)
388
389 foreign import ccall unsafe "guestfs_set_busy" c_set_busy
390   :: GuestfsP -> IO (CInt)
391
392 set_busy :: GuestfsH -> IO ()
393 set_busy h = do
394   r <- withForeignPtr h (\p -> c_set_busy p)
395   if (r == -1)
396     then do
397       err <- last_error h
398       fail err
399     else return ()
400
401 foreign import ccall unsafe "guestfs_set_ready" c_set_ready
402   :: GuestfsP -> IO (CInt)
403
404 set_ready :: GuestfsH -> IO ()
405 set_ready h = do
406   r <- withForeignPtr h (\p -> c_set_ready p)
407   if (r == -1)
408     then do
409       err <- last_error h
410       fail err
411     else return ()
412
413 foreign import ccall unsafe "guestfs_end_busy" c_end_busy
414   :: GuestfsP -> IO (CInt)
415
416 end_busy :: GuestfsH -> IO ()
417 end_busy h = do
418   r <- withForeignPtr h (\p -> c_end_busy p)
419   if (r == -1)
420     then do
421       err <- last_error h
422       fail err
423     else return ()
424
425 foreign import ccall unsafe "guestfs_mount" c_mount
426   :: GuestfsP -> CString -> CString -> IO (CInt)
427
428 mount :: GuestfsH -> String -> String -> IO ()
429 mount h device mountpoint = do
430   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount p device mountpoint)
431   if (r == -1)
432     then do
433       err <- last_error h
434       fail err
435     else return ()
436
437 foreign import ccall unsafe "guestfs_sync" c_sync
438   :: GuestfsP -> IO (CInt)
439
440 sync :: GuestfsH -> IO ()
441 sync h = do
442   r <- withForeignPtr h (\p -> c_sync p)
443   if (r == -1)
444     then do
445       err <- last_error h
446       fail err
447     else return ()
448
449 foreign import ccall unsafe "guestfs_touch" c_touch
450   :: GuestfsP -> CString -> IO (CInt)
451
452 touch :: GuestfsH -> String -> IO ()
453 touch h path = do
454   r <- withCString path $ \path -> withForeignPtr h (\p -> c_touch p path)
455   if (r == -1)
456     then do
457       err <- last_error h
458       fail err
459     else return ()
460
461 foreign import ccall unsafe "guestfs_aug_init" c_aug_init
462   :: GuestfsP -> CString -> CInt -> IO (CInt)
463
464 aug_init :: GuestfsH -> String -> Int -> IO ()
465 aug_init h root flags = do
466   r <- withCString root $ \root -> withForeignPtr h (\p -> c_aug_init p root (fromIntegral flags))
467   if (r == -1)
468     then do
469       err <- last_error h
470       fail err
471     else return ()
472
473 foreign import ccall unsafe "guestfs_aug_close" c_aug_close
474   :: GuestfsP -> IO (CInt)
475
476 aug_close :: GuestfsH -> IO ()
477 aug_close h = do
478   r <- withForeignPtr h (\p -> c_aug_close p)
479   if (r == -1)
480     then do
481       err <- last_error h
482       fail err
483     else return ()
484
485 foreign import ccall unsafe "guestfs_aug_defvar" c_aug_defvar
486   :: GuestfsP -> CString -> CString -> IO (CInt)
487
488 aug_defvar :: GuestfsH -> String -> Maybe String -> IO (Int)
489 aug_defvar h name expr = do
490   r <- withCString name $ \name -> maybeWith withCString expr $ \expr -> withForeignPtr h (\p -> c_aug_defvar p name expr)
491   if (r == -1)
492     then do
493       err <- last_error h
494       fail err
495     else return (fromIntegral r)
496
497 foreign import ccall unsafe "guestfs_aug_set" c_aug_set
498   :: GuestfsP -> CString -> CString -> IO (CInt)
499
500 aug_set :: GuestfsH -> String -> String -> IO ()
501 aug_set h path val = do
502   r <- withCString path $ \path -> withCString val $ \val -> withForeignPtr h (\p -> c_aug_set p path val)
503   if (r == -1)
504     then do
505       err <- last_error h
506       fail err
507     else return ()
508
509 foreign import ccall unsafe "guestfs_aug_insert" c_aug_insert
510   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
511
512 aug_insert :: GuestfsH -> String -> String -> Bool -> IO ()
513 aug_insert h path label before = do
514   r <- withCString path $ \path -> withCString label $ \label -> withForeignPtr h (\p -> c_aug_insert p path label (fromBool before))
515   if (r == -1)
516     then do
517       err <- last_error h
518       fail err
519     else return ()
520
521 foreign import ccall unsafe "guestfs_aug_rm" c_aug_rm
522   :: GuestfsP -> CString -> IO (CInt)
523
524 aug_rm :: GuestfsH -> String -> IO (Int)
525 aug_rm h path = do
526   r <- withCString path $ \path -> withForeignPtr h (\p -> c_aug_rm p path)
527   if (r == -1)
528     then do
529       err <- last_error h
530       fail err
531     else return (fromIntegral r)
532
533 foreign import ccall unsafe "guestfs_aug_mv" c_aug_mv
534   :: GuestfsP -> CString -> CString -> IO (CInt)
535
536 aug_mv :: GuestfsH -> String -> String -> IO ()
537 aug_mv h src dest = do
538   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_aug_mv p src dest)
539   if (r == -1)
540     then do
541       err <- last_error h
542       fail err
543     else return ()
544
545 foreign import ccall unsafe "guestfs_aug_save" c_aug_save
546   :: GuestfsP -> IO (CInt)
547
548 aug_save :: GuestfsH -> IO ()
549 aug_save h = do
550   r <- withForeignPtr h (\p -> c_aug_save p)
551   if (r == -1)
552     then do
553       err <- last_error h
554       fail err
555     else return ()
556
557 foreign import ccall unsafe "guestfs_aug_load" c_aug_load
558   :: GuestfsP -> IO (CInt)
559
560 aug_load :: GuestfsH -> IO ()
561 aug_load h = do
562   r <- withForeignPtr h (\p -> c_aug_load p)
563   if (r == -1)
564     then do
565       err <- last_error h
566       fail err
567     else return ()
568
569 foreign import ccall unsafe "guestfs_rm" c_rm
570   :: GuestfsP -> CString -> IO (CInt)
571
572 rm :: GuestfsH -> String -> IO ()
573 rm h path = do
574   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm p path)
575   if (r == -1)
576     then do
577       err <- last_error h
578       fail err
579     else return ()
580
581 foreign import ccall unsafe "guestfs_rmdir" c_rmdir
582   :: GuestfsP -> CString -> IO (CInt)
583
584 rmdir :: GuestfsH -> String -> IO ()
585 rmdir h path = do
586   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rmdir p path)
587   if (r == -1)
588     then do
589       err <- last_error h
590       fail err
591     else return ()
592
593 foreign import ccall unsafe "guestfs_rm_rf" c_rm_rf
594   :: GuestfsP -> CString -> IO (CInt)
595
596 rm_rf :: GuestfsH -> String -> IO ()
597 rm_rf h path = do
598   r <- withCString path $ \path -> withForeignPtr h (\p -> c_rm_rf p path)
599   if (r == -1)
600     then do
601       err <- last_error h
602       fail err
603     else return ()
604
605 foreign import ccall unsafe "guestfs_mkdir" c_mkdir
606   :: GuestfsP -> CString -> IO (CInt)
607
608 mkdir :: GuestfsH -> String -> IO ()
609 mkdir h path = do
610   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir p path)
611   if (r == -1)
612     then do
613       err <- last_error h
614       fail err
615     else return ()
616
617 foreign import ccall unsafe "guestfs_mkdir_p" c_mkdir_p
618   :: GuestfsP -> CString -> IO (CInt)
619
620 mkdir_p :: GuestfsH -> String -> IO ()
621 mkdir_p h path = do
622   r <- withCString path $ \path -> withForeignPtr h (\p -> c_mkdir_p p path)
623   if (r == -1)
624     then do
625       err <- last_error h
626       fail err
627     else return ()
628
629 foreign import ccall unsafe "guestfs_chmod" c_chmod
630   :: GuestfsP -> CInt -> CString -> IO (CInt)
631
632 chmod :: GuestfsH -> Int -> String -> IO ()
633 chmod h mode path = do
634   r <- withCString path $ \path -> withForeignPtr h (\p -> c_chmod p (fromIntegral mode) path)
635   if (r == -1)
636     then do
637       err <- last_error h
638       fail err
639     else return ()
640
641 foreign import ccall unsafe "guestfs_chown" c_chown
642   :: GuestfsP -> CInt -> CInt -> CString -> IO (CInt)
643
644 chown :: GuestfsH -> Int -> Int -> String -> IO ()
645 chown h owner group path = do
646   r <- withCString path $ \path -> withForeignPtr h (\p -> c_chown p (fromIntegral owner) (fromIntegral group) path)
647   if (r == -1)
648     then do
649       err <- last_error h
650       fail err
651     else return ()
652
653 foreign import ccall unsafe "guestfs_pvcreate" c_pvcreate
654   :: GuestfsP -> CString -> IO (CInt)
655
656 pvcreate :: GuestfsH -> String -> IO ()
657 pvcreate h device = do
658   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvcreate p device)
659   if (r == -1)
660     then do
661       err <- last_error h
662       fail err
663     else return ()
664
665 foreign import ccall unsafe "guestfs_vgcreate" c_vgcreate
666   :: GuestfsP -> CString -> Ptr CString -> IO (CInt)
667
668 vgcreate :: GuestfsH -> String -> [String] -> IO ()
669 vgcreate h volgroup physvols = do
670   r <- withCString volgroup $ \volgroup -> withMany withCString physvols $ \physvols -> withArray0 nullPtr physvols $ \physvols -> withForeignPtr h (\p -> c_vgcreate p volgroup physvols)
671   if (r == -1)
672     then do
673       err <- last_error h
674       fail err
675     else return ()
676
677 foreign import ccall unsafe "guestfs_lvcreate" c_lvcreate
678   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
679
680 lvcreate :: GuestfsH -> String -> String -> Int -> IO ()
681 lvcreate h logvol volgroup mbytes = do
682   r <- withCString logvol $ \logvol -> withCString volgroup $ \volgroup -> withForeignPtr h (\p -> c_lvcreate p logvol volgroup (fromIntegral mbytes))
683   if (r == -1)
684     then do
685       err <- last_error h
686       fail err
687     else return ()
688
689 foreign import ccall unsafe "guestfs_mkfs" c_mkfs
690   :: GuestfsP -> CString -> CString -> IO (CInt)
691
692 mkfs :: GuestfsH -> String -> String -> IO ()
693 mkfs h fstype device = do
694   r <- withCString fstype $ \fstype -> withCString device $ \device -> withForeignPtr h (\p -> c_mkfs p fstype device)
695   if (r == -1)
696     then do
697       err <- last_error h
698       fail err
699     else return ()
700
701 foreign import ccall unsafe "guestfs_sfdisk" c_sfdisk
702   :: GuestfsP -> CString -> CInt -> CInt -> CInt -> Ptr CString -> IO (CInt)
703
704 sfdisk :: GuestfsH -> String -> Int -> Int -> Int -> [String] -> IO ()
705 sfdisk h device cyls heads sectors lines = do
706   r <- withCString device $ \device -> withMany withCString lines $ \lines -> withArray0 nullPtr lines $ \lines -> withForeignPtr h (\p -> c_sfdisk p device (fromIntegral cyls) (fromIntegral heads) (fromIntegral sectors) lines)
707   if (r == -1)
708     then do
709       err <- last_error h
710       fail err
711     else return ()
712
713 foreign import ccall unsafe "guestfs_write_file" c_write_file
714   :: GuestfsP -> CString -> CString -> CInt -> IO (CInt)
715
716 write_file :: GuestfsH -> String -> String -> Int -> IO ()
717 write_file h path content size = do
718   r <- withCString path $ \path -> withCString content $ \content -> withForeignPtr h (\p -> c_write_file p path content (fromIntegral size))
719   if (r == -1)
720     then do
721       err <- last_error h
722       fail err
723     else return ()
724
725 foreign import ccall unsafe "guestfs_umount" c_umount
726   :: GuestfsP -> CString -> IO (CInt)
727
728 umount :: GuestfsH -> String -> IO ()
729 umount h pathordevice = do
730   r <- withCString pathordevice $ \pathordevice -> withForeignPtr h (\p -> c_umount p pathordevice)
731   if (r == -1)
732     then do
733       err <- last_error h
734       fail err
735     else return ()
736
737 foreign import ccall unsafe "guestfs_umount_all" c_umount_all
738   :: GuestfsP -> IO (CInt)
739
740 umount_all :: GuestfsH -> IO ()
741 umount_all h = do
742   r <- withForeignPtr h (\p -> c_umount_all p)
743   if (r == -1)
744     then do
745       err <- last_error h
746       fail err
747     else return ()
748
749 foreign import ccall unsafe "guestfs_lvm_remove_all" c_lvm_remove_all
750   :: GuestfsP -> IO (CInt)
751
752 lvm_remove_all :: GuestfsH -> IO ()
753 lvm_remove_all h = do
754   r <- withForeignPtr h (\p -> c_lvm_remove_all p)
755   if (r == -1)
756     then do
757       err <- last_error h
758       fail err
759     else return ()
760
761 foreign import ccall unsafe "guestfs_blockdev_setro" c_blockdev_setro
762   :: GuestfsP -> CString -> IO (CInt)
763
764 blockdev_setro :: GuestfsH -> String -> IO ()
765 blockdev_setro h device = do
766   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setro p device)
767   if (r == -1)
768     then do
769       err <- last_error h
770       fail err
771     else return ()
772
773 foreign import ccall unsafe "guestfs_blockdev_setrw" c_blockdev_setrw
774   :: GuestfsP -> CString -> IO (CInt)
775
776 blockdev_setrw :: GuestfsH -> String -> IO ()
777 blockdev_setrw h device = do
778   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setrw p device)
779   if (r == -1)
780     then do
781       err <- last_error h
782       fail err
783     else return ()
784
785 foreign import ccall unsafe "guestfs_blockdev_getss" c_blockdev_getss
786   :: GuestfsP -> CString -> IO (CInt)
787
788 blockdev_getss :: GuestfsH -> String -> IO (Int)
789 blockdev_getss h device = do
790   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getss p device)
791   if (r == -1)
792     then do
793       err <- last_error h
794       fail err
795     else return (fromIntegral r)
796
797 foreign import ccall unsafe "guestfs_blockdev_getbsz" c_blockdev_getbsz
798   :: GuestfsP -> CString -> IO (CInt)
799
800 blockdev_getbsz :: GuestfsH -> String -> IO (Int)
801 blockdev_getbsz h device = do
802   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getbsz p device)
803   if (r == -1)
804     then do
805       err <- last_error h
806       fail err
807     else return (fromIntegral r)
808
809 foreign import ccall unsafe "guestfs_blockdev_setbsz" c_blockdev_setbsz
810   :: GuestfsP -> CString -> CInt -> IO (CInt)
811
812 blockdev_setbsz :: GuestfsH -> String -> Int -> IO ()
813 blockdev_setbsz h device blocksize = do
814   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_setbsz p device (fromIntegral blocksize))
815   if (r == -1)
816     then do
817       err <- last_error h
818       fail err
819     else return ()
820
821 foreign import ccall unsafe "guestfs_blockdev_getsz" c_blockdev_getsz
822   :: GuestfsP -> CString -> IO (Int64)
823
824 blockdev_getsz :: GuestfsH -> String -> IO (Integer)
825 blockdev_getsz h device = do
826   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getsz p device)
827   if (r == -1)
828     then do
829       err <- last_error h
830       fail err
831     else return (fromIntegral r)
832
833 foreign import ccall unsafe "guestfs_blockdev_getsize64" c_blockdev_getsize64
834   :: GuestfsP -> CString -> IO (Int64)
835
836 blockdev_getsize64 :: GuestfsH -> String -> IO (Integer)
837 blockdev_getsize64 h device = do
838   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_getsize64 p device)
839   if (r == -1)
840     then do
841       err <- last_error h
842       fail err
843     else return (fromIntegral r)
844
845 foreign import ccall unsafe "guestfs_blockdev_flushbufs" c_blockdev_flushbufs
846   :: GuestfsP -> CString -> IO (CInt)
847
848 blockdev_flushbufs :: GuestfsH -> String -> IO ()
849 blockdev_flushbufs h device = do
850   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_flushbufs p device)
851   if (r == -1)
852     then do
853       err <- last_error h
854       fail err
855     else return ()
856
857 foreign import ccall unsafe "guestfs_blockdev_rereadpt" c_blockdev_rereadpt
858   :: GuestfsP -> CString -> IO (CInt)
859
860 blockdev_rereadpt :: GuestfsH -> String -> IO ()
861 blockdev_rereadpt h device = do
862   r <- withCString device $ \device -> withForeignPtr h (\p -> c_blockdev_rereadpt p device)
863   if (r == -1)
864     then do
865       err <- last_error h
866       fail err
867     else return ()
868
869 foreign import ccall unsafe "guestfs_upload" c_upload
870   :: GuestfsP -> CString -> CString -> IO (CInt)
871
872 upload :: GuestfsH -> String -> String -> IO ()
873 upload h filename remotefilename = do
874   r <- withCString filename $ \filename -> withCString remotefilename $ \remotefilename -> withForeignPtr h (\p -> c_upload p filename remotefilename)
875   if (r == -1)
876     then do
877       err <- last_error h
878       fail err
879     else return ()
880
881 foreign import ccall unsafe "guestfs_download" c_download
882   :: GuestfsP -> CString -> CString -> IO (CInt)
883
884 download :: GuestfsH -> String -> String -> IO ()
885 download h remotefilename filename = do
886   r <- withCString remotefilename $ \remotefilename -> withCString filename $ \filename -> withForeignPtr h (\p -> c_download p remotefilename filename)
887   if (r == -1)
888     then do
889       err <- last_error h
890       fail err
891     else return ()
892
893 foreign import ccall unsafe "guestfs_tar_in" c_tar_in
894   :: GuestfsP -> CString -> CString -> IO (CInt)
895
896 tar_in :: GuestfsH -> String -> String -> IO ()
897 tar_in h tarfile directory = do
898   r <- withCString tarfile $ \tarfile -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tar_in p tarfile directory)
899   if (r == -1)
900     then do
901       err <- last_error h
902       fail err
903     else return ()
904
905 foreign import ccall unsafe "guestfs_tar_out" c_tar_out
906   :: GuestfsP -> CString -> CString -> IO (CInt)
907
908 tar_out :: GuestfsH -> String -> String -> IO ()
909 tar_out h directory tarfile = do
910   r <- withCString directory $ \directory -> withCString tarfile $ \tarfile -> withForeignPtr h (\p -> c_tar_out p directory tarfile)
911   if (r == -1)
912     then do
913       err <- last_error h
914       fail err
915     else return ()
916
917 foreign import ccall unsafe "guestfs_tgz_in" c_tgz_in
918   :: GuestfsP -> CString -> CString -> IO (CInt)
919
920 tgz_in :: GuestfsH -> String -> String -> IO ()
921 tgz_in h tarball directory = do
922   r <- withCString tarball $ \tarball -> withCString directory $ \directory -> withForeignPtr h (\p -> c_tgz_in p tarball directory)
923   if (r == -1)
924     then do
925       err <- last_error h
926       fail err
927     else return ()
928
929 foreign import ccall unsafe "guestfs_tgz_out" c_tgz_out
930   :: GuestfsP -> CString -> CString -> IO (CInt)
931
932 tgz_out :: GuestfsH -> String -> String -> IO ()
933 tgz_out h directory tarball = do
934   r <- withCString directory $ \directory -> withCString tarball $ \tarball -> withForeignPtr h (\p -> c_tgz_out p directory tarball)
935   if (r == -1)
936     then do
937       err <- last_error h
938       fail err
939     else return ()
940
941 foreign import ccall unsafe "guestfs_mount_ro" c_mount_ro
942   :: GuestfsP -> CString -> CString -> IO (CInt)
943
944 mount_ro :: GuestfsH -> String -> String -> IO ()
945 mount_ro h device mountpoint = do
946   r <- withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_ro p device mountpoint)
947   if (r == -1)
948     then do
949       err <- last_error h
950       fail err
951     else return ()
952
953 foreign import ccall unsafe "guestfs_mount_options" c_mount_options
954   :: GuestfsP -> CString -> CString -> CString -> IO (CInt)
955
956 mount_options :: GuestfsH -> String -> String -> String -> IO ()
957 mount_options h options device mountpoint = do
958   r <- withCString options $ \options -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_options p options device mountpoint)
959   if (r == -1)
960     then do
961       err <- last_error h
962       fail err
963     else return ()
964
965 foreign import ccall unsafe "guestfs_mount_vfs" c_mount_vfs
966   :: GuestfsP -> CString -> CString -> CString -> CString -> IO (CInt)
967
968 mount_vfs :: GuestfsH -> String -> String -> String -> String -> IO ()
969 mount_vfs h options vfstype device mountpoint = do
970   r <- withCString options $ \options -> withCString vfstype $ \vfstype -> withCString device $ \device -> withCString mountpoint $ \mountpoint -> withForeignPtr h (\p -> c_mount_vfs p options vfstype device mountpoint)
971   if (r == -1)
972     then do
973       err <- last_error h
974       fail err
975     else return ()
976
977 foreign import ccall unsafe "guestfs_lvremove" c_lvremove
978   :: GuestfsP -> CString -> IO (CInt)
979
980 lvremove :: GuestfsH -> String -> IO ()
981 lvremove h device = do
982   r <- withCString device $ \device -> withForeignPtr h (\p -> c_lvremove p device)
983   if (r == -1)
984     then do
985       err <- last_error h
986       fail err
987     else return ()
988
989 foreign import ccall unsafe "guestfs_vgremove" c_vgremove
990   :: GuestfsP -> CString -> IO (CInt)
991
992 vgremove :: GuestfsH -> String -> IO ()
993 vgremove h vgname = do
994   r <- withCString vgname $ \vgname -> withForeignPtr h (\p -> c_vgremove p vgname)
995   if (r == -1)
996     then do
997       err <- last_error h
998       fail err
999     else return ()
1000
1001 foreign import ccall unsafe "guestfs_pvremove" c_pvremove
1002   :: GuestfsP -> CString -> IO (CInt)
1003
1004 pvremove :: GuestfsH -> String -> IO ()
1005 pvremove h device = do
1006   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvremove p device)
1007   if (r == -1)
1008     then do
1009       err <- last_error h
1010       fail err
1011     else return ()
1012
1013 foreign import ccall unsafe "guestfs_set_e2label" c_set_e2label
1014   :: GuestfsP -> CString -> CString -> IO (CInt)
1015
1016 set_e2label :: GuestfsH -> String -> String -> IO ()
1017 set_e2label h device label = do
1018   r <- withCString device $ \device -> withCString label $ \label -> withForeignPtr h (\p -> c_set_e2label p device label)
1019   if (r == -1)
1020     then do
1021       err <- last_error h
1022       fail err
1023     else return ()
1024
1025 foreign import ccall unsafe "guestfs_set_e2uuid" c_set_e2uuid
1026   :: GuestfsP -> CString -> CString -> IO (CInt)
1027
1028 set_e2uuid :: GuestfsH -> String -> String -> IO ()
1029 set_e2uuid h device uuid = do
1030   r <- withCString device $ \device -> withCString uuid $ \uuid -> withForeignPtr h (\p -> c_set_e2uuid p device uuid)
1031   if (r == -1)
1032     then do
1033       err <- last_error h
1034       fail err
1035     else return ()
1036
1037 foreign import ccall unsafe "guestfs_fsck" c_fsck
1038   :: GuestfsP -> CString -> CString -> IO (CInt)
1039
1040 fsck :: GuestfsH -> String -> String -> IO (Int)
1041 fsck h fstype device = do
1042   r <- withCString fstype $ \fstype -> withCString device $ \device -> withForeignPtr h (\p -> c_fsck p fstype device)
1043   if (r == -1)
1044     then do
1045       err <- last_error h
1046       fail err
1047     else return (fromIntegral r)
1048
1049 foreign import ccall unsafe "guestfs_zero" c_zero
1050   :: GuestfsP -> CString -> IO (CInt)
1051
1052 zero :: GuestfsH -> String -> IO ()
1053 zero h device = do
1054   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zero p device)
1055   if (r == -1)
1056     then do
1057       err <- last_error h
1058       fail err
1059     else return ()
1060
1061 foreign import ccall unsafe "guestfs_grub_install" c_grub_install
1062   :: GuestfsP -> CString -> CString -> IO (CInt)
1063
1064 grub_install :: GuestfsH -> String -> String -> IO ()
1065 grub_install h root device = do
1066   r <- withCString root $ \root -> withCString device $ \device -> withForeignPtr h (\p -> c_grub_install p root device)
1067   if (r == -1)
1068     then do
1069       err <- last_error h
1070       fail err
1071     else return ()
1072
1073 foreign import ccall unsafe "guestfs_cp" c_cp
1074   :: GuestfsP -> CString -> CString -> IO (CInt)
1075
1076 cp :: GuestfsH -> String -> String -> IO ()
1077 cp h src dest = do
1078   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp p src dest)
1079   if (r == -1)
1080     then do
1081       err <- last_error h
1082       fail err
1083     else return ()
1084
1085 foreign import ccall unsafe "guestfs_cp_a" c_cp_a
1086   :: GuestfsP -> CString -> CString -> IO (CInt)
1087
1088 cp_a :: GuestfsH -> String -> String -> IO ()
1089 cp_a h src dest = do
1090   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_cp_a p src dest)
1091   if (r == -1)
1092     then do
1093       err <- last_error h
1094       fail err
1095     else return ()
1096
1097 foreign import ccall unsafe "guestfs_mv" c_mv
1098   :: GuestfsP -> CString -> CString -> IO (CInt)
1099
1100 mv :: GuestfsH -> String -> String -> IO ()
1101 mv h src dest = do
1102   r <- withCString src $ \src -> withCString dest $ \dest -> withForeignPtr h (\p -> c_mv p src dest)
1103   if (r == -1)
1104     then do
1105       err <- last_error h
1106       fail err
1107     else return ()
1108
1109 foreign import ccall unsafe "guestfs_drop_caches" c_drop_caches
1110   :: GuestfsP -> CInt -> IO (CInt)
1111
1112 drop_caches :: GuestfsH -> Int -> IO ()
1113 drop_caches h whattodrop = do
1114   r <- withForeignPtr h (\p -> c_drop_caches p (fromIntegral whattodrop))
1115   if (r == -1)
1116     then do
1117       err <- last_error h
1118       fail err
1119     else return ()
1120
1121 foreign import ccall unsafe "guestfs_ping_daemon" c_ping_daemon
1122   :: GuestfsP -> IO (CInt)
1123
1124 ping_daemon :: GuestfsH -> IO ()
1125 ping_daemon h = do
1126   r <- withForeignPtr h (\p -> c_ping_daemon p)
1127   if (r == -1)
1128     then do
1129       err <- last_error h
1130       fail err
1131     else return ()
1132
1133 foreign import ccall unsafe "guestfs_zerofree" c_zerofree
1134   :: GuestfsP -> CString -> IO (CInt)
1135
1136 zerofree :: GuestfsH -> String -> IO ()
1137 zerofree h device = do
1138   r <- withCString device $ \device -> withForeignPtr h (\p -> c_zerofree p device)
1139   if (r == -1)
1140     then do
1141       err <- last_error h
1142       fail err
1143     else return ()
1144
1145 foreign import ccall unsafe "guestfs_pvresize" c_pvresize
1146   :: GuestfsP -> CString -> IO (CInt)
1147
1148 pvresize :: GuestfsH -> String -> IO ()
1149 pvresize h device = do
1150   r <- withCString device $ \device -> withForeignPtr h (\p -> c_pvresize p device)
1151   if (r == -1)
1152     then do
1153       err <- last_error h
1154       fail err
1155     else return ()
1156
1157 foreign import ccall unsafe "guestfs_sfdisk_N" c_sfdisk_N
1158   :: GuestfsP -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (CInt)
1159
1160 sfdisk_N :: GuestfsH -> String -> Int -> Int -> Int -> Int -> String -> IO ()
1161 sfdisk_N h device n cyls heads sectors line = do
1162   r <- withCString device $ \device -> withCString line $ \line -> withForeignPtr h (\p -> c_sfdisk_N p device (fromIntegral n) (fromIntegral cyls) (fromIntegral heads) (fromIntegral sectors) line)
1163   if (r == -1)
1164     then do
1165       err <- last_error h
1166       fail err
1167     else return ()
1168
1169 foreign import ccall unsafe "guestfs_vg_activate_all" c_vg_activate_all
1170   :: GuestfsP -> CInt -> IO (CInt)
1171
1172 vg_activate_all :: GuestfsH -> Bool -> IO ()
1173 vg_activate_all h activate = do
1174   r <- withForeignPtr h (\p -> c_vg_activate_all p (fromBool activate))
1175   if (r == -1)
1176     then do
1177       err <- last_error h
1178       fail err
1179     else return ()
1180
1181 foreign import ccall unsafe "guestfs_vg_activate" c_vg_activate
1182   :: GuestfsP -> CInt -> Ptr CString -> IO (CInt)
1183
1184 vg_activate :: GuestfsH -> Bool -> [String] -> IO ()
1185 vg_activate h activate volgroups = do
1186   r <- withMany withCString volgroups $ \volgroups -> withArray0 nullPtr volgroups $ \volgroups -> withForeignPtr h (\p -> c_vg_activate p (fromBool activate) volgroups)
1187   if (r == -1)
1188     then do
1189       err <- last_error h
1190       fail err
1191     else return ()
1192
1193 foreign import ccall unsafe "guestfs_lvresize" c_lvresize
1194   :: GuestfsP -> CString -> CInt -> IO (CInt)
1195
1196 lvresize :: GuestfsH -> String -> Int -> IO ()
1197 lvresize h device mbytes = do
1198   r <- withCString device $ \device -> withForeignPtr h (\p -> c_lvresize p device (fromIntegral mbytes))
1199   if (r == -1)
1200     then do
1201       err <- last_error h
1202       fail err
1203     else return ()
1204
1205 foreign import ccall unsafe "guestfs_resize2fs" c_resize2fs
1206   :: GuestfsP -> CString -> IO (CInt)
1207
1208 resize2fs :: GuestfsH -> String -> IO ()
1209 resize2fs h device = do
1210   r <- withCString device $ \device -> withForeignPtr h (\p -> c_resize2fs p device)
1211   if (r == -1)
1212     then do
1213       err <- last_error h
1214       fail err
1215     else return ()
1216
1217 foreign import ccall unsafe "guestfs_e2fsck_f" c_e2fsck_f
1218   :: GuestfsP -> CString -> IO (CInt)
1219
1220 e2fsck_f :: GuestfsH -> String -> IO ()
1221 e2fsck_f h device = do
1222   r <- withCString device $ \device -> withForeignPtr h (\p -> c_e2fsck_f p device)
1223   if (r == -1)
1224     then do
1225       err <- last_error h
1226       fail err
1227     else return ()
1228
1229 foreign import ccall unsafe "guestfs_sleep" c_sleep
1230   :: GuestfsP -> CInt -> IO (CInt)
1231
1232 sleep :: GuestfsH -> Int -> IO ()
1233 sleep h secs = do
1234   r <- withForeignPtr h (\p -> c_sleep p (fromIntegral secs))
1235   if (r == -1)
1236     then do
1237       err <- last_error h
1238       fail err
1239     else return ()
1240
1241 foreign import ccall unsafe "guestfs_ntfs_3g_probe" c_ntfs_3g_probe
1242   :: GuestfsP -> CInt -> CString -> IO (CInt)
1243
1244 ntfs_3g_probe :: GuestfsH -> Bool -> String -> IO (Int)
1245 ntfs_3g_probe h rw device = do
1246   r <- withCString device $ \device -> withForeignPtr h (\p -> c_ntfs_3g_probe p (fromBool rw) device)
1247   if (r == -1)
1248     then do
1249       err <- last_error h
1250       fail err
1251     else return (fromIntegral r)
1252
1253 foreign import ccall unsafe "guestfs_scrub_device" c_scrub_device
1254   :: GuestfsP -> CString -> IO (CInt)
1255
1256 scrub_device :: GuestfsH -> String -> IO ()
1257 scrub_device h device = do
1258   r <- withCString device $ \device -> withForeignPtr h (\p -> c_scrub_device p device)
1259   if (r == -1)
1260     then do
1261       err <- last_error h
1262       fail err
1263     else return ()
1264
1265 foreign import ccall unsafe "guestfs_scrub_file" c_scrub_file
1266   :: GuestfsP -> CString -> IO (CInt)
1267
1268 scrub_file :: GuestfsH -> String -> IO ()
1269 scrub_file h file = do
1270   r <- withCString file $ \file -> withForeignPtr h (\p -> c_scrub_file p file)
1271   if (r == -1)
1272     then do
1273       err <- last_error h
1274       fail err
1275     else return ()
1276
1277 foreign import ccall unsafe "guestfs_scrub_freespace" c_scrub_freespace
1278   :: GuestfsP -> CString -> IO (CInt)
1279
1280 scrub_freespace :: GuestfsH -> String -> IO ()
1281 scrub_freespace h dir = do
1282   r <- withCString dir $ \dir -> withForeignPtr h (\p -> c_scrub_freespace p dir)
1283   if (r == -1)
1284     then do
1285       err <- last_error h
1286       fail err
1287     else return ()
1288
1289 foreign import ccall unsafe "guestfs_wc_l" c_wc_l
1290   :: GuestfsP -> CString -> IO (CInt)
1291
1292 wc_l :: GuestfsH -> String -> IO (Int)
1293 wc_l h path = do
1294   r <- withCString path $ \path -> withForeignPtr h (\p -> c_wc_l p path)
1295   if (r == -1)
1296     then do
1297       err <- last_error h
1298       fail err
1299     else return (fromIntegral r)
1300
1301 foreign import ccall unsafe "guestfs_wc_w" c_wc_w
1302   :: GuestfsP -> CString -> IO (CInt)
1303
1304 wc_w :: GuestfsH -> String -> IO (Int)
1305 wc_w h path = do
1306   r <- withCString path $ \path -> withForeignPtr h (\p -> c_wc_w p path)
1307   if (r == -1)
1308     then do
1309       err <- last_error h
1310       fail err
1311     else return (fromIntegral r)
1312
1313 foreign import ccall unsafe "guestfs_wc_c" c_wc_c
1314   :: GuestfsP -> CString -> IO (CInt)
1315
1316 wc_c :: GuestfsH -> String -> IO (Int)
1317 wc_c h path = do
1318   r <- withCString path $ \path -> withForeignPtr h (\p -> c_wc_c p path)
1319   if (r == -1)
1320     then do
1321       err <- last_error h
1322       fail err
1323     else return (fromIntegral r)
1324