
I just (re)discovered that I can do things like data Foo x = Foo Int Int Now "Foo Int" and "Foo Double" are, as far as the type checker cares, two completely different types, even though in fact they are the same. This is actually Quite Useful, in the particular case I'm working on. Here's the thing though... How do I get it so that "Foo Int" and "Foo Double" produce slightly different strings when printed?

Hello Andrew, Wednesday, August 6, 2008, 10:09:43 PM, you wrote:
Here's the thing though... How do I get it so that "Foo Int" and "Foo Double" produce slightly different strings when printed?
instnace Show (Foo Int) ... instnace Show (Foo Double) ... -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Andrew,
Wednesday, August 6, 2008, 10:09:43 PM, you wrote:
Here's the thing though... How do I get it so that "Foo Int" and "Foo Double" produce slightly different strings when printed?
instnace Show (Foo Int) ... instnace Show (Foo Double) ...
...WHY did I not think of this myself? o_O

Hello Andrew, Monday, August 11, 2008, 8:32:46 PM, you wrote:
Here's the thing though... How do I get it so that "Foo Int" and "Foo Double" produce slightly different strings when printed? instnace Show (Foo Int) ... instnace Show (Foo Double) ...
...WHY did I not think of this myself? o_O
because it's impossible with OOP classes? :))) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Malcolm Wallace wrote:
Andrew Coppin
wrote: instnace Show (Foo Int) ... instnace Show (Foo Double) ...
...WHY did I not think of this myself? o_O
Because it is not Haskell'98? It requires {-# LANGUAGE OverlappingInstances #-}
No it doesn't? It requires the much more semantically simple -XFlexibleInstances, as far as I know. Overlapping would only be needed if there was also a polymorphic instance on Foo a? Jules

On Fri, 15 Aug 2008, Jules Bean wrote:
Malcolm Wallace wrote:
Andrew Coppin
wrote: instnace Show (Foo Int) ... instnace Show (Foo Double) ...
...WHY did I not think of this myself? o_O
Because it is not Haskell'98? It requires {-# LANGUAGE OverlappingInstances #-}
No it doesn't?
It requires the much more semantically simple -XFlexibleInstances, as far as I know.
Overlapping would only be needed if there was also a polymorphic instance on Foo a?
Btw. was anything bad about the suggested Haskell98 solution?

Henning Thielemann wrote:
instance on Foo a?
Btw. was anything bad about the suggested Haskell98 solution?
You called it 'non-hacky'; I would call it 'slightly hacky' since, IMO, it qualifies as a hack around a deficiency in the class system. However, I don't think there is anything wrong with it. After all it's the same trick the Prelude uses for instance Show [Char]. Jules

On Wed, 6 Aug 2008, Andrew Coppin wrote:
I just (re)discovered that I can do things like
data Foo x = Foo Int Int
Now "Foo Int" and "Foo Double" are, as far as the type checker cares, two completely different types, even though in fact they are the same. This is actually Quite Useful, in the particular case I'm working on.
Here's the thing though... How do I get it so that "Foo Int" and "Foo Double" produce slightly different strings when printed?
The non-hacky Haskell 98 solution is: class ShowPhantom a where showPhantom :: Foo a -> String You can call this from the 'show' implemention for 'Foo a'.

On Wed, Aug 6, 2008 at 11:09 AM, Andrew Coppin
I just (re)discovered that I can do things like
data Foo x = Foo Int Int
Now "Foo Int" and "Foo Double" are, as far as the type checker cares, two completely different types, even though in fact they are the same. This is actually Quite Useful, in the particular case I'm working on.
Phantom types are indeed useful for many things, but a bit of cautionary advice. If you start to depend on the phantoms for type safety AND you export your data constructors then you run a serious risk of being type unsafe. Bonus points if you can demonstrate an equivalent of unsafeCoerce# this way. Example: fooCast :: Foo Int -> Foo Double fooCast (Foo x) = Foo x On noes! We just cast that Foo Int to a Foo Double without changing it! It works because the value on the RHS is consider freshly constructed and other than sharing x it is unrelated to the one on the LHS. Note that by contrast this does not type check: foo :: Foo Int -> Foo Double foo f@(Foo x) = f Or, for that matter, any other variant where you don't use the constructor on the RHS. One way to get around this is to create your own constructor functions: mkFooInt :: Int -> Foo Int mkFooInt = Foo mkFooDouble :: Int -> Foo Double mkFooDouble = Foo Now export these instead of your data constructor. Similarly you'll probably want ones to take the place of pattern matching. The most obvious general purpose one being: unFoo :: Foo a -> Int unFoo (Foo a) = a But, if you're really relying on that phantom as a "witness", then you should probably define separate unFooInt :: Foo Int -> Int and unFooDouble : Foo Double -> Int. Here is the part where it gets really interesting. If you use GADTs, it rolls some of the above into one nice declaration: data Foo a where FooInt :: Int -> Foo Int FooDouble :: Int -> Foo Double I'm not sure if the GADT way can lead to an unsafeCoerce# equivalents or not. Maybe someone else can comment on that. Jason

