RE: bracketOnError, while, forever

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?
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"
Since there's no easy way to catch failure of read operations, 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

On Wed, Feb 09, 2005 at 11:50:48AM -0000, Simon Marlow wrote:
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?
only that it's not clear where to put it. This is useful when the function is expensive: -- sortImage f = sortBy (comparing f) sortImage :: Ord b => (a -> b) -> [a] -> [a] sortImage f xs = map snd $ sortBy (comparing fst) [(f x, x) | x <- xs]

"Simon Marlow"
comparing :: (Ord a) => (b -> a) -> b -> b -> Ordering comparing p x y = compare (p x) (p y)
sortBy (comparing fst)
is just too cute not to have. Any objections?
Looks good to me.
readM :: (Monad m, Read a) => String -> m a
Also subsumes System.IO.readIO. Looks useful to me.
Yup.
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 ]
Here's another one. I'm not sure what to call it, since 'permutation' means something subtly different. -- Given a list of alphabets, return all possible strings with one -- symbol chosen from each alphabet respectively. permute :: [[a]] -> [[a]] permute [] = [[]] permute (xs:xss) = [ f:fs | f <- xs, fs <- permute xss ] Regards, Malcolm

On Wed, Feb 09, 2005 at 01:33:37PM +0000, Malcolm Wallace wrote:
Here's another one. I'm not sure what to call it, since 'permutation' means something subtly different.
-- Given a list of alphabets, return all possible strings with one -- symbol chosen from each alphabet respectively. permute :: [[a]] -> [[a]] permute [] = [[]] permute (xs:xss) = [ f:fs | f <- xs, fs <- permute xss ]
sequence?

At 13:33 09/02/05 +0000, Malcolm Wallace wrote:
Here's another one. I'm not sure what to call it, since 'permutation' means something subtly different.
-- Given a list of alphabets, return all possible strings with one -- symbol chosen from each alphabet respectively. permute :: [[a]] -> [[a]] permute [] = [[]] permute (xs:xss) = [ f:fs | f <- xs, fs <- permute xss ]
Doesn't 'sequence' do that? #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

"Simon Marlow"
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?
No objection. My version of this is defined in terms of another function which I use directly almost as often, onField :: (fv -> fv -> r) -> (s -> fv) -> s -> s -> r onField op field r1 r2 = field r1 `op` field r2 , which I consider a good candidate for inclusion in a library. (I expect there's a better name, though.) mike

On Wed, Feb 09, 2005 at 11:50:48AM -0000, Simon Marlow wrote:
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?
How about a more general function: composeFGxGy :: (b -> b -> c) -> (a -> b) -> a -> a -> c composeFGxGy f g x y = f (g x) (g y) Best regards Tomasz -- Szukamy programisty C++ i Haskell'a: http://tinyurl.com/5mw4e

On Wed, Feb 09, 2005 at 08:47:43PM +0100, Tomasz Zielonka wrote:
On Wed, Feb 09, 2005 at 11:50:48AM -0000, Simon Marlow wrote:
sortBy (comparing fst)
is just too cute not to have. Any objections?
How about a more general function:
composeFGxGy :: (b -> b -> c) -> (a -> b) -> a -> a -> c composeFGxGy f g x y = f (g x) (g y)
I agree, though I don't like its name ;) Mike just called it `onField', and I've seen it as `on' before. sortBy (compare `on` fst) groupBy ((==) `on` toLower) zipWith ((*) `on` fst) Having both `comparing' and `equaling' seems overkill, and just `on' is just as usable IMO. (No, I never used that last one.) Greetings, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

Here's another common function I use all the time, which appears to be missing from Data.List: elemBy :: (a -> a -> Bool) -> a -> [a] -> Bool elemBy eq _ [] = False elemBy eq x (y:ys) = x `eq` y || elemBy eq x ys Regards, Malcolm

On Thu, Feb 10, 2005 at 05:56:09PM +0000, Malcolm Wallace wrote:
Here's another common function I use all the time, which appears to be missing from Data.List:
elemBy :: (a -> a -> Bool) -> a -> [a] -> Bool elemBy eq _ [] = False elemBy eq x (y:ys) = x `eq` y || elemBy eq x ys
How about any (x `eq`) ys ? Best regards Tomasz -- Szukamy programisty C++ i Haskell'a: http://tinyurl.com/5mw4e

On Thu, Feb 10, 2005 at 05:56:09PM +0000, Malcolm Wallace wrote:
Here's another common function I use all the time, which appears to be missing from Data.List:
elemBy :: (a -> a -> Bool) -> a -> [a] -> Bool elemBy eq _ [] = False elemBy eq x (y:ys) = x `eq` y || elemBy eq x ys
Section 17.6 of the Report: "The library does not provide elemBy, because any (eq x) does the same job as elemBy eq x would."
participants (7)
-
Graham Klyne
-
Malcolm Wallace
-
Mike Gunter
-
Remi Turk
-
Ross Paterson
-
Simon Marlow
-
Tomasz Zielonka