[Haskell-beginners] Split list by list using Continuations

Dmitriy Matrosov sgf.dma at gmail.com
Tue Sep 24 16:30:24 CEST 2013


Hi.

I want to write a function to split list by list. E.g. if i have input list
"aXYbc" and list "XY" is separator, then result should be ["a", "bc"]. And i
want to write it using Continuations. Here is my version, which implements
following scheme:

   ..  >>= f x(k+1) >>= f x(k+2) >>= f x(k+3) >>= f x(k+4) >>= ..
              ....(match to sep) ..........>+
                                            | (failed)
              +<= (continuation backward) <=+
(add to word) |
              \------->..(match to sep).....+
                                            | (succeed)
                                            +------>+.. (match to sep) ..

> import qualified Data.Foldable as F
> import Control.Applicative
> import Control.Monad.Cont
>
> nullF :: F.Foldable t => t a -> Bool
> nullF               = null . F.toList
>
> addToHeadA :: Alternative f => a -> [f a] -> [f a]
> addToHeadA x []       = [pure x]
> addToHeadA x (y : ys) = (pure x <|> y) : ys
>
> type Sep a          = [a]   -- Word separator.
> type Res5 f a       = [f a] -- Result.
> data SplitState5 m f a  = MaybeSep5 (Sep a) (Res5 f a)
>                                     (() -> m (SplitState5 m f a))
>                         | Word5 (Res5 f a)
> 
> split5M :: (Eq a, F.Foldable t, Alternative f, MonadCont m) =>
>            Sep a -> t a -> m (Res5 f a)
> split5M ks0 xs
>   | nullF xs        = return []
>   | otherwise       = F.foldrM go (Word5 [empty]) xs >>= finalize
>   where
>     ksR             = reverse ks0
>     --go :: (Eq a, MonadCont m) =>
>     --      a -> SplitState5 m f a -> m (SplitState5 m f a)
>     go _ (MaybeSep5 []  _  h) = h ()
>     go x (MaybeSep5 [k] zs _)
>       | x == k      = return (Word5 (empty : zs))
>     go x (MaybeSep5 (k : ks) zs h)
>       | x == k      = return (MaybeSep5 ks zs h)
>       | otherwise   = h ()
>     go x (Word5 zs) = callCC $ \r -> do
>                         callCC $ \h -> go x (MaybeSep5 ksR zs h) >>= r
>                         return (Word5 (x `addToHeadA` zs))
>     finalize :: (Alternative f, MonadCont m) =>
>                 SplitState5 m f a -> m (Res5 f a)
>     finalize (Word5 zs)         = return zs
>     finalize (MaybeSep5 _ _ h)  = h () >> return undefined
>

And i have several questions about this implementation:
    - Is it good CPS implementation? Or there is much simpler and better one?
    - Can it be improved?
    - Can i make it more generic?
    - Would non-CPS implementation be better or simpler, than this one?

--
    Dmitriy Matrosov




More information about the Beginners mailing list