[Haskell-cafe] Question about instance

John Velman velman at cox.net
Thu Jan 13 20:25:08 EST 2005


Thanks, Andreas.  Your example still left me without context in the show
statement itself, but your message set me to look in the right place.

Now I have

--- Code
>data Relation a i b = Rel {name::RN, arity::Int, members::(Set [EN])}
>
>instance (Show a, Show i, Show b) => Show (Relation a i b)
>   where
>     show (Rel a i b) =
>                    a ++ "/" ++ (show i) ++ " "
>                    ++ (show b)
>

---
with result:
---GHCI

Prelude> :l test.hs
Compiling Main             ( test.hs, interpreted )
Ok, modules loaded: Main.
*Main> mkRelation1 "test" 2 [["one","two"], ["three","four"]]
test/2 mkSet [["one","two"],["three","four"]]
*Main>
---End GHCI

It's hard to find examples like this, and the fact that it is fairly
standard practice for the type name and constructor names to be the same
in, for example, Gentle Haskell, and Haskell School of Expression make it
more difficult for the novice to see when each is used!

Best,

John Velman



On Fri, Jan 14, 2005 at 01:49:57AM +0100, Andreas Marth wrote:
> If you replace
> >data Relation  = Relation {name::RN, arity::Int, members::(Set [EN])}
> with
> >data Relation  = Rel {name::RN, arity::Int, members::(Set [EN])}
> you will easy find out what is wrong and come to:
> 
> >import Data.Set
> >
> >type EN = String  -- element name
> >
> >type RN = String  -- relation name
> >
> >instance Show a => Show (Set a) where
> >   show s = "mkSet " ++ show (setToList s)
> >
> >data Relation  = Rel {name::RN, arity::Int, members::(Set [EN])}
> >
> >instance Show (Relation)
> >   where
> >     show (Rel a i b) = a ++ "/" ++ (show i) ++ " " ++ (show b)
> 
> 
> Of course you can now change Rel back to Relation. But because of the
> problems you just experienced I don't like it to name a type and its
> constructor the same.
> 
> 
> Happy coding,
> Andreas
> 
> 
> 
> ----- Original Message ----- 
> From: "John Velman" <velman at cox.net>
> To: <haskell-cafe at haskell.org>
> Sent: Friday, January 14, 2005 1:29 AM
> Subject: [Haskell-cafe] Question about instance
> 
> 
> > Instance with a context doesn't seem to work as I expect.
> >
> > Here's the story:
> >
> > I define an data type, Relation, and I want to make it an instance of
> > "Show", partly so I can debug and tinker with things interactively and
> have
> > ghci print something.
> >
> > Here is my first try:
> > ----
> > >
> > >import Data.Set
> > >
> > >type EN = String  -- element name
> > >
> > >type RN = String  -- relation name
> > >
> > >instance Show a => Show (Set a) where
> > >   show s = "mkSet " ++ show (setToList s)
> > >
> > >data Relation  = Relation {name::RN, arity::Int, members::(Set [EN])}
> > >
> > >instance (Show a, Show i, Show b) => Show (Relation a i b)
> > >   where
> > >     show (Relation a i b) =
> > >                    a ++ "/" ++ (show i) ++ " "
> > >                    ++ (show b)
> > ----
> >
> > When I try to load this into ghci, I get:
> >
> > ---GHCI:
> >
> > *Main> :l test.hs
> > Compiling Main             ( test.hs, interpreted )
> >
> > test.hs:14:
> >     Kind error: `Relation' is applied to too many type arguments
> >     When checking kinds in `Relation a i b'
> >     When checking kinds in `Show (Relation a i b)'
> >     In the instance declaration for `Show (Relation a i b)'
> > Failed, modules loaded: none.
> > Prelude>
> > ---END GHCI
> > But, when I define showRelation separately, then leave the context out of
> > the instance declaration with show = showRelation it works:
> >
> > -----------(Everything down to the instance declaration is the same)
> > >instance  Show Relation
> > >   where
> > >     show = showRelation
> > >
> > >showRelation:: Relation -> String
> > >showRelation (Relation a i b) =
> > >                    a ++ "/" ++ (show i) ++ " "
> > >                    ++ (show b)
> > >
> > -----------
> >
> > Now I get:
> > ----------- GHCI output:
> > Prelude> :l test.hs
> > Compiling Main             ( test.hs, interpreted )
> > Ok, modules loaded: Main.
> > *Main> mkRelation1 "test" 2 [["one","two"], ["three","four"]]
> > test/2 mkSet [["one","two"],["three","four"]]
> > *Main>
> > ---------- End GHCI
> >
> > Why does the original instance declaration result in failure and the
> > message "Kind error: `Relation' is applied to too many type arguments" (I
> > confess to not understanding 'kinds' too well.)
> >
> > I've done a bit of tinkering with the original version, and have tried the
> > second version with a context in the instance declaration, but none of my
> > attmepts work.  The only one that worked was the one shown, with no
> context
> > in the instance declaration.  Needless to say (?), I've tried to
> > understand this from reading in the Haskell 98 report, `Haskell school of
> > Expression', and any place else I can think of, but I'm missing the point
> > somewhere.
> >
> >
> > Thanks,
> >
> > John Velman
> > _______________________________________________
> > 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