[Haskell-cafe] How to unify these three types with identical structures into one definition?

William Yager will.yager at gmail.com
Sun Dec 16 06:00:39 UTC 2018


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 <will.yager at gmail.com> wrote:

> 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 <monkleyon at gmail.com> 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.
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20181216/9ab24e89/attachment.html>


More information about the Haskell-Cafe mailing list