Thanks! It is a good toy for testing!
Nicolas Trangez wrote > Here's an example implementing your proposal: > > {-# LANGUAGE RebindableSyntax #-} > > import Prelude > > class Boolean a where > toBool :: a -> Bool > > instance Boolean Bool where > toBool = id > > instance Boolean [a] where > toBool = not . null > > instance Boolean (Maybe a) where > toBool = maybe False (const True) > > instance Boolean Int where > toBool = (/= 0) > > ifThenElse :: Boolean a => a -> b -> b -> b > ifThenElse i t e = case toBool i of > True -> t > False -> e > > main :: IO () > main = do > test False > test ([] :: [Int]) > test [1] > test (Nothing :: Maybe Int) > test (Just 1 :: Maybe Int) > test (0 :: Int) > test (1 :: Int) > {- test 'c' fails to type-check: no instance Boolean Char defined! > -} > where > test v = putStrLn $ show v ++ " is " ++ (if v then "true" else > "false") > > which outputs > > False is false > [] is false > [1] is true > Nothing is false > Just 1 is true > 0 is false > 1 is true > > Using RebindableSyntax, 'if I then T else E' is rewritten into > 'ifThenElse I T E' by the compiler, for whatever 'ifThenElse' is in > scope. > > Nicolas > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@ > http://www.haskell.org/mailman/listinfo/haskell-cafe -- View this message in context: http://haskell.1045720.n5.nabble.com/Proposal-Generic-conditions-for-if-and-case-tp5735366p5735424.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe