A handy little consequence of the Cont monad

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

On Fri, 1 Feb 2008, 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.
Nice idea. Could serve as an explanation what the Cont monad is good for. What about uploading it to the Wiki Category:Idioms ?

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

On Fri, 2008-02-01 at 00:09 -0500, 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))
This is what you write after all that time on #haskell? nest = runCont . sequence . map Cont

Not to start a flame war or religious debate, but I don't think that eta-expansions should be considered bad style. I realize that composition-style is good for certain types of reasoning, but fully eta-expanded code has an important legibility advantage: you can tell the shape of its type just by looking at it! Personally, I'd rather read the original version. -Dan On Feb01, Derek Elkins wrote:
On Fri, 2008-02-01 at 00:09 -0500, 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))
This is what you write after all that time on #haskell?
nest = runCont . sequence . map Cont
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

It's a matter of taste. I prefer the function composition in this case.
It reads nicely as a pipeline.
-- Lennart
On Fri, Feb 1, 2008 at 9:48 PM, Dan Licata
Not to start a flame war or religious debate, but I don't think that eta-expansions should be considered bad style. I realize that composition-style is good for certain types of reasoning, but fully eta-expanded code has an important legibility advantage: you can tell the shape of its type just by looking at it! Personally, I'd rather read the original version.
-Dan
On Feb01, Derek Elkins wrote:
On Fri, 2008-02-01 at 00:09 -0500, 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))
This is what you write after all that time on #haskell?
nest = runCont . sequence . map Cont
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Folks On 1 Feb 2008, at 22:19, Lennart Augustsson wrote:
It's a matter of taste. I prefer the function composition in this case. It reads nicely as a pipeline.
-- Lennart
Dan L :
On Fri, Feb 1, 2008 at 9:48 PM, Dan Licata
wrote: Not to start a flame war or religious debate, but I don't think that eta-expansions should be considered bad style.
Cale:
nest :: [(r -> a) -> a] -> ([r] -> a) -> a nest xs = runCont (sequence (map Cont xs))
Derek:
This is what you write after all that time on #haskell?
nest = runCont . sequence . map Cont
Pardon my voodoo (apologies to libraries readers, but here we go again, slightly updated). With these useful general purpose goodies...
module Newtype where
import Data.Monoid
class Newtype p u | p -> u where unpack :: p -> u
instance Newtype p u => Newtype (a -> p) (a -> u) where unpack = (unpack .)
op :: Newtype p u => (u -> p) -> p -> u op _ p = unpack p
wrap :: Newtype p u => (x -> y) ->(y -> p) -> x -> u wrap pack f = unpack . f . pack
ala :: Newtype p' u' => (u -> p) -> ((a -> p) -> b -> p') -> (a -> u) -> b -> u' ala pack hitWith = wrap (pack .) hitWith
...and the suitable Newtype instance for Cont, I get to write... nest = ala Cont traverse id ..separating the newtype encoding from what's really going on, fusing the map with the sequence, and generalizing to any old Traversable structure. Third-order: it's a whole other order. Conor

Hello Conor, Saturday, February 2, 2008, 1:29:02 AM, you wrote:
nest = ala Cont traverse id
Third-order: it's a whole other order.
oh! i remember faces of my friends when i showed them something like "sortOn snd . zip [0..]". probably i have the same face now :))) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Fri, Feb 01, 2008 at 10:19:17PM +0000, Lennart Augustsson wrote:
It's a matter of taste. I prefer the function composition in this case. It reads nicely as a pipeline.
(Hoping not to contribute to any flamage...) I've always liked $ for this kind of code, if you want to keep the arguments around: next xs = runCont $ sequence $ map Cont xs seems quite natural to me. Phil -- http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt

On 04/02/2008, Philip Armstrong
I've always liked $ for this kind of code, if you want to keep the arguments around:
next xs = runCont $ sequence $ map Cont xs
seems quite natural to me.
I'd probably write that as nest xs = runCont . sequence . map Cont $ xs or else as: nest xs = runCont . sequence $ map Cont xs so as not to abuse the fact that ($) really has the wrong associativity. (I didn't really give that aspect of the code a moment's thought, or else I'd probably have made it either points-free or used the first form above. I've been bitten by the MR enough times that I'm wary of eta-reducing the last parameter out of functions -- of course, the explicit type signature means it doesn't matter.) It would be nice to flip the associativity of ($) someday. It loses little in the way of expressiveness, since one can generally replace the first (n-1) instances of ($) with (.) straightforwardly (the one exception to this being when there are other operator symbols like (***) acting on the functions involved, but these cases are fairly rare, and it's arguably clearer to leave those parens in). What it would buy us to make ($) left associative is that we could, for instance, remove the parens from an expression like: f (g x) (h y) (k z) getting: f $ g x $ h y $ k z Perhaps for Haskell 2. :) - Cale

On Mon, 2008-02-04 at 16:56 -0500, Cale Gibbard wrote:
On 04/02/2008, Philip Armstrong
wrote: I've always liked $ for this kind of code, if you want to keep the arguments around:
next xs = runCont $ sequence $ map Cont xs
seems quite natural to me.
I'd probably write that as
nest xs = runCont . sequence . map Cont $ xs
or else as:
nest xs = runCont . sequence $ map Cont xs
so as not to abuse the fact that ($) really has the wrong associativity. (I didn't really give that aspect of the code a moment's thought, or else I'd probably have made it either points-free or used the first form above. I've been bitten by the MR enough times that I'm wary of eta-reducing the last parameter out of functions -- of course, the explicit type signature means it doesn't matter.)
It would be nice to flip the associativity of ($) someday. It loses little in the way of expressiveness, since one can generally replace the first (n-1) instances of ($) with (.) straightforwardly (the one exception to this being when there are other operator symbols like (***) acting on the functions involved, but these cases are fairly rare, and it's arguably clearer to leave those parens in).
What it would buy us to make ($) left associative is that we could, for instance, remove the parens from an expression like:
f (g x) (h y) (k z)
getting:
f $ g x $ h y $ k z
and also, pointedly, f $! g x $! h y $! k z or even just f $! x $! y
Perhaps for Haskell 2. :)
We'll get rid of the monomorphism restriction then too and you won't have to be wary.

On Fri, 2008-02-01 at 16:48 -0500, Dan Licata wrote:
Not to start a flame war or religious debate, but I don't think that eta-expansions should be considered bad style. I realize that composition-style is good for certain types of reasoning, but fully eta-expanded code has an important legibility advantage: you can tell the shape of its type just by looking at it! Personally, I'd rather read the original version.
Clearly you don't hang out on #haskell enough and have missed the humor.

derek.a.elkins:
On Fri, 2008-02-01 at 16:48 -0500, Dan Licata wrote:
Not to start a flame war or religious debate, but I don't think that eta-expansions should be considered bad style. I realize that composition-style is good for certain types of reasoning, but fully eta-expanded code has an important legibility advantage: you can tell the shape of its type just by looking at it! Personally, I'd rather read the original version.
Clearly you don't hang out on #haskell enough and have missed the humor.
For those not following, the last thing one does before comitting any Haskell code, once you've been on #haskell, is to feed it to lambdabot for "improvement" :) dons> @pl \f g (a,b) -> (f a, g b) lambdabot> flip flip snd . (ap .) . flip flip fst . ((.) .) . flip . (((.) . (,)) .) Ah, much better. We have a strange culture. -- Don
participants (10)
-
Bulat Ziganshin
-
Cale Gibbard
-
ChrisK
-
Conor McBride
-
Dan Licata
-
Derek Elkins
-
Don Stewart
-
Henning Thielemann
-
Lennart Augustsson
-
Philip Armstrong