How to unify these three types with identical structures into one definition?

Hello, Say I have a certain type for parse trees: data Expr = Var String | Enclosed String Expr String | Prefix Expr Expr | Ternary Expr String Expr String Expr deriving (Show,Eq,Ord,Generic)--,Typeable) Then I want a new type where every occurence of "Expr" definition changed to "[Expr]": data ExprL = VarL String | EnclosedL String [Expr] String | PrefixL [Expr] [Expr] | TernaryL [Expr] String [Expr] String [Expr] deriving (Show,Eq,Ord,Generic) Sometimes, I also want to use a DList instead of list. data ExprD = VarD String | EnclosedD String (DList Expr) String | PrefixD (DList Expr) (DList Expr) | TernaryD (DList Expr) String (DList Expr) String (DList Expr) deriving (Show,Eq,Ord,Generic) They have exactly the same structure, is there a way to unify the three definitions into one? Furthurmore, is it possible to generalise the latter two for all Functors ? Thanks, ducis

Hello, my adhoc solution would be to add a type parameter: data ExprG a = Var String | Enclosed String a String | Prefix a a | Ternary a String a String a deriving Show type Expr = ExprG (ExprG ()) type ExprL = ExprG [Expr] Cheers, Tobias On 12/14/18 1:56 PM, ducis wrote:
Hello,
Say I have a certain type for parse trees: data Expr = Var String | Enclosed String Expr String | Prefix Expr Expr | Ternary Expr String Expr String Expr deriving (Show,Eq,Ord,Generic)--,Typeable)
Then I want a new type where every occurence of "Expr" definition changed to "[Expr]": data ExprL = VarL String | EnclosedL String [Expr] String | PrefixL [Expr] [Expr] | TernaryL [Expr] String [Expr] String [Expr] deriving (Show,Eq,Ord,Generic)
Sometimes, I also want to use a DList instead of list. data ExprD = VarD String | EnclosedD String (DList Expr) String | PrefixD (DList Expr) (DList Expr) | TernaryD (DList Expr) String (DList Expr) String (DList Expr) deriving (Show,Eq,Ord,Generic)
They have exactly the same structure, is there a way to unify the three definitions into one? Furthurmore, is it possible to generalise the latter two for all Functors ?
Thanks, ducis
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

You probably mean
newtype Expr = Expr (ExprG Expr)
Az iPademről küldve
2018. dec. 14. dátummal, 14:08 időpontban Tobias Brandt
Hello,
my adhoc solution would be to add a type parameter:
data ExprG a = Var String | Enclosed String a String | Prefix a a | Ternary a String a String a deriving Show
type Expr = ExprG (ExprG ())
type ExprL = ExprG [Expr]
Cheers,
Tobias
On 12/14/18 1:56 PM, ducis wrote: Hello,
Say I have a certain type for parse trees: data Expr = Var String | Enclosed String Expr String | Prefix Expr Expr | Ternary Expr String Expr String Expr deriving (Show,Eq,Ord,Generic)--,Typeable)
Then I want a new type where every occurence of "Expr" definition changed to "[Expr]": data ExprL = VarL String | EnclosedL String [Expr] String | PrefixL [Expr] [Expr] | TernaryL [Expr] String [Expr] String [Expr] deriving (Show,Eq,Ord,Generic)
Sometimes, I also want to use a DList instead of list. data ExprD = VarD String | EnclosedD String (DList Expr) String | PrefixD (DList Expr) (DList Expr) | TernaryD (DList Expr) String (DList Expr) String (DList Expr) deriving (Show,Eq,Ord,Generic)
They have exactly the same structure, is there a way to unify the three definitions into one? Furthurmore, is it possible to generalise the latter two for all Functors ?
Thanks, ducis
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi Ducis, you can parametrise over type variables of other kinds than just *. If what you write is really what you want, the most straightforward answer is simply data ExprG f = Var VarName | Enclosed VarName (f Expr) VarName | Prefix (f Expr) (f Expr) | Ternary (f Expr) VarName (f Expr) VarName (f Expr) type Expr = ExprG Identity -- From Data.Functor.Identity type ExprL = ExprG [] type ExprD = ExprG DList There is no mention of the word "functor" because you will have to add that constraint to the usage sites. Downside: notice that the deriving clauses are gone because the instances aren't as easy to derive any more. Even the simplest and most harmless way I know to get that possibility back involves two language extensions: StandaloneDeriving and FlexibleInstances. With those you can write deriving instance Show (ExprG Identity) deriving instance Show (ExprG []) deriving instance Show (ExprG DList) deriving instance Eq (ExprG Identity) : I suspect though that what you actually want, but didn't write, is more along the lines of data ExprL = … | EnclosedL VarName [ExprL] VarName | … -- using ExprL instead of Expr on the right side data ExprD = … | EnclosedD VarName (DList ExprD) VarName | … -- using ExprD instead of Expr on the right side The good news is that if you have the first solution, this step is rather simple. Because you can just use replace Expr with ExprG f again: data ExprG f = Var VarName | Enclosed VarName (f (ExprG f)) VarName | Prefix (f (ExprG f)) (f (ExprG f)) | Ternary (f (ExprG f)) VarName (f (ExprG f)) VarName (f (ExprG f)) The better news is that although this looks repetitive and hard to read, it's well on the way to discovering the magic of the Free Monad. Hope this helps. Cheers, MarLinn

There may be some fun to be had with QuantifiedConstraints. I've thought about solving similar parser/formatter problems this way, extending parsers via functor composition. Consider:
data F f = F (f (F f))
-- Sadly the below does not work. It seems like maybe it should be able to work?
instance (forall a . Show a => Show (f a)) => Show (F f) where show (F f) = "(F " ++ show f ++ ")"
<interactive>:23:10: error: • The constraint ‘Show (f a)’ is no smaller than the instance head ‘Show (F f)’ (Use UndecidableInstances to permit this) • In the instance declaration for ‘Show (F f)’
-- We can get something almost as good
class (forall a . Show a => Show (f a)) => Show1 f
instance Show1 f => Show (F f) where show (F f) = "(F " ++ show f ++ ")"
instance Show1 Maybe
show (F $ Just $ F $ Nothing)
"(F Just (F Nothing))"
On Fri, Dec 14, 2018 at 10:52 PM MarLinn
Hi Ducis,
you can parametrise over type variables of other kinds than just *.
If what you write is really what you want, the most straightforward answer is simply
data ExprG f = Var VarName | Enclosed VarName (f Expr) VarName | Prefix (f Expr) (f Expr) | Ternary (f Expr) VarName (f Expr) VarName (f Expr)
type Expr = ExprG Identity -- From Data.Functor.Identity type ExprL = ExprG [] type ExprD = ExprG DList
There is no mention of the word "functor" because you will have to add that constraint to the usage sites.
Downside: notice that the deriving clauses are gone because the instances aren't as easy to derive any more. Even the simplest and most harmless way I know to get that possibility back involves two language extensions: StandaloneDeriving and FlexibleInstances. With those you can write
deriving instance Show (ExprG Identity) deriving instance Show (ExprG []) deriving instance Show (ExprG DList) deriving instance Eq (ExprG Identity) :
I suspect though that what you actually want, but didn't write, is more along the lines of
data ExprL = … | EnclosedL VarName [ExprL] VarName | … -- using ExprL instead of Expr on the right side
data ExprD = … | EnclosedD VarName (DList ExprD) VarName | … -- using ExprD instead of Expr on the right side
The good news is that if you have the first solution, this step is rather simple. Because you can just use replace Expr with ExprG f again:
data ExprG f = Var VarName | Enclosed VarName (f (ExprG f)) VarName | Prefix (f (ExprG f)) (f (ExprG f)) | Ternary (f (ExprG f)) VarName (f (ExprG f)) VarName (f (ExprG f))
The better news is that although this looks repetitive and hard to read, it's well on the way to discovering the magic of the Free Monad.
Hope this helps.
Cheers, MarLinn
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

I've been thinking about this a bit more - I'm still not sure if it's
correct for the instance above to require UndecidableInstances.
Why is the `a` counting towards the "size" of the constraint? It seems like
since it's introduced existentially, it shouldn't introduce ambiguities in
the typeclass resolution mechanism. However, I know little about the
internals of the typeclass solver, so I could be wrong about that.
On Sat, Dec 15, 2018 at 8:58 PM William Yager
There may be some fun to be had with QuantifiedConstraints. I've thought about solving similar parser/formatter problems this way, extending parsers via functor composition. Consider:
data F f = F (f (F f))
-- Sadly the below does not work. It seems like maybe it should be able to work?
instance (forall a . Show a => Show (f a)) => Show (F f) where show (F f) = "(F " ++ show f ++ ")"
<interactive>:23:10: error:
• The constraint ‘Show (f a)’
is no smaller than the instance head ‘Show (F f)’
(Use UndecidableInstances to permit this)
• In the instance declaration for ‘Show (F f)’
-- We can get something almost as good
class (forall a . Show a => Show (f a)) => Show1 f
instance Show1 f => Show (F f) where show (F f) = "(F " ++ show f ++ ")"
instance Show1 Maybe
show (F $ Just $ F $ Nothing)
"(F Just (F Nothing))"
On Fri, Dec 14, 2018 at 10:52 PM MarLinn
wrote: Hi Ducis,
you can parametrise over type variables of other kinds than just *.
If what you write is really what you want, the most straightforward answer is simply
data ExprG f = Var VarName | Enclosed VarName (f Expr) VarName | Prefix (f Expr) (f Expr) | Ternary (f Expr) VarName (f Expr) VarName (f Expr)
type Expr = ExprG Identity -- From Data.Functor.Identity type ExprL = ExprG [] type ExprD = ExprG DList
There is no mention of the word "functor" because you will have to add that constraint to the usage sites.
Downside: notice that the deriving clauses are gone because the instances aren't as easy to derive any more. Even the simplest and most harmless way I know to get that possibility back involves two language extensions: StandaloneDeriving and FlexibleInstances. With those you can write
deriving instance Show (ExprG Identity) deriving instance Show (ExprG []) deriving instance Show (ExprG DList) deriving instance Eq (ExprG Identity) :
I suspect though that what you actually want, but didn't write, is more along the lines of
data ExprL = … | EnclosedL VarName [ExprL] VarName | … -- using ExprL instead of Expr on the right side
data ExprD = … | EnclosedD VarName (DList ExprD) VarName | … -- using ExprD instead of Expr on the right side
The good news is that if you have the first solution, this step is rather simple. Because you can just use replace Expr with ExprG f again:
data ExprG f = Var VarName | Enclosed VarName (f (ExprG f)) VarName | Prefix (f (ExprG f)) (f (ExprG f)) | Ternary (f (ExprG f)) VarName (f (ExprG f)) VarName (f (ExprG f))
The better news is that although this looks repetitive and hard to read, it's well on the way to discovering the magic of the Free Monad.
Hope this helps.
Cheers, MarLinn
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (5)
-
ducis
-
MarLinn
-
MigMit
-
Tobias Brandt
-
William Yager