bracketOnError, while, forever

Simon Marlow simonmar at microsoft.com
Wed Feb 9 06:50:48 EST 2005


On 08 February 2005 12:33, Thomas Jäger wrote:

> 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.

 sortBy (comparing fst)

is just too cute not to have.  Any objections?

> 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.

Also subsumes System.IO.readIO.  Looks useful to me.

> 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).

Both look reasonable.  Not all the names in Data.List are imperative (eg. inits, tails, lines, words).  I think the names are fine.

Cheers,
	Simon


More information about the Libraries mailing list