{-| Module : StrTok Description : Provides the strTok function License : Public Domain Maintainer : Manuel Eberl Stability : experimental This module provides the function @strTok@, a variant of the @strtok@ function in C and PHP. This function can be used to tokenise a string (or, more generally, a list) with successive calls of the @strtok@ function. Since @strTok@ is a stateful function (it produces different results when called with the same parameter multiple times), computations using @strTok@ must take place in the @StrTok@ monad or the @StrTokT@ monad transformer. -} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Acme.StrTok ( -- * The StrTokT monad transformer StrTokT, runStrTokT, -- * The StrTok monad StrTok, runStrTok, -- * The strTok function strTok ) where import Control.Applicative import Control.Monad import Control.Monad.State import Control.Monad.Identity import Control.Monad.Trans -- | The @StrTokT@ monad, parametrised with: -- -- * @s@ - The type of list elements (e.g. @Char@ if the input to @strTok@ is a @String@). -- -- * @m@ - The inner monad. newtype StrTokT s m a = StrTokT (StateT [s] m a) deriving (Functor, Applicative, Alternative, Monad, MonadPlus, MonadFix, MonadTrans, MonadIO) -- | Executes a @strTok@ computation in the state transformer monad @StrTokT@. runStrTokT :: Functor m => StrTokT s m a -> m a runStrTokT (StrTokT x) = fmap fst (runStateT x []) -- | The @StrTok@ monad. type StrTok s = StrTokT s Identity -- | Executes a @strTok@ computation in the state monad @StrTok@. runStrTok :: StrTok s a -> a runStrTok = runIdentity . runStrTokT -- | A Haskell variant of the @strtok@ function from C and PHP. This function splits a string into tokens which are -- delimited by a given set of characters. A call with @Just s@ and the delimiting characters @ds@ will yield -- the first token in @s@ that is delimited by characters from @ds@. Every subsequent call of @strTok@ with @Nothing@ -- will yield the next token. If the string contains no more tokens, an empty list is returned. -- -- @strTok@ returns a stateful computation of type @StrTokT a m [a]@ (or @StrTok a [a]@). -- Several invocations of @strTok@ and computations with the results can be chained in the @StrTokT@ (resp. @StrTok@) -- monad and then executed with @runStrTokT@ (resp. @runStrTok@). -- -- Example: -- -- >runStrTokT $ -- > do a <- strTok (Just "- This, a sample string.") " ,.-" -- > b <- strTok Nothing " ,.-" -- > c <- strTok Nothing ",.-" -- > return (a, b, c) -- -- evaluates to -- -- >("This","a"," sample string") strTok :: (Eq a, Monad m) => Maybe [a] -> [a] -> StrTokT a m [a] strTok s delims = StrTokT $ StateT $ maybe strTok' (const . strTok') s where strTok' = return . break (`elem` delims) . dropWhile (`elem` delims)