Jason Dagit wrote:
On Wed, Aug 6, 2008 at 11:09 AM, Andrew Coppin
wrote: I just (re)discovered that I can do things like
data Foo x = Foo Int Int
Now "Foo Int" and "Foo Double" are, as far as the type checker cares, two completely different types, even though in fact they are the same. This is actually Quite Useful, in the particular case I'm working on.
Phantom types are indeed useful for many things, but a bit of cautionary advice. If you start to depend on the phantoms for type safety AND you export your data constructors then you run a serious risk of being type unsafe. Bonus points if you can demonstrate an equivalent of unsafeCoerce# this way.
This would be very bad, but I doubt it is possible.
Example: fooCast :: Foo Int -> Foo Double fooCast (Foo x) = Foo x
On noes! We just cast that Foo Int to a Foo Double without changing it!
What's the problem?
It works because the value on the RHS is consider freshly constructed and other than sharing x it is unrelated to the one on the LHS.
Right. You must call the data constructor Foo in order to exploit that it has the type Foo :: Int -> Foo a I don't see how this is not type safe, and I was not able to produce an #unsafeCoerce with this technique. One would need some unFoo a -> a but the a in data Foo a is phantom, i.e. there is no thing of type a in a Foo. Cheers Ben

On Sat, Aug 16, 2008 at 1:12 PM, Ben Franksen
Jason Dagit wrote:
On Wed, Aug 6, 2008 at 11:09 AM, Andrew Coppin
wrote: I just (re)discovered that I can do things like
data Foo x = Foo Int Int
Now "Foo Int" and "Foo Double" are, as far as the type checker cares, two completely different types, even though in fact they are the same. This is actually Quite Useful, in the particular case I'm working on.
Phantom types are indeed useful for many things, but a bit of cautionary advice. If you start to depend on the phantoms for type safety AND you export your data constructors then you run a serious risk of being type unsafe. Bonus points if you can demonstrate an equivalent of unsafeCoerce# this way.
This would be very bad, but I doubt it is possible.
Example: fooCast :: Foo Int -> Foo Double fooCast (Foo x) = Foo x
On noes! We just cast that Foo Int to a Foo Double without changing it!
What's the problem?
It's not so bad if you keep in mind that it's possible. Sometimes it's exactly what you want.
It works because the value on the RHS is consider freshly constructed and other than sharing x it is unrelated to the one on the LHS.
Right. You must call the data constructor Foo in order to exploit that it has the type
Foo :: Int -> Foo a
I don't see how this is not type safe, and I was not able to produce an #unsafeCoerce with this technique. One would need some
unFoo a -> a
but the a in data Foo a is phantom, i.e. there is no thing of type a
in a Foo.
Ah, it seems that the example I remembered cooking up requires GADTs, lexically scoped type variables and one unsafeCoerce#, so I guess it can be dismissed on the grounds that it uses unsafeCoerce# internally. I only need that because to make my thing work I need the following: data EqCheck a b where IsEq :: EqCheck a a NotEq :: EqCheck a b (=\/=) :: C a b -> C a c -> EqCheck b c Without unsafeCoerce# I don't see how to implement (=\/=). But, if you had that you could do the following: (=\/=) :: C a b -> C a c -> EqCheck b c a =\/= b | unC a == unC b = unsafeCoerce# IsEq | otherwise = NotEq data C x y = C String unsafeC :: String -> C x y unsafeC a = C a unC :: C x y -> String unC (C x) = x myCoerce :: forall a b. a -> b myCoerce x = fromJust $ do let ab = unsafeC "" :: C a b let aa = unsafeC "" :: C a a IsEq <- return $ aa =\/= ab return x Actually, it turns out that this also requires ghc 6.6. I just tried this out in both 6.6 and 6.8 and it turns out that in 6.8 the type checker was upgraded, in particular the way type checking works for GADTs was refined and the above program is rejected. I'm glad to see that myCoerce is not possible without using an unsafeCoerce# yourself. Thanks, Jason
participants (7)
-
Andrew Coppin
-
Ben Franksen
-
Bulat Ziganshin
-
Henning Thielemann
-
Jason Dagit
-
Jules Bean
-
Malcolm Wallace