Re: [Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-23 Thread John Meacham
On Thu, Nov 16, 2006 at 10:44:59PM +0200, isto wrote:
> I'll guess the reason it didn't compile was different
> types at case branches (am I wrong?) Anyhow, do you know that 
> is it possible to choose the return type somehow in the spirit 
> above?  


GADTs let you do this. And they even omit the run time type check. though, the 
type class solution is the correct way to
do this sort of thing.

data Value a where
   IntLike :: Int -> Value Int
   CharLike :: Char -> Value Char

f :: Value a -> a
f x = case x of
   IntLike x -> x + 1
   CharLike x -> x:" plus one"


there is also Data.Dynamic and existential types which are related to
the task. 

John
-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-23 Thread isto
Hi & thanks!


to, 2006-11-16 kello 14:02 -0800, Greg Buchholz kirjoitti:
> ] I'll guess the reason it didn't compile was different
> ] types at case branches (am I wrong?) 
> 
> Correct.
> 
> ] Anyhow, do you know that is it possible to choose the return type
> ] somehow in the spirit above?  
> 
> Maybe you want something like...

This time, however, I'm not sure after seeing oleg's email:
  http://www.haskell.org/pipermail/haskell/2006-November/018736.html

I'll have yet to re-read it carefully to be sure... :)

br, Isto



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-16 Thread Greg Buchholz
isto wrote:
] > isto wrote:
] > ]   let t = show (typeOf a)
] > ]   in case t of
] > ]   "Double"  -> roundDDec d a
] > ]   "Complex Double" -> roundCDec d a
] 
] I'll guess the reason it didn't compile was different
] types at case branches (am I wrong?) 

Correct.

] Anyhow, do you know that is it possible to choose the return type
] somehow in the spirit above?  

Maybe you want something like...

> roundDec d (Left a)  = Left  (roundDDec d a)
> roundDec d (Right a) = Right (roundCDec d a)
> 
> roundCDec :: (RealFloat a) => Int -> Complex a -> Complex a
> roundCDec d (c :+ b) = (roundDDec d c :+ roundDDec d b)
> 
> roundDDec :: (RealFloat a) => Int -> a -> a
> roundDDec d a = a  -- or somegthing

Greg Buchholz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-16 Thread isto
ke, 2006-11-15 kello 13:31 -0800, Greg Buchholz kirjoitti:
> isto wrote:
> ] let t = show (typeOf a)
> ] in case t of
> ] "Double"  -> roundDDec d a
> ] "Complex Double" -> roundCDec d a

> Maybe you want type classes instead?

 yes, I was blind... Thanks! 

I'll guess the reason it didn't compile was different
types at case branches (am I wrong?) Anyhow, do you know that 
is it possible to choose the return type somehow in the spirit 
above?  

br, Isto


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-15 Thread Greg Buchholz
isto wrote:
] I've been trying to compile the following function
] (rounding to a desired degree):
] 
] roundDec :: (Num a, Typeable a) => Int -> a -> a
] roundDec d a = 
]   let t = show (typeOf a)
]   in case t of
]   "Double"  -> roundDDec d a
]   "Complex Double" -> roundCDec d a
]   otherwise -> a  -- or something
] 
] The two other functions are 
] 
] roundCDec :: (RealFloat a) => Int -> Complex a -> Complex a
] roundCDec d (c :+ b) = (roundDDec d c :+ roundDDec d b)
] and
] roundDDec :: (RealFloat a) => Int -> a -> a
] roundDDec d a = a  -- or somegthing

Maybe you want type classes instead?

> import Complex
> 
> class Round a where
> roundD :: Int -> a -> a
> 
> instance Round Double where
> roundD d a = a
> 
> instance (Round a, RealFloat a) => Round (Complex a) where
> roundD d (c :+ b) = (roundD d c :+ roundD d b)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-15 Thread isto
Hi,

I've been trying to compile the following function
(rounding to a desired degree):

roundDec :: (Num a, Typeable a) => Int -> a -> a
roundDec d a = 
let t = show (typeOf a)
in case t of
"Double"  -> roundDDec d a
"Complex Double" -> roundCDec d a
otherwise -> a  -- or something

The two other functions are 

roundCDec :: (RealFloat a) => Int -> Complex a -> Complex a
roundCDec d (c :+ b) = (roundDDec d c :+ roundDDec d b)
and
roundDDec :: (RealFloat a) => Int -> a -> a
roundDDec d a = a  -- or somegthing

Compiler gives the following error message:
Couldn't match expected type `Complex a'
   against inferred type `a1' (a rigid variable)
  `a1' is bound by the type signature for `roundDec' at FFT.hs:57:17
In the second argument of `roundCDec', namely `a'
In the expression: roundCDec d a
In a case alternative: "Complex Double" -> roundCDec d a

If in the roundDDec a's are replaced with Double, there will
be similar error message from the "Double"-line.  The functionality
can be written differently, but I wanted to try write rounding
having in a signature at least "(Num a) => Int -> a -> a".

Again, any help would be appreciated a lot! Thanks in advance!

br, Isto


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe