
So suppose I have a simple data type:
data Thing { thing_id :: ThingId , thing_stuff :: Stuff } newtype ThingId = ThingId String
Stuff is a Monoid, and Things need to be combined as well, so:
instance Monoid Thing where mappend (Thing id1 stuff1) (Thing id2 stuff2) | id1 /= id2 = error "..." | otherwise = Thing id1 (stuff1 `mappend` stuff2) mempty = Thing $ (ThingId "dummy value?") mempty
So clearly both the error and the "dummy value?" are not very nice (and mappend would need a special hack to treat the dummy as compatible with everything). I'd like to be able to lift that ID up to the type level, and then I don't have to worry about incompatible IDs and the mempty can figure out the ID from the type. Now if ThingId were a natural, I gather there's a new GHC feature for type level naturals that can do this kind of thing. Of course any string could be encoded into a large natural, but the resulting type errors would be less than readable. There is probably also a way to encode type level strings in the same way as the traditional way for type level naturals, e.g. 'data A; ... data Z;' and then a type encoding for lists. But I'm guessing that would also lead to excessive compilation times and crazy type errors. In any case, I don't think this can work even if I used naturals instead of ints, because it seems to me I can't write a function '(NatI n) => ThingId -> Thing n' without a statically knowable constant value for 'n'. Otherwise, the value has magically disappeared into the type system and I can't expect to get it back after types are erased. So I need a runtime value for the ThingId, but it still seems like it should be possible to do something better than the 'error' and "dummy value?". Maybe there's a completely different way to ensure that incompatible Things can't be mappended. Any ideas?

You can do this with phantom types, i.e.:
data Thing a = Thing Stuff
instance Monoid (Thing a) where mappend (Thing stuff1) (Thing stuff2) = Thing (stuff1 `mappend` stuff2) mempty = Thing mempty
data ID1 data ID2
thing1 :: Thing ID1 thing1 = Thing Stuff
thing2 :: Thing ID2 thing2 = Thing Stuff
-- will not typecheck: f = thing1 `mappend` thing2
2011/11/23 Evan Laforge
So suppose I have a simple data type:
data Thing { thing_id :: ThingId , thing_stuff :: Stuff } newtype ThingId = ThingId String
Stuff is a Monoid, and Things need to be combined as well, so:
instance Monoid Thing where mappend (Thing id1 stuff1) (Thing id2 stuff2) | id1 /= id2 = error "..." | otherwise = Thing id1 (stuff1 `mappend` stuff2) mempty = Thing $ (ThingId "dummy value?") mempty
So clearly both the error and the "dummy value?" are not very nice (and mappend would need a special hack to treat the dummy as compatible with everything). I'd like to be able to lift that ID up to the type level, and then I don't have to worry about incompatible IDs and the mempty can figure out the ID from the type.
Now if ThingId were a natural, I gather there's a new GHC feature for type level naturals that can do this kind of thing. Of course any string could be encoded into a large natural, but the resulting type errors would be less than readable. There is probably also a way to encode type level strings in the same way as the traditional way for type level naturals, e.g. 'data A; ... data Z;' and then a type encoding for lists. But I'm guessing that would also lead to excessive compilation times and crazy type errors.
In any case, I don't think this can work even if I used naturals instead of ints, because it seems to me I can't write a function '(NatI n) => ThingId -> Thing n' without a statically knowable constant value for 'n'. Otherwise, the value has magically disappeared into the type system and I can't expect to get it back after types are erased.
So I need a runtime value for the ThingId, but it still seems like it should be possible to do something better than the 'error' and "dummy value?". Maybe there's a completely different way to ensure that incompatible Things can't be mappended. Any ideas?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Nov 23, 2011 at 4:03 PM, Holger Reinhardt
You can do this with phantom types, i.e.:
data Thing a = Thing Stuff
instance Monoid (Thing a) where mappend (Thing stuff1) (Thing stuff2) = Thing (stuff1 `mappend` stuff2) mempty = Thing mempty
data ID1 data ID2
thing1 :: Thing ID1 thing1 = Thing Stuff
thing2 :: Thing ID2 thing2 = Thing Stuff
-- will not typecheck: f = thing1 `mappend` thing2
Well yes, but the key feature is that the IDs are arbitrary strings. And they're not knowable at compile time, since they are read from user input...

