bracketOnError, while, forever

Thomas Jäger thjaeger at gmail.com
Tue Feb 8 07:33:13 EST 2005


Hi,

speaking of additions to the libraries, i'd like to mention a few
functions from http://haskell.org/hawiki/LicensedPreludeExts that I
think deserve to be in the libs.

First of all
| -- Cale Gibbard
| comparing :: (Ord a) => (b -> a) -> b -> b -> Ordering
| comparing p x y = compare (p x) (p y)
fits nicely with the ...By functions from Data.List.

Since there's no easy way to catch failure of read operations,
| readM :: (Monad m, Read a) => String -> m a
| readM s       =  case [x | (x,t) <- reads s, ("","") <- lex t] of
|                       [x] -> return x
|                       []  -> fail "Prelude.readM: no parse"
|                       _   -> fail "Prelude.readM: ambiguous parse"
this function seems to be quite natural.

Finally, 
| -- Koen Claessen
| selections :: [a] -> [(a,[a])]
| selections []     = []
| selections (x:xs) = (x,xs) : [ (y,x:ys) | (y,ys) <- selections xs ]
| 
| permutations    :: [a] -> [[a]]
| permutations [] = [[]]
| permutations xs =
|     [ y : zs
|     | (y,ys) <- selections xs
|     , zs     <- permutations ys
|     ]
are quite useful (maybe they should be named select and permute since
most Data.List names seem to be imperatives).

>   forever :: (Monad m) => m a -> m ()
>   forever f = while (return True) f
a more logical name would be repeatM_

Btw, is there some rule which prelude functions should have monadic
equivalents in Control.Monad? There is mapM, filterM, zipWithM, foldM
and replicateM, but no foldrM, unfoldM, repeatM, allM, anyM (the last
three are easily defined using sequence, but so are mapM and
replicateM).

What do you think?

Thomas


More information about the Libraries mailing list