[Haskell-cafe] Fwd: Re: 123

Dmitriy Matrosov sgf.dma at gmail.com
Wed Aug 16 20:54:29 UTC 2017


And even sent the answer not to the list.. Huh.

-------- Forwarded Message --------

Oops, i forgot to change the subject. Sorry!

On 08/16/2017 09:01 PM, Jack Henahan wrote:
>
> 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?

Well, the `Show` was just an example. And examples with `A` was just a
simplified versions, but perhaps oversimplified and hiding original 
intention.

> {-# LANGUAGE RankNTypes       #-}
> {-# LANGUAGE GADTs            #-}
> {-# LANGUAGE StandaloneDeriving #-}
>
> import Control.Applicative
> import Data.Monoid
> import Data.Typeable

I want to have a type with many records:

> data Volume t     = Volume
>                       { _volName  :: t String
>                       , _volSize  :: t Int
>                       }
>
> showVolume :: (Show (t String), Show (t Int)) => Volume t -> String
> showVolume x      = "Volume " ++ show (_volName x) ++ ", " ++ show 
(_volSize x)

with instances parametrized by some other type. E.g. i want to define a
`Monoid` based on that other type properties:

> instance Alternative t => Monoid (Volume t) where
>   mempty          = Volume {_volName = empty, _volSize = empty}
>   x `mappend` y   = Volume
>                       { _volName = _volName x <|> _volName y
>                       , _volSize = _volSize x <|> _volSize y
>                       }

and i may use this like

> v1 :: Alternative t => Volume t
> v1                = Volume {_volName = pure "vol1", _volSize = empty}
> v2 :: Alternative t => Volume t
> v2                = Volume {_volName = pure "vol2", _volSize = pure 200}

     *Main> showVolume (v1 <> v2 :: Volume Maybe)
     "Volume Just \"vol1\", Just 200"

     *Main> showVolume (v1 <> v2 :: Volume [])
     "Volume [\"vol1\",\"vol2\"], [200]"

But then i want to define a GADT, which has different behaviors depending on
argument type. So different records, depending on their type, will behave
differently.

> data Config a where
>   Empty :: Config a
>   Name :: Last String -> Config String
>   Size :: Num a => Sum a  -> Config a
> deriving instance Show a => Show (Config a)
> instance Monoid (Config a) where
>   mempty  = Empty
>   (Name x) `mappend` (Name y)     = Name (x `mappend` y)
>   (Size x) `mappend` (Size y)     = Size (x `mappend` y)
>   x        `mappend` Empty        = x
>   Empty    `mappend` y            = y

but i can't even define a `Functor` instance for this type, because `case`
branches have different type and `Functor` laws won't hold.. Hm..

  instance Functor Config where
    fmap f Empty    = Empty
    --fmap f (Name s) = case cast f of
    --                    Just g  -> case (g s) of
    --                        Just s' -> Name s'
    --                        _   -> Empty
    --                    Nothing -> Empty

The other problem is with instances for classes requiring type of kind `*`.
I'll end up with what i've asked before:

  instance (Show a, Show (t a)) => Show (Volume t) where

Well, i didn't write that before asking, so i realize all these problems 
only
now (i even forgot to change the subject, what else to say?). And now i 
don't
even sure what the proper subject should be. So thanks and never mind, i 
need
to try more to figure out what to ask.

>
> 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
>



More information about the Haskell-Cafe mailing list