CC: Functional dependencies question

Hello! Andrew J Bromage wrote:
class Foo a b | a -> b where foo :: a -> b
bar :: (Foo Char t) => t bar = foo 'a'
All well and good so far. Let's add an instance of Foo...
instance Foo Char Bool where foo c = isAlpha c
Now neither GHC nor Hugs will allow this to compile, as the declared type of bar is "too general".
The type of bar is indeed too general. It should be bar:: forall t. (Foo Char t | Char -> t) => t or bar:: exists t. (Foo Char t) => t because the functional dependency implies that there can be only one such type that relates to Char. Yet such types are not expressible. Perhaps because of that, GHC and Hugs delay reporting an error. For example, if we omit the instance declaration, both GHC and Hugs seem happy. But they only seem. In Hugs, if we try to actually evaluate 'bar', we get Main> bar ERROR - Unresolved overloading *** Type : Foo Char a => a *** Expression : bar Indeed, an instance declaration is required. Incidentally, GHC can report the error even before running the code: if we just want to see the type of bar: *Main> :t bar No instance for (Foo Char t) arising from use of `bar' at <No locn> If we add an instance of Foo, such as "instance Foo Char Bool", then the signature of bar is clearly too polymorphic: there can be only one type t (namely, Bool) for which the constraint Foo Char t is true. Incidentally, local type variable again seem to help -- they can help express types that are normally inexpressible. If we define bar as bar :: (Foo Char t) => t bar ::tbar = (foo::(Char->tbar)) 'a' we get an error: /tmp/f.hs:10: Inferred type is less polymorphic than expected Quantified type variable `t' escapes It is mentioned in the environment: tbar = t is bound by the pattern type signature at /tmp/f.hs:1 When trying to generalize the type inferred for `bar' Signature type: forall t. (Foo Char t) => t Type to generalise: t When checking the type signature for `bar' When generalising the type(s) for `bar' which alerts us that the given type of bar is indeed too general. Now, we get the error right away. If we drop the explicit type declaration, bar ::tbar = (foo::(Char->tbar)) 'a' we get another error, /tmp/f.hs:12: No instance for (Foo Char tbar) arising from use of `foo' at /tmp/f.hs:12 When checking the type signature of the expression: foo :: Char -> tbar In the definition of `bar': (foo :: Char -> tbar) 'a' The compiler demands to see an instance of Foo Char t. If we add the instance now, the compiler is happy. bar ::tbar = (foo::(Char->tbar)) 'a' instance Foo Char Bool where foo c = c == 'a' *Main> bar True and the code even runs.

G'day all. On Mon, May 12, 2003 at 12:35:39PM -0700, oleg@pobox.com wrote:
bar ::tbar = (foo::(Char->tbar)) 'a'
instance Foo Char Bool where foo c = c == 'a' *Main> bar True
and the code even runs.
That's a very ingenious solution, but unfortunately it doesn't solve the "larger" problem. The full ugly details of what I'm trying to do is that I'm trying to support unit-safe physical computations. For that, we need a way to encode phyics units (e.g. mass, force, energy etc) in Haskell's type system and then use phantom types to guarantee correctness. We know how to encode natural numbers: data Peano0 = Peano0 data PeanoSucc n = PeanoSucc with operations such as: class PeanoAdd l r n | l r -> n instance PeanoAdd Peano0 r r instance (PeanoAdd l r n) => PeanoAdd (PeanoSucc l) r (PeanoSucc n) That's straightforward. However, we actually need integers (hereafter called "whole numbers" so as not to confuse with Haskell Integers), not just natural numbers. We can do this using a pair of natural numbers (m,n) which corresponds to the integer m-n: data Whole m n = Whole Each Whole number has a unique representation where at least one of m or n is zero: class WholeUniqueRep m n | m -> n instance WholeUniqueRep (Whole Peano0 Peano0) (Whole Peano0 Peano0) instance WholeUniqueRep (Whole (PeanoSucc m) Peano0) (Whole (PeanoSucc m) Peano0) instance WholeUniqueRep (Whole Peano0 (PeanoSucc n)) (Whole Peano0 (PeanoSucc n)) instance (WholeUniqueRep (Whole m n) uniq) => WholeUniqueRep (Whole (PeanoSucc m) (PeanoSucc n)) uniq Some sample whole numbers in unique form include: type WholeN1 = Whole Peano0 Peano1 type Whole0 = Whole Peano0 Peano0 type Whole3 = Whole Peano3 Peano0 where Peano1 = Succ Peano0 etc. We can then do operations on Whole numbers such as addition: class WholeAdd l r n | l r -> n instance (PeanoAdd m1 m2 m3, PeanoAdd n1 n2 n3, WholeUniqueRep (Whole m3 n3) w) => WholeAdd (Whole m1 n1) (Whole m2 n2) w A physical unit is some product of integral powers of some set of basis units, such as a length unit and a mass unit. For example: newtype PhysicalUnit length mass time = PhysicalUnit Double Sample units include: -- basis units type Length -- e.g. metre = PhysicalUnit Whole1 Whole0 Whole0 type Mass -- e.g. kilogram = PhysicalUnit Whole0 Whole1 Whole0 type Time -- e.g. second = PhysicalUnit Whole0 Whole0 Whole1 -- derived units type Acceleration -- e.g. m/s^2 = PhysicalUnit Whole1 Whole0 WholeN2 type Force -- e.g. Newton = PhysicalUnit Whole1 Whole1 WholeN2 type Energy -- e.g. Joule = PhysicalUnit Whole2 Whole1 WholeN2 Addition and subtraction can only be done on matching units: class Add l r n | l r -> n where add :: l -> r -> n instance Add (PhysicalUnit a1 b1 c1) (PhysicalUnit a1 b1 c1) (PhysicalUnit a1 b1 c1) where add (PhysicalUnit m) (PhysicalUnit n) = PhysicalUnit (m+n) Multiplication is done by adding powers: class Mult l r n | l r -> n where mult :: l -> r -> n instance (WholeAdd a1 a2 a3, WholeAdd b1 b2 b3, WholeAdd c1 c2 c3) => Mult (PhysicalUnit a1 b1 c1) (PhysicalUnit a2 b2 c2) (PhysicalUnit a3 b3 c3) where mult (PhysicalUnit m) (PhysicalUnit n) = PhysicalUnit (m*n) We can now write functions such as: newtonsSecondLaw :: Mass -> Acceleration -> Force newtonsSecondLaw m a = m `mult` a OK, that's the part that works. Now here's the problem... I want people to be able to specify PhysicalUnit types without worrying about how they're implemented at the _type_ level. Suppose, for example, you want to declare Planck's constant. It's units are Joule seconds, i.e. the Energy unit multiplied by the Time unit. I want people to be able to write something like: hbar :: (Mult Energy Time t) => t hbar = PhysicalUnit 6.62606876e-34 rather than give the full type of t. I can't give a type synonym for it, either, because I don't know the full set of physical units that people will want to work with. Besides, I want to be able to extend or change the PhysicalUnit type without requiring people to rewrite their code. Today, we only need length, mass and time. Tomorrow we might need the full SI basis set: newtype PhysicalUnit length mass time current temperature lightIntensity amount = PhysicalUnit Double Cheers, Andrew Bromage
participants (2)
-
Andrew J Bromage
-
oleg@pobox.com