On Wednesday, May 21, 2014, Dimitri DeFigueiredo <
defigueiredo@ucdavis.edu>
wrote:
Hi All,
I'm trying to write a simplified dimensional library where
where quantities in meters, seconds and meters/second can all
co-exist adjusting their respective units when multiplied
and/or divided.
Also, meter+meter is allowed, but meter+second should cause
the type checker to complain.
This is a bit like a *much* simplified version of the Units
library. However, I am having trouble understanding why my
instance declaration below appears to be under specified.
Here's the code:
------------
module Dimensional where
import qualified Prelude
-- A Group allows you to add and subtract (but not multiply or
divide)
class Group a where
(+) :: a -> a -> a
(-) :: a -> a -> a
x - y = x + negate y
negate :: a -> a
negate x = fromInteger 0 - x
fromInteger :: Prelude.Integer -> a
class Unit a where
(*) :: (Unit a, Unit b, Unit c) => a -> b -> c
(/) :: (Unit a, Unit b, Unit c) => a -> b -> c
toDouble :: a -> Prelude.Double
instance Unit Prelude.Double where
(*) x y = (Prelude.*) x (toDouble y) -- <-----
Error here
(/) x y = (Prelude./) x (toDouble y)
toDouble x = x
------------
GHC complains as follows:
Could not deduce (c ~ Prelude.Double)
from the context (Unit Prelude.Double, Unit b, Unit c)
bound by the type signature for
* :: (Unit Prelude.Double, Unit b, Unit c)
=>
Prelude.Double -> b -> c
at /code/haskell/dimensional.hs:25:5-43
`c' is a rigid type variable bound by
the type signature for
* :: (Unit Prelude.Double, Unit b, Unit c) =>
Prelude.Double -> b -> c
at /code/haskell/dimensional.hs:25:5
In the first argument of `(Prelude.*)', namely `x'
In the expression: (Prelude.*) x (toDouble y)
In an equation for `*': * x y = (Prelude.*) x (toDouble y)
Any pointers would be much appreciated!
Thanks,
Dimitri
_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners