Combining Wouter's expressions with extensible records

Well, my extension of Wouter's datatypes proved to be unweildy.... So, I'm trying to use http://fmapfixreturn.wordpress.com/2008/05/03/simple-extensible-records-now-... for extensible records. I ran across my first problem rather quickly! data Expr f = In (f (Expr f)) Ok, but to make it part of a record, it needs to implement Data: data Expr f = In (f (Expr f)) deriving Data but this gives No instances for (Data (f (Expr f)), Typeable (Expr f)) arising from the 'deriving' clause of a data type declaration at Planning/Wouter.hs:77:0-42 Any hints? Thanks, -Ron

On Wed, Jul 9, 2008 at 9:40 PM, Ron Alford
Ok, but to make it part of a record, it needs to implement Data: data Expr f = In (f (Expr f)) deriving Data
but this gives No instances for (Data (f (Expr f)), Typeable (Expr f)) arising from the 'deriving' clause of a data type declaration at Planning/Wouter.hs:77:0-42
The Data class has a requirement that any instances are also instances of Typeable, so you'd really want
data ... = ... deriving (Data, Typeable)
Except that I couldn't derive Typeable for your particular data type. It isn't immediately obvious to me that the "Typeable" family of classes deal at all with higher-kinded type constructors, but I didn't look that hard. -Antoine

On Wed, Jul 9, 2008 at 11:01 PM, Antoine Latter
It isn't immediately obvious to me that the "Typeable" family of classes deal at all with higher-kinded type constructors, but I didn't look that hard.
Yes, that's what I'm worried about. For people's fun and amusement, I've attached the file. The trailing comments show what I'm trying to accomplish (getName, setName, and so forth). -Ron

Or, if people have easy-enough extensible records that /will/ work
with funky types, I'd be happy to use those!
-Ron
On Thu, Jul 10, 2008 at 10:29 AM, Ron Alford
On Wed, Jul 9, 2008 at 11:01 PM, Antoine Latter
wrote: It isn't immediately obvious to me that the "Typeable" family of classes deal at all with higher-kinded type constructors, but I didn't look that hard.
Yes, that's what I'm worried about. For people's fun and amusement, I've attached the file. The trailing comments show what I'm trying to accomplish (getName, setName, and so forth).
-Ron

I'm making progress, but how would I make the following a Typeable instance:
data (f :+: g) e = Inl (f e) | Inr (g e) deriving Eq
Here is what I'm using for Expr:
data Expr f = In (f (Expr f))
instance Typeable1 f => Typeable (Expr f) where
typeOf (In x) = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [typeOf1 x]
I don't think I can use this for ':+:', because the typeOf instance
only has access to a member of one type at a time.
This may be similar to a definition of Typeable2 for Either, but I
can't find an example to follow for that.
Thanks,
-Ron
On Wed, Jul 9, 2008 at 10:40 PM, Ron Alford
Well, my extension of Wouter's datatypes proved to be unweildy.... So, I'm trying to use http://fmapfixreturn.wordpress.com/2008/05/03/simple-extensible-records-now-... for extensible records.
I ran across my first problem rather quickly! data Expr f = In (f (Expr f))
Ok, but to make it part of a record, it needs to implement Data: data Expr f = In (f (Expr f)) deriving Data
but this gives No instances for (Data (f (Expr f)), Typeable (Expr f)) arising from the 'deriving' clause of a data type declaration at Planning/Wouter.hs:77:0-42
Any hints?
Thanks, -Ron

On Thu, Jul 10, 2008 at 2:15 PM, Ron Alford
I'm making progress, but how would I make the following a Typeable instance: data (f :+: g) e = Inl (f e) | Inr (g e) deriving Eq
Here is what I'm using for Expr: data Expr f = In (f (Expr f)) instance Typeable1 f => Typeable (Expr f) where typeOf (In x) = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [typeOf1 x]
I don't think I can use this for ':+:', because the typeOf instance only has access to a member of one type at a time. This may be similar to a definition of Typeable2 for Either, but I can't find an example to follow for that.
Maybe something like: instance (Typeable1 f, Typeable1 g) => Typeable (f :+: g) where typeOf in@(InL f) = (some function of 'f' and 'g') where InR g = undefined `asTypeOf` in typeOf in@(InR g) = (some function of 'f' and 'g') where InL f = undefined `asTypeOf` in would work? -Antoine

Close - it compiles now! I made a minor change, going to Typeable1
instead of Typeable:
instance (Typeable1 f, Typeable1 g) => Typeable1 (f :+: g) where
typeOf1 l@(Inl x) = mkTyConApp (mkTyCon "Planning.Wouter.:+:")
[typeOf1 x, typeOf1 y]
where (Inr y) = undefined `asTypeOf` l
typeOf1 r@(Inr y) = mkTyConApp (mkTyCon "Planning.Wouter.:+:")
[typeOf1 x, typeOf1 y]
where (Inl x) = undefined `asTypeOf` r
Except this gives me a runtime error:
*WouterTest> getName testNamed
"*** Exception: Prelude.undefined
The only thing I can think of is to have a class that gives default
values to type - ick!
-Ron Alford
On Thu, Jul 10, 2008 at 4:16 PM, Antoine Latter
On Thu, Jul 10, 2008 at 2:15 PM, Ron Alford
wrote: I'm making progress, but how would I make the following a Typeable instance: data (f :+: g) e = Inl (f e) | Inr (g e) deriving Eq
Here is what I'm using for Expr: data Expr f = In (f (Expr f)) instance Typeable1 f => Typeable (Expr f) where typeOf (In x) = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [typeOf1 x]
I don't think I can use this for ':+:', because the typeOf instance only has access to a member of one type at a time. This may be similar to a definition of Typeable2 for Either, but I can't find an example to follow for that.
Maybe something like:
instance (Typeable1 f, Typeable1 g) => Typeable (f :+: g) where typeOf in@(InL f) = (some function of 'f' and 'g') where InR g = undefined `asTypeOf` in
typeOf in@(InR g) = (some function of 'f' and 'g') where InL f = undefined `asTypeOf` in
would work?
-Antoine

This is a bit similar to Either. Is there a way to see the generated
instance code for
deriving instance Data Either ?
On Thu, Jul 10, 2008 at 6:38 PM, Ron Alford
Close - it compiles now! I made a minor change, going to Typeable1 instead of Typeable:
instance (Typeable1 f, Typeable1 g) => Typeable1 (f :+: g) where typeOf1 l@(Inl x) = mkTyConApp (mkTyCon "Planning.Wouter.:+:") [typeOf1 x, typeOf1 y] where (Inr y) = undefined `asTypeOf` l typeOf1 r@(Inr y) = mkTyConApp (mkTyCon "Planning.Wouter.:+:") [typeOf1 x, typeOf1 y] where (Inl x) = undefined `asTypeOf` r
Except this gives me a runtime error: *WouterTest> getName testNamed "*** Exception: Prelude.undefined
The only thing I can think of is to have a class that gives default values to type - ick!
-Ron Alford
On Thu, Jul 10, 2008 at 4:16 PM, Antoine Latter
wrote: On Thu, Jul 10, 2008 at 2:15 PM, Ron Alford
wrote: I'm making progress, but how would I make the following a Typeable instance: data (f :+: g) e = Inl (f e) | Inr (g e) deriving Eq
Here is what I'm using for Expr: data Expr f = In (f (Expr f)) instance Typeable1 f => Typeable (Expr f) where typeOf (In x) = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [typeOf1 x]
I don't think I can use this for ':+:', because the typeOf instance only has access to a member of one type at a time. This may be similar to a definition of Typeable2 for Either, but I can't find an example to follow for that.
Maybe something like:
instance (Typeable1 f, Typeable1 g) => Typeable (f :+: g) where typeOf in@(InL f) = (some function of 'f' and 'g') where InR g = undefined `asTypeOf` in
typeOf in@(InR g) = (some function of 'f' and 'g') where InL f = undefined `asTypeOf` in
would work?
-Antoine

Ok, I'm closer, but I'm running into a problem with typeOf and lists, of all things: *WouterTest> typeOf (eVar "v" :: TermExpr) Planning.Wouter.Expr (Planning.Wouter.:+: WouterTest.Const WouterTest.Var) *WouterTest> typeOf ([eVar "v"] :: [TermExpr]) *** Exception: Prelude.undefined I'm pretty sure this is the culprit for getName: *WouterTest> getName testNamed "*** Exception: Prelude.undefined Any hints? Also, anyone have hints for how to get automatic derivation of Data (Expr f) ? I don't want to proliferate the last lines: deriving instance Data (Expr (And :+: Atomic (Expr (Const :+: Var)))) deriving instance Data (Expr (Const :+: Var)) -Ron Alford

2008/7/10 Ron Alford
Ok, I'm closer, but I'm running into a problem with typeOf and lists, of all things: *WouterTest> typeOf (eVar "v" :: TermExpr) Planning.Wouter.Expr (Planning.Wouter.:+: WouterTest.Const WouterTest.Var) *WouterTest> typeOf ([eVar "v"] :: [TermExpr]) *** Exception: Prelude.undefined
I'm pretty sure this is the culprit for getName: *WouterTest> getName testNamed "*** Exception: Prelude.undefined
Any hints?
Also, anyone have hints for how to get automatic derivation of Data (Expr f) ? I don't want to proliferate the last lines: deriving instance Data (Expr (And :+: Atomic (Expr (Const :+: Var)))) deriving instance Data (Expr (Const :+: Var))
I screwed up the example code - it typechecks, but it'll fail at runtime. If you say:
Inr x = undefined
and then try to pass 'x' off to another function, you're trying to evaluate the "undeifned", which is a runtime error. You'll want something more like: typeOf1 in@(InR f) = [...] where InL f = (InL undefined) `asTypeOf` in This is approaching silliness, but I've tested the code this time around - so it should even work. -Antoine

What's odd is that it works directly (typeOf ... (Expr (f :+: g))
returns a type), but if you enclose the expression in a list, it fails
with Prelude.undefined. Do I also need a custom instance for
Typeable [Expr ...] ? (See previous message for code)
-Ron
On Fri, Jul 11, 2008 at 1:56 AM, Antoine Latter
2008/7/10 Ron Alford
: Ok, I'm closer, but I'm running into a problem with typeOf and lists, of all things: *WouterTest> typeOf (eVar "v" :: TermExpr) Planning.Wouter.Expr (Planning.Wouter.:+: WouterTest.Const WouterTest.Var) *WouterTest> typeOf ([eVar "v"] :: [TermExpr]) *** Exception: Prelude.undefined
I'm pretty sure this is the culprit for getName: *WouterTest> getName testNamed "*** Exception: Prelude.undefined
Any hints?
Also, anyone have hints for how to get automatic derivation of Data (Expr f) ? I don't want to proliferate the last lines: deriving instance Data (Expr (And :+: Atomic (Expr (Const :+: Var)))) deriving instance Data (Expr (Const :+: Var))
I screwed up the example code - it typechecks, but it'll fail at runtime.
If you say:
Inr x = undefined
and then try to pass 'x' off to another function, you're trying to evaluate the "undeifned", which is a runtime error.
You'll want something more like:
typeOf1 in@(InR f) = [...] where InL f = (InL undefined) `asTypeOf` in
This is approaching silliness, but I've tested the code this time around - so it should even work.
-Antoine

On Fri, Jul 11, 2008 at 7:07 AM, Ron Alford
What's odd is that it works directly (typeOf ... (Expr (f :+: g)) returns a type), but if you enclose the expression in a list, it fails with Prelude.undefined. Do I also need a custom instance for Typeable [Expr ...] ? (See previous message for code)
The problem is that the List instance is playing the same dirty tricks with it's 'typeOf' implementation as we are: it's asking us the type of one of the list elements by passing in "undefined" to our "typeOf1" implementation. And then your "typeOf1" implementation tries to do pattern matching on undefined. Here is what will work: instance (Typeable1 f, Typeable1 g) => Typeable1 (f :+: g) where typeOf1 x = mkTyConApp (mkTyCon "Planning.Wouter.:+:") [typeOf1 left, typeOf1 right] where (Inr right) = Inr undefined `asTypeOf` x (Inl left) = Inl undefined `asTypeOf` x Now we never do pattern matching on our input. This has been pretty educational. -Antoine
participants (2)
-
Antoine Latter
-
Ron Alford