Re: [Haskell-cafe] Parse text difficulty

Conor McBride writes:
Jan-Willem Maessen - Sun Labs East wrote:
Tomasz Zielonka wrote:
I found it useful recently, when I needed zip functions for Trees - this way I didn't have to define functions for 3 trees, 4 trees, and so on.
Note also that:
repeat f `zwApply` xs = map f xs
When cooking up my own collection-y things (including splittable supplies, for example), I generally provide fmap and an equivalent of zwApply (a generic repeat is not quite so simple or useful). It's a nice little idiom, and a recommend it highly. ^^^^^
Funny you should choose that word:
http://www.mail-archive.com/haskell@haskell.org/msg15073.html
saves me banging the same old drum.
Now that I think about it, you can generalize the trick I mentioned elsewhere to work over any Idiom/Sequence/more-than-a-functor-not-yet-a-monad thingy.
class Sequence f where unit :: a -> f a (<*>) :: f (a -> b) -> f a -> f b
liftN :: Sequence f => (f a -> b) -> a -> b liftN d f = d (unit f)
suc :: Sequence f => (f b -> c) -> f (a -> b) -> f a -> c suc d f x = d (f <*> x)
zero = id
one :: Sequence f => f (a -> b) -> f a -> f b one = suc zero
two :: Sequence f => f (a -> b -> c) -> f a -> f b -> f c two = suc one
newtype L1 a = L1 { unL1 :: [a] } newtype L2 a = L2 { unL2 :: [a] }
instance Idiom L1 where unit x = L1 [x] L1 fs <*> L1 xs = L1 [ f x | f <- fs, x <- xs ]
instance Idiom L2 where unit x = L2 (repeat x) L2 fs <*> L2 xs = L2 (zipWith ($) fs xs)
*Main> unL1 $ liftN two (,) (L1 [1,2,3]) (L1 "abc")
[(1,'a'),(1,'b'),(1,'c'),(2,'a'),(2,'b'),(2,'c'),(3,'a'),(3,'b'),(3,'c')
]
*Main> unL2 $ liftN two (,) (L2 [1,2,3]) (L2 "abc")
[(1,'a'),(2,'b'),(3,'c')]
--
David Menendez

David Menendez wrote:
Now that I think about it, you can generalize the trick I mentioned elsewhere to work over any Idiom/Sequence/more-than-a-functor-not-yet-a-monad thingy.
Just to fill in the genealogy: the numeral thing is from Daniel Fridlender and Mia Indrika's 'Do we need dependent types?', it's inspired by Olivier Danvy's 'Functional Unparsing' and it was part of the inspiration for my own 'Faking It'.
*Main> unL1 $ liftN two (,) (L1 [1,2,3]) (L1 "abc") [(1,'a'),(1,'b'),(1,'c'),(2,'a'),(2,'b'),(2,'c'),(3,'a'),(3,'b'),(3,'c') ] *Main> unL2 $ liftN two (,) (L2 [1,2,3]) (L2 "abc") [(1,'a'),(2,'b'),(3,'c')]
My funny brackety notation, cheap hack though it is, spares the counting idI (,) (L1 [1,2,3]) (L1 "abc") Idi etc. Here's an idiom I knocked up the other day. It's quite like the zipWith, except that it pads instead of truncating (so it's like the zero and max monoid, not the infinity and min monoid). data Paddy x = Pad [x] x instance Idiom Paddy where idi x = Pad [] x Pad fs fp <%> Pad ss sp = Pad (papp fs ss) (fp sp) where papp [] [] = [] papp [] ss = map (fp $) ss papp fs [] = map ($ sp) fs papp (f : fs) (s : ss) = f s : papp fs ss I use it for two-dimensional formatting. type Box = Paddy (Paddy Char) Idioms have two key good points (1) they look applicative (2) they compose without difficulty If you're willing to make the types distinguish the idioms you're using, as in choice-lists and vector-lists, then a lot of routine operations wither to a huddle of combinators sitting under a type signature which actually does most of the work. Instance inference is like having a great rhythm section: you hum it, they play it. Cheers Conor -- http://www.cs.nott.ac.uk/~ctm
participants (2)
-
Conor McBride
-
David Menendez