[Haskell-cafe] Existentially-quantified constructors, Eq and Show

Cale Gibbard cgibbard at gmail.com
Thu Dec 8 05:09:21 EST 2005


Okay, so here you *did* get something from the existential typing :)

The type of show, restricted to State in the original version is:
show :: Show a => State a -> String

Now, in the new version, you get the type:
show :: (Eq a, Show a) => State a -> String
because what happens is that pattern matches against data constructors
of the new State type result in that class context being added to the
type of a function. The derived instance of show pattern matches
against values of the state type, and there you have it. Here's an
excerpt from: http://www.haskell.org/onlinereport/decls.html#user-defined-datatypes

================

For example, the declaration

  data Eq a => Set a = NilSet | ConsSet a (Set a)

introduces a type constructor Set of kind *->*, and constructors
NilSet and ConsSet with types

NilSet 	:: forall a. Set a
ConsSet 	:: forall a. Eq a =>a ->Set a ->Set a

In the example given, the overloaded type for ConsSet ensures that
ConsSet can only be applied to values whose type is an instance of the
class Eq. Pattern matching against ConsSet also gives rise to an Eq a
constraint. For example:

  f (ConsSet a s) = a

the function f has inferred type Eq a => Set a -> a. The context in
the data declaration has no other effect whatsoever.

================

This doesn't happen in the strangely existential version (which isn't
really making full use of the existential quantification) since such a
pattern matching rule doesn't apply there.

It's actually probably best to just leave the context off the type
altogether. Though this makes the type of the data constructors more
general, it probably won't cause any further trouble.

 - Cale

On 08/12/05, Joel Reymont <joelr1 at gmail.com> wrote:
> Here is something else that I don't quite understand...
>
> Original version compiles:
>
> push :: Show b => State b -> Dispatcher b a -> (ScriptState a b) ()
> push state dispatcher =
>      do w <- get
>         trace 95 $ "push: Pushing " ++ show state ++ " onto the stack"
>         let s = stack w
>         putStrict $ w { stack = (state, dispatcher):s }
>
> data State a
>      = Start
>      | Stop
>      | (Show a, Eq a) => State a
>
> instance Eq a => Eq (State a) where
>      (State a) == (State b) = a == b
>      Start == Start = True
>      Stop == Stop = True
>      _ == _ = False
>
> instance Show a => Show (State a) where
>      show (State a) = show a
>      show Start = "Start"
>      show Stop = "Stop"
>
> This version does not. Why does it require Eq in the ++ context? And
> why doesn't the other version?
>
> data (Show a, Eq a) => State a
>      = Start
>      | Stop
>      | State a
>      deriving (Eq, Show)
>
> Could not deduce (Eq b) from the context (Show b)
>     arising from use of `show' at ./Script/Engine.hs:86:38-41
> Probable fix: add (Eq b) to the type signature(s) for `push'
> In the first argument of `(++)', namely `show state'
> In the second argument of `(++)', namely `(show state) ++ " onto the
> stack"'
>
> --
> http://wagerlabs.com/
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list