[Haskell-cafe] 123

Jack Henahan jhenahan at me.com
Wed Aug 16 18:01:50 UTC 2017


Some mostly unrelated thoughts:

An instance head has the form `T a_1 ... a_n`, and the constraint can only
apply to the `a_i`s. Consider the Show instance for
pairs.

instance (Show a, Show b) => Show (a, b) -- Show ((,) a b)

The constraints only act on the parameters of the type.

It looks like you're taking the constraint to mean "whenever I have a Showable
`f String`, this is how to define a Show instance", but a constraint
actually means "use this rule to make a Show instance for any `A f`, and
it is an error if a Show instance for `f String` is not in scope".

In the second error, you are making the strong claim that your Show
instance for `A f` holds for any `f` and `a`. Even if you could trick
the compiler into allowing that, I don't think it would actually express
the constraint that you want it to.

Is there something a Show instance gets you that a pretty-print function wouldn't?

Dmitriy Matrosov <sgf.dma at gmail.com> writes:

> Hi.
>
> Is there a way to avoid `UndecidableInstances` in following code:
>
>     data A f        = A {_a1 :: f String}
>
>     instance Show (f String) => Show (A f) where
>
> it does not compile with
>
>     1.hs:4:10: error:
>         • The constraint ‘Show (f String)’
>             is no smaller than the instance head
>           (Use UndecidableInstances to permit this)
>         • In the instance declaration for ‘Show (A f)’
>
> Though, initially, this was
>
>     {-# LANGUAGE RankNTypes #-}
>
>     data A f        = A {_a1 :: f String}
>
>     instance forall f a. Show (f a) => Show (A f) where
>
> which also does not compile with
>
>     1.hs:5:10: error:
>         • Variable ‘a’ occurs more often
>             in the constraint ‘Show (f a)’ than in the instance head
>           (Use UndecidableInstances to permit this)
>         • In the instance declaration for ‘Show (A f)’
>
> The error is different and i don't sure, that this two cases are related.
>
> I want these instances to make a type with many records parametrized by
> `Alternative` type, e.g.
>
>     data Volume t       = Volume
>                             { _volName  :: t Name
>                             , _volSize  :: t Size
>                             , _volPath  :: t Path
>                             , _pool     :: t Pool
>                             }
>
> When i try to make instances, which require `*` type, i will end with
> above cases.


--
Jack
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 832 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170816/14e690ec/attachment.sig>


More information about the Haskell-Cafe mailing list