[C2hs] A new kind of output marshallers *- (patch attached)

Einar Karttunen ekarttun at cs.helsinki.fi
Sat Sep 2 09:28:04 EDT 2006


Hello

When wrapping libraries that return error codes from functions
a monadic output marshaller that does not return a value is
very useful. This implements *- output marshallers that take
the value and consume it, but don't return a result.

This is used like:

foo_error_t foo_something(random, arguments);

type Err = {#type foo_error_t#}

{#fun {`Foo', `Bar'} -> `()' handleError*- #}

handleError :: Err -> IO ()
handleError ...

- Einar Karttunen
-------------- next part --------------

New patches:

[Support for *- out marshallers
Einar Karttunen <ekarttun at cs.helsinki.fi>**20060902132122
 
 Implement *- out marshallers that are a monadic
 action but their return values are ignored. This
 is very useful for converting error codes into
 exceptions.
] {
hunk ./c2hs/chs/CHS.hs 68
---  parm     -> [ident_1 [`*' | `-']] verbhs [`&'] [ident_2 [`*' | `-']]
+--  parm     -> [ident_1 [`*' | `-']] verbhs [`&'] [ident_2 [`*'] [`-']]
hunk ./c2hs/chs/CHS.hs 276
+            | CHSIOVoidArg                      -- drops argument, but in monad
hunk ./c2hs/chs/CHS.hs 563
-					   CHSValArg  -> id
-					   CHSIOArg   -> showString "*"
-					   CHSVoidArg -> showString "-")
+					   CHSValArg    -> id
+					   CHSIOArg     -> showString "*"
+					   CHSVoidArg   -> showString "-"
+                                           CHSIOVoidArg -> showString "*-")
hunk ./c2hs/chs/CHS.hs 964
+    parseOptMarsh (CHSTokIdent _ ide:CHSTokStar _ :CHSTokMinus _:toks) = 
+      return (Just (ide, CHSIOVoidArg) , toks)
hunk ./c2hs/gen/GenBind.hs 842
+	            CHSParm _ _ twoCVal (Just (omIde, CHSIOVoidArg)) _ ->
+	              "  " ++ identToLexeme omIde ++ " res >> \n"
hunk ./c2hs/gen/GenBind.hs 851
-	            CHSParm _ _ _ (Just (_, CHSVoidArg)) _ ->        retArgs
-	            _					   -> "res'":retArgs
+	            CHSParm _ _ _ (Just (_, CHSVoidArg))   _ ->        retArgs
+	            CHSParm _ _ _ (Just (_, CHSIOVoidArg)) _ ->        retArgs
+	            _					     -> "res'":retArgs
hunk ./c2hs/gen/GenBind.hs 892
-	notVoid (Just (_, kind)) = kind /= CHSVoidArg
+	notVoid (Just (_, kind)) = kind /= CHSVoidArg && kind /= CHSIOVoidArg
hunk ./c2hs/gen/GenBind.hs 918
-		     CHSVoidArg -> ""
-		     CHSIOArg   -> omApp ++ ">>= \\" ++ outBndr ++ " -> "
-		     CHSValArg  -> "let {" ++ outBndr ++ " = " ++ 
+		     CHSVoidArg   -> ""
+		     CHSIOVoidArg -> omApp ++ ">>"
+		     CHSIOArg     -> omApp ++ ">>= \\" ++ outBndr ++ " -> "
+		     CHSValArg    -> "let {" ++ outBndr ++ " = " ++ 
hunk ./c2hs/gen/GenBind.hs 923
-	retArg   = if omArgKind == CHSVoidArg then "" else outBndr
+	retArg   = if omArgKind == CHSVoidArg || omArgKind == CHSIOVoidArg then "" else outBndr
hunk ./doc/c2hs/c2hs.sgml 372
-[<it/inmarsh/ [* | -]] <it/hsty/ [&] [<it/outmarsh/ [* | -]]
+[<it/inmarsh/ [* | -]] <it/hsty/ [&] [<it/outmarsh/ [*] [-]]
hunk ./doc/c2hs/c2hs.sgml 387
+The <tt/*-/ output marshal specification is for monadic actions that
+must be executed but whose results are discarded. This is very useful
+for e.g. checking an error value and throwing an exception if needed.
+<p>
hunk ./doc/c2hs/c2hs.sgml 740
-parm     -> [ident_1 [`*' | `-']] verbhs [`&'] [ident_2 [`*' | `-']]
+parm     -> [ident_1 [`*' | `-']] verbhs [`&'] [ident_2 [`*'] [`-']]
}

Context:

[Cancel previous patch installing the c2hs library
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20060525181726] 
[Teach c2hs about C style line pragmas for accurate source location info.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060524174216] 
[Fix typo
Jelmer Vernooij <jelmer at samba.org>**20060208004733] 
[Install helper library for use by other packages
Jelmer Vernooij <jelmer at samba.org>**20060207224532] 
[Use PreCST for CParser to avoid unnecessary module deps
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060523142434] 
[Make the C parser test prog build again.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060523135822
 This program is useful for reproducing C parser errors
 for when users send in their .i files.
 
 Just run:
 ./parse foo.i
 
 Build using:
 ghc --make Main.hs -o parse ../i -i../../../base/general
   -i../../../base/admin -i../../../base/errors
   -i../../../base/state -i../../../base/syms -i../../state
] 
[change handling of marshallers for dynamic function hooks
Udo Stenzel <u.stenzel at web.de>**20060515142639] 
[minor beautification
Udo Stenzel <u.stenzel at web.de>**20060430215444] 
[support fun hooks for FunPtrs inside structs
Udo Stenzel <u.stenzel at web.de>**20060429235956
 This is a bit hackish at times, as I cut-and-paste-coded a bit.  Though
 pending cleanup, it seems to work.
] 
[improve translation of apath to identifier
Udo Stenzel <u.stenzel at web.de>**20060429235900] 
[allow call hooks for FunPtrs inside structures
Udo Stenzel <u.stenzel at web.de>**20060429155023] 
[Allow escape sequences in the file name part of #line directives
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060406214715] 
[darcs.haskell.org repo
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20060514224852] 
[calculate size of embedded arrays correctly
Udo Stenzel <u.stenzel at web.de>**20060502231635] 
[Adapt Setup.hs to Cabal in GHC 6.4.2
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20060429012513
 
   ** WARNING: This will break the build on GHC 6.4.1 and earlier! **
 
   On GHC 6.4.1 and earlier omit this patch or follow the instructions
   in `Setup.hs'.
 
] 
[Version 0.14.6 credits
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20060429012404] 
[tolerate variadic functions
Udo Stenzel <u.stenzel at web.de>**20060423234358
 This adds support for pointers to variadic functions in structs.  They
 cannot be called, but the rest of the struct is accessible without c2hs
 bombing out.
] 
[enum define workaround example
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20051219124518] 
[TAG c2hs 0.14.5
Manuel M T Chakravarty <chak at cse.unsw.edu.au>**20051212115038] 
Patch bundle hash:
493766174e50ca758b23cd42097cf82cd9befb16


More information about the C2hs mailing list