On Thu, Nov 24, 2011 at 10:06 AM, Evan Laforge
Well yes, but the key feature is that the IDs are arbitrary strings. And they're not knowable at compile time, since they are read from user input...
You can still use phantom types for this, you just need existentials as well. For example, you could define a type for indexed strings/id's as: data IString s = IString String data Exists f = forall x. Exists (f x) read :: String -> Exists IString read stuff = Exists (IString stuff) I assume you'll also want to compare strings/id's, in which case you'll also need (using GADT's): data Equal a b where Refl :: Equal a a equal :: IString s -> IString t -> Maybe (Equal s t) equal (IString x) (IString y) | x == y = Just (unsafeCoerce Refl) equal _ _ = Nothing

On Wed, Nov 23, 2011 at 4:25 PM, Julian Beaumont
On Thu, Nov 24, 2011 at 10:06 AM, Evan Laforge
wrote: Well yes, but the key feature is that the IDs are arbitrary strings. And they're not knowable at compile time, since they are read from user input...
You can still use phantom types for this, you just need existentials as well. For example, you could define a type for indexed strings/id's as:
data IString s = IString String
data Exists f = forall x. Exists (f x)
read :: String -> Exists IString read stuff = Exists (IString stuff)
I assume you'll also want to compare strings/id's, in which case you'll also need (using GADT's):
data Equal a b where Refl :: Equal a a
equal :: IString s -> IString t -> Maybe (Equal s t) equal (IString x) (IString y) | x == y = Just (unsafeCoerce Refl) equal _ _ = Nothing
I don't fully understand this but it looks interesting! I guess 'read' is a constructor for a sort of witness of the id, but I don't see how to get this value into the type parameter, or how Equal would be used in my mappend example. Could you help me figure out how it relates? Here's the closest I could get: data Thing thing_id = Thing { thing_id :: Exists IString , thing_stuff :: [Int] } thing :: String -> [Int] -> Thing thing_id thing thing_id stuff = Thing (istring thing_id) stuff instance Monoid.Monoid (Thing thing_id) where mempty = Thing undefined [] mappend (Thing id1 stuff1) (Thing _ stuff2) = Thing id1 (Monoid.mappend stuff1 stuff2) istring :: String -> Exists IString istring thing_id = Exists (IString thing_id) data IString s = IString String data Exists f = forall x. Exists (f x) data Equal a b where Refl :: Equal a a equal :: IString s -> IString t -> Maybe (Equal s t) equal (IString x) (IString y) | x == y = Just (Coerce.unsafeCoerce Refl) equal _ _ = Nothing But as you can see it's not right, because the 'thing_id' goes into the existential but is not expressed in the type parameter to Thing (the real usage is that Things are Pitches which have a Scale and a Signal, and it only makes sense to combine Pitches with the same scale, which is probably a more interesting example, but I started with Stuff and Things so I guess I should stick with it). I don't see how I could use Equal, because the signature for mappend already expresses that the arguments should be the same type. And while I can see how to extract the String from the IString, I don't see how to figure out the String from the *type* of the IString, as I would need to do in mempty, since IString has no type parameter.

On Thu, Nov 24, 2011 at 2:17 AM, Evan Laforge
I don't fully understand this but it looks interesting! I guess 'read' is a constructor for a sort of witness of the id, but I don't see how to get this value into the type parameter, or how Equal would be used in my mappend example. Could you help me figure out how it relates? Here's the closest I could get:
Did you try something like below? data Thing id = Thing { thing_id :: IString id , thing_stuff :: [Int] } thing :: String -> [Int] -> Exists Thing thing id stuff = case istring id of Exists id_ -> Exists (Thing id_ stuff) instance Monoid (Thing id) where mempty = Thing undefined [] mappend (Thing id1 stuff1) (Thing _ stuff2) = Thing id1 (mappend stuff1 stuff2) maybeAppend :: Exists Thing -> Exists Thing -> Maybe (Exists Thing) maybeAppend (Exists t1) (Exists t2) = case thing_id t1 `equal` thing_id t2 of Just Refl -> Just $ Exists (t1 `mappend` t2) Nothing -> Nothing Cheers, -- Felipe.
participants (4)
-
Evan Laforge
-
Felipe Almeida Lessa
-
Holger Reinhardt
-
Julian Beaumont