Haskell Quiz/Text Munger/Solution Dolio

From HaskellWiki
< Haskell Quiz‎ | Text Munger
Revision as of 10:57, 13 January 2007 by Quale (talk | contribs) (sharpen cat)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search


This solution makes use of the random monad elsewhere on the wiki.

module Main where
import Control.Monad
import Data.Char
import Data.List
import System.Random
import MonadRandom

permute [] = return []
permute l  = do r <- getRandomR (0, n)
                let (a, e:b) = splitAt r l
                l' <- permute (a ++ b)
                return $ e : l'
 where n = length l - 1

munge l
    | isAlpha h && length l > 2 = ((h:) . (++[f])) `liftM` permute m
    | otherwise                 = return l
 where h = head l
       f = last l
       m = tail (init l)

main = do g <- getStdGen
          interact $ flip evalRand g . liftM join . mapM munge . groupBy f
 where f a b = isAlpha a == isAlpha b