> -- | Common helper functions
> module Frame.Utilities ( 
>   -- * String helpers
>   explode,
>   explodeURL,
>   explodeFieldName,
>   implode,
>   implodeUrl,
>   humanise,
>   humaniseCamel,
>   humaniseUrl,
>   humanisePath,
>   -- * Maybe helpers
>   maybeMaybe,
>   headMaybe,
>   pop,
>   appMaybe,
>   allNothing,
>   -- * Failure helpers
>   (?),
>   (??),
>   module Data.Map,
>   module Data.Maybe
> ) where
> import Data.Map (Map, empty, fromList)
> import Data.Maybe
> import Data.Char
> -- | Similar to 'Prelude.words' except splitting against arbitrary 'Char'
> explode :: Char     -- ^ The character to split against
>         -> String   -- ^ The string to split
>         -> [String] -- ^ The resultant list
> explode c s = case dropWhile (==c) s of
>                    "" -> []
>                    s' -> w : explode c s''
>                        where (w, s'') = break (==c) s'
> -- | Explode for URLs
> explodeURL :: String -> [String]
> explodeURL = explode '/'
> -- | Explode for field names
> explodeFieldName :: String         -- ^ The 'FieldName'
>                 -> (Int, [String]) -- ^ (Length of the list, Resultant list)
> explodeFieldName fn = let fns = explode '.' fn in
>                           (length fns, fns)
> -- | Opposite of explode
> implode :: Char -> [String] -> String
> implode _ [] =  ""
> implode _ [w] = w
> implode c (w:ws) = w ++ c : implode c ws
> -- | Implode for URLs
> implodeUrl :: [String] -> String
> implodeUrl ws = implode '/' ws
> -- | 'Maybe' 'Maybe' == 'Maybe' 
> maybeMaybe :: Maybe (Maybe a) -> Maybe a
> maybeMaybe (Just ma) = ma
> maybeMaybe Nothing = Nothing
> -- | Safe head
> headMaybe :: [a] -> Maybe a
> headMaybe [] = Nothing
> headMaybe (a:_) = Just a 
> -- | Function application within 'Maybe'
> appMaybe :: (a -> b) -> Maybe a -> Maybe b
> appMaybe f Nothing  = Nothing
> appMaybe f (Just a) = Just $ f a
> -- | Monadic safe head
> pop :: (Monad m) => m [a] -> m (Maybe a)
> pop s = do s' <- s
>            return $ headMaybe s'
> -- | List of 'Nothing' == True
> allNothing :: [Maybe a] -> Bool
> allNothing [] = True
> allNothing (Nothing:ns) = allNothing ns
> allNothing (Just _:ns) = False
> -- | Cast maybe to string (with 'Nothing' == '''')
> showMaybeString :: Maybe String -> String
> showMaybeString (Just s) = s
> showMaybeString Nothing  = ""
> -- | ''camelCase'' to ''Camel Case''
> humaniseCamel :: String -> String
> humaniseCamel []     = "" 
> humaniseCamel (s:ss) = (toUpper s):humaniseCamel' ss
> humaniseCamel' :: String -> String
> humaniseCamel' []     = "" 
> humaniseCamel' (s:ss) = if isUpper s then ' ':s:humaniseCamel' ss else s:humaniseCamel' ss
> -- | ''hi there'' to ''Hi There''
> humanise :: String -> String
> humanise = humaniseGen ' ' ' '
> humaniseGen :: Char -> Char -> String -> String
> humaniseGen e i = implode i . humaniseGen' . explode e
> humaniseGen' :: [String] -> [String]
> humaniseGen' []          = []
> humaniseGen' ((h:ts):ws) = ((toUpper h):ts):humaniseGen' ws
> -- | ''/a/url'' to ''A Url''
> humaniseUrl :: String -> String -> String
> humaniseUrl "" d  = d
> humaniseUrl "/" d = d
> humaniseUrl u _   = humaniseGen '/' '/' $ humaniseGen '_' ' ' u
> -- | \[''a'', ''url''\] to ''A Url''
> humanisePath :: [String] -> String -> String
> humanisePath u d   = humaniseUrl (implodeUrl u) d
? offers a way to catch validation failures
> infix 3 ?
> -- | Captures failure
> (?) :: Bool         -- ^ Test
>     -> String       -- ^ String on failure
>     -> Maybe String -- ^ Nothing if success, (Just ''message'') on success
> False ? s = Just s
> True ? _ = Nothing
> infix 3 ??
> -- | Same as (?), always returns a string ('''' on success)
> (??) :: Bool -> String -> String
> b ?? s = showMaybeString $ b ? s