[Haskell-cafe] Re: Why is there no splitBy in the list module?
Jon Fairbairn
jon.fairbairn at cl.cam.ac.uk
Thu Jul 20 13:31:44 EDT 2006
On 2006-07-13 at 10:16BST I wrote:
> Hooray! I've been waiting to ask "Why aren't we asking what
> laws hold for these operations?"
Having thought about this for a bit, I've come up with the
below. This is intended to give the general idea -- it's not
polished code, and I'm not at all wedded to the names I've
used, and it almost certainly should be split up.
> module Parts (parts, fromParts, contiguousParts, segmentsSatisfying) where
> import List (groupBy)
> parts p = map hack . groupBy sameSide . map (predicateToEither p)
> fromParts = concat . map fromEither
Now we should have fromParts . parts p ⊑ (id:: [a]->[a])
In particular, it should be possible to apply a function
to all the Right parts, and then reconstruct the list with
the Left parts left alone.
for example
fromParts . mapRight uc_first . parts Char.isAlpha $ "A random list of words\non lines"
where uc_first [] = []
uc_first (a:as) = Char.toUpper a:as
=> "A Random List Of Words\nOn Lines"
> contiguousParts p l = [a | Right a <- parts p l]
so words = contiguousParts Char.isAlphaNum
> segmentsSatisfying predicate
> = concat . map dropSeps . parts predicate
> where dropSeps e
> = case e of
> Left x -> map (const []) $ tail x
> Right r -> [r]
So
lines = segmentsSatisfying (/= '\n')
... but the tail in the definition of segmentsSatisfying
makes me uneasy.
needing the function `hack` suggests that the definition of
parts is written badly
> hack (Left x:rest) = Left (x: map (\(Left x) -> x) rest)
> hack (Right x:rest) = Right (x: map (\(Right x) -> x) rest)
what follows must surely exist in a library somewhere?
I'd expect it to be called Either...
> predicateToEither :: (a -> Bool) -> a -> Either a a
> predicateToEither p x = if p x
> then Right x
> else Left x
> sameSide (Left _) (Left _) = True
> sameSide (Right _) (Right _) = True
> sameSide _ _ = False
> fromEither (Left x) = x
> fromEither (Right x) = x
> liftE f1 f2 = either (Left . f1) (Right . f2)
> mapRight f = map (onRight f)
> onRight f = liftE id f
> mapLeft f = map (onLeft f)
> onLeft f = liftE f id
we could do some of half of those using this:
> instance Functor (Either a) where
> fmap f (Right a) = Right (f a)
> fmap f (Left l) = Left l
Is a Monad instance any use?
> instance Monad (Either a) where
> Right a >>= f = f a
> Left l >>= f = Left l
> return = Right
--
Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk
More information about the Libraries
mailing list