
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