How do I simulate dependent types using phantom types?

Hi, I am trying to implement quadratic fields Q(sqrt d). These are numbers of the form a + b sqrt d, where a and b are rationals, and d is an integer. In an earlier attempt, I tried data QF = QF Integer Rational Rational (see http://www.polyomino.f2s.com/david/haskell/hs/QuadraticField.hs.txt) The problem with this approach is that it's not really type-safe: I can attempt to add a + b sqrt 2 to c + d sqrt 3, whereas this should be a type error because 2 /= 3. So I thought I'd have a go at doing it with phantom types. In effect I'd be using phantom types to simulate dependent types. Here's the code: {-# OPTIONS_GHC -fglasgow-exts #-} import Data.Ratio class IntegerType a where value :: Integer data Two instance IntegerType Two where value = 2 data Three instance IntegerType Three where value = 3 data QF d = QF Rational Rational deriving (Eq) instance IntegerType d => Show (QF d) where show (QF a b) = show a ++ " + " ++ show b ++ " sqrt " ++ show value instance IntegerType d => Num (QF d) where QF a b + QF a' b' = QF (a+a') (b+b') negate (QF a b) = QF (-a) (-b) QF a b * QF c d = QF (a*c + b*d*value) (a*d + b*c) fromInteger n = QF (fromInteger n) 0 The problem is, this doesn't work. GHC complains: The class method `value' mentions none of the type variables of the class IntegerType a When checking the class method: value :: Integer In the class declaration for `IntegerType' Is what I'm trying to do reasonable? If no, what should I be doing instead? If yes, why doesn't GHC like it? Thanks, David

Use
value :: a -> Integer
On 8/18/07, DavidA
Hi,
I am trying to implement quadratic fields Q(sqrt d). These are numbers of the form a + b sqrt d, where a and b are rationals, and d is an integer.
In an earlier attempt, I tried data QF = QF Integer Rational Rational (see http://www.polyomino.f2s.com/david/haskell/hs/QuadraticField.hs.txt) The problem with this approach is that it's not really type-safe: I can attempt to add a + b sqrt 2 to c + d sqrt 3, whereas this should be a type error because 2 /= 3.
So I thought I'd have a go at doing it with phantom types. In effect I'd be using phantom types to simulate dependent types. Here's the code:
{-# OPTIONS_GHC -fglasgow-exts #-}
import Data.Ratio
class IntegerType a where value :: Integer
data Two instance IntegerType Two where value = 2
data Three instance IntegerType Three where value = 3
data QF d = QF Rational Rational deriving (Eq)
instance IntegerType d => Show (QF d) where show (QF a b) = show a ++ " + " ++ show b ++ " sqrt " ++ show value
instance IntegerType d => Num (QF d) where QF a b + QF a' b' = QF (a+a') (b+b') negate (QF a b) = QF (-a) (-b) QF a b * QF c d = QF (a*c + b*d*value) (a*d + b*c) fromInteger n = QF (fromInteger n) 0
The problem is, this doesn't work. GHC complains: The class method `value' mentions none of the type variables of the class IntegerType a When checking the class method: value :: Integer In the class declaration for `IntegerType'
Is what I'm trying to do reasonable? If no, what should I be doing instead? If yes, why doesn't GHC like it?
Thanks, David
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, 2007-08-18 at 19:26 +0000, DavidA wrote:
Hi,
I am trying to implement quadratic fields Q(sqrt d). These are numbers of the form a + b sqrt d, where a and b are rationals, and d is an integer.
In an earlier attempt, I tried data QF = QF Integer Rational Rational (see http://www.polyomino.f2s.com/david/haskell/hs/QuadraticField.hs.txt) The problem with this approach is that it's not really type-safe: I can attempt to add a + b sqrt 2 to c + d sqrt 3, whereas this should be a type error because 2 /= 3.
So I thought I'd have a go at doing it with phantom types. In effect I'd be using phantom types to simulate dependent types. Here's the code:
{-# OPTIONS_GHC -fglasgow-exts #-}
import Data.Ratio
class IntegerType a where value :: Integer
data Two instance IntegerType Two where value = 2
data Three instance IntegerType Three where value = 3
data QF d = QF Rational Rational deriving (Eq)
instance IntegerType d => Show (QF d) where show (QF a b) = show a ++ " + " ++ show b ++ " sqrt " ++ show value
instance IntegerType d => Num (QF d) where QF a b + QF a' b' = QF (a+a') (b+b') negate (QF a b) = QF (-a) (-b) QF a b * QF c d = QF (a*c + b*d*value) (a*d + b*c) fromInteger n = QF (fromInteger n) 0
The problem is, this doesn't work. GHC complains: The class method `value' mentions none of the type variables of the class IntegerType a When checking the class method: value :: Integer In the class declaration for `IntegerType'
Is what I'm trying to do reasonable? If no, what should I be doing instead? If yes, why doesn't GHC like it?
When you write 'value' how is GHC supposed to know what instance you want? The typical trick is to add what could be called a phantom argument to propagate the type. I.e. class IntegerType a where value :: a -> Integer instance IntegerType Two where value _ = 2 value (undefined :: Two) == 2

DavidA wrote:
Hi,
I am trying to implement quadratic fields Q(sqrt d). These are numbers of the form a + b sqrt d, where a and b are rationals, and d is an integer.
...
class IntegerType a where value :: Integer
The problem is, this doesn't work. GHC complains: The class method `value' mentions none of the type variables of the class IntegerType a When checking the class method: value :: Integer In the class declaration for `IntegerType'
Is what I'm trying to do reasonable? If no, what should I be doing instead? If yes, why doesn't GHC like it?
You are on the right track. The problem with the class method is that it doesn't use type 'a' anywhere, consider
f :: Integer f = value What class instance should be used here?
The solution is to use a dummy parameter:
class IntegerType a where value :: a -> Integer And call it like: f = value (undefined :: Two)
So for instance:
instance IntegerType d => Show (QF d) where show (QF a b) = show a ++ " + " ++ show b ++ " sqrt " ++ show (value (undefined::d))
The problem is that this doesn't work, because d is not in scope, you need the scoped type variables extension:
valueOfQF :: forall a. IntegerType a => QF a -> Integer valueOfQF qf = value (undefined :: a)
or maybe better, change the class:
class IntegerType a where value :: QF a -> Integer
Now you can simply use
instance IntegerType d => Show (QF d) where show qf@(QF a b) = show a ++ " + " ++ show b ++ " sqrt " ++ show (value qf)
Twan

Twan van Laarhoven
The solution is to use a dummy parameter:
class IntegerType a where value :: a -> Integer And call it like: f = value (undefined :: Two)
So for instance:
instance IntegerType d => Show (QF d) where show (QF a b) = show a ++ " + " ++ show b ++ " sqrt " ++ show (value (undefined::d))
Thanks to all respondents for this suggestion. That works great.
The problem is that this doesn't work, because d is not in scope, you need the scoped type variables extension:
valueOfQF :: forall a. IntegerType a => QF a -> Integer valueOfQF qf = value (undefined :: a)
Well actually, your first attempt *did* work for me (using GHC 6.6.1). Is this not behaviour that I can rely on?

DavidA wrote:
Twan van Laarhoven
writes: The solution is to use a dummy parameter:
class IntegerType a where value :: a -> Integer
Thanks to all respondents for this suggestion. That works great.
I prefer a slightly elaborate way,
newtype Mark n t = Mark t
-- provide conversion from and to dummy functions because they are -- much more convenient to use. toDummy :: Mark n t -> n -> t toDummy (Mark x) _ = x
fromDummy :: (n -> t) -> Mark n t fromDummy f = Mark (f undefined)
class Natural a where value' :: Mark a Integer
value :: Natural a => a -> Integer value = toDummy value'
The advantage of this approach is that the 'Natural' class dictionary contains a constant Integer value, not some function that the compiler doesn't know anything about. This makes no difference for simple uses, but once you define type level natural numbers, like
data Zero = Zero newtype D0 a = D0 a newtype D1 a = D1 a
with instances,
instance Natural Zero where value' = Mark 0
instance Natural a => Natural (D0 a) where value' = fromDummy (\(D0 d) -> value d * 2)
instance Natural a => Natural (D1 a) where value' = fromDummy (\(D1 d) -> value d * 2 + 1)
you get an actual speedup at runtime, because the value represented by the type is passed directly in the class dictionary and doesn't have to be recomputed each time "value" is called. (Note: it *is* possible to share intermediate results even with dummy functions, but I got a significant speed boost in my modular arithmetic code with this trick anyway.) This also opens up a *naughty* way to construct such phantom types in GHC. When I say "naughty" I mean it - use this code at your own risk.
-- Or is this reify? I'm confused about the convention here. reflect :: Integer -> (forall n . Nat n => Mark n a) -> a reflect = flip unsafeCoerce
which can be used like this: *Test> reflect 42 value' 42 *Test> reflect 7 (fromDummy (\d -> value d * 6)) 42 It is an interesting exercise to implement reflect :: Integer -> (forall n . Nat n => Mark n a) -> a using Zero, D0 and D1 :) Bertram
participants (5)
-
Bertram Felgenhauer
-
DavidA
-
Derek Elkins
-
Lennart Augustsson
-
Twan van Laarhoven