Re: [Haskell-cafe] Proposal: Generic conditions for 'if' and 'case'

2013-09-02 Thread Nicolas Trangez
On Sun, 2013-09-01 at 15:51 -0700, Wvv wrote: I think it is an old idea, but nevertheless. Now we have next functions: if (a :: Bool) then x else y case b of a1 :: Bool - x1 a2 :: Bool - x2 ... Let we have generic conditions for 'if' and 'case': class Boolean a where toBool

Re: [Haskell-cafe] Proposal: Generic conditions for 'if' and 'case'

2013-09-02 Thread Wvv
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

[Haskell-cafe] Proposal: Generic conditions for 'if' and 'case'

2013-09-01 Thread Wvv
I think it is an old idea, but nevertheless. Now we have next functions: if (a :: Bool) then x else y case b of a1 :: Bool - x1 a2 :: Bool - x2 ... Let we have generic conditions for 'if' and 'case': class Boolean a where toBool :: a - Bool instance Boolean Bool where toBool = id

Re: [Haskell-cafe] Proposal: Generic conditions for 'if' and 'case'

2013-09-01 Thread Nicolas Trangez
I didn't test it, but you might want to look into the 'rebindable syntax' extension and its 'ifThenElse' feature. Nicolas On Sep 2, 2013 12:51 AM, Wvv vite...@rambler.ru wrote: I think it is an old idea, but nevertheless. Now we have next functions: if (a :: Bool) then x else y case b of