[Haskell-cafe] Re: A handy little consequence of the Cont monad

ChrisK haskell at list.mightyreason.com
Fri Feb 1 09:18:05 EST 2008


The "bit of a mess" that comes from avoiding monads is (my version):
> import Foreign.Marshal.Array(withArray0)
> import Foreign.Ptr(nullPtr,Ptr)
> import Foreign.C.String(withCString,CString)

This uses withCString in order of the supplied strings, and a difference list 
([CString]->[CString]) initialized by "id" to assemble the [CString].  This is 
the laziest way to proceed.

> acquireInOrder :: [String] -> (Ptr CString -> IO a) -> IO a
> acquireInOrder strings act =
> foldr (\s cs'io'a ->
>         (\cs ->
>           withCString s (\c -> cs'io'a (cs . (c:))
>                         )
>         )
>       )
>       (\cs ->
>          withArray0 nullPtr (cs []) act
>       )
>       strings
>       id

This uses in withCString in reversed order of the supplied strings, and normal 
list ([CString]) initialized by "[]" to assemble the [CString].  This is not as 
lazy since it needs to go to the end of the supplied list for the first IO action.

> acquireInRerverseOrder :: [String] -> (Ptr CString -> IO a) -> IO a
> acquireInRerverseOrder strings act =
>   foldl (\cs'io'a s ->
>           (\cs ->
>             withCString s (\c -> cs'io'a (c:cs)
>                           )
>           )
>         )
>         (\cs ->
>            withArray0 nullPtr cs act
>         )
>         strings
>         []


Cale Gibbard wrote:
> Hello,
> 
> Today on #haskell, resiak was asking about a clean way to write the
> function which allocates an array of CStrings using withCString and
> withArray0 to produce a new with* style function. I came up with the
> following:
> 
> nest :: [(r -> a) -> a] -> ([r] -> a) -> a
> nest xs = runCont (sequence (map Cont xs))
> 
> withCStringArray0 :: [String] -> (Ptr CString -> IO a) -> IO a
> withCStringArray0 strings act = nest (map withCString strings)
>                                      (\rs -> withArray0 nullPtr rs act)
> 
> Originally, I'd written nest without using the Cont monad, which was a
> bit of a mess by comparison, then noticed that its type was quite
> suggestive.
> 
> Clearly, it would be more generally useful whenever you have a bunch
> of with-style functions for managing the allocation of resources, and
> would like to turn them into a single with-style function providing a
> list of the acquired resources.
> 
>  - Cale



More information about the Haskell-Cafe mailing list