Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Keean Schupke
Marcin 'Qrczak' Kowalczyk wrote:
Ben Rudiak-Gould [EMAIL PROTECTED] writes:
 

is there *any* way to get, without an exploitable race condition,
two filehandles to the same file which don't share a file pointer?
   

In unix the traditional way to do this is to use a directory. Each 
process/thread
opens its own file... and you have some kind of master index/ordering 
file to
keep track of which file is doing what (for example Highly parallel mail 
software).

At the end of the day IO is serial by nature (to one device anyway), so 
the way to
do this into one file is to have one thread that reads and writes, and 
to 'send'
read and write requests over channels from the threads that need the work
done... Effectively the channels serialise the requests. This has the added
advantage that is guarantees the transactional itegrity of the IO (for 
example
database software)

   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Ketil Malde
Keean Schupke [EMAIL PROTECTED] writes:

 At the end of the day IO is serial by nature (to one device anyway),
 so the way to do this into one file is to have one thread that reads
 and writes, and to 'send' read and write requests over channels from
 the threads that need the work done

Would the stream proposal make this possible and easy?  I.e. could the
IO thread provide (say) output streams to the other threads, and pass
writes on to its own output stream?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Keean Schupke
No I meant Channels (from Data.Concurrent)... you can use a structure like:
   data Command = Read FileAddr (MVar MyData) | Write FileAddr MyData
So to write you just do:
   writeChan iochan (Write address data) -- returns immediately
   -- write happens asynchronously later
and to read:
   data - newEmptyMVar
   writeChan iochan (Read address data) -- read not happend yet.
   myData - readMVar data -- blocks until read completes.
The forked thread (with forkIO) just reads the commands form the iochan
and processes them one at a time.
   Keean
Ketil Malde wrote:
Keean Schupke [EMAIL PROTECTED] writes:
 

At the end of the day IO is serial by nature (to one device anyway),
so the way to do this into one file is to have one thread that reads
and writes, and to 'send' read and write requests over channels from
the threads that need the work done
   

Would the stream proposal make this possible and easy?  I.e. could the
IO thread provide (say) output streams to the other threads, and pass
writes on to its own output stream?
-kzm
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


package readline unknown symbol problem on GHCi 6.2.2 Windows binary (Was: [Haskell-cafe] Problem with wxHaskell

2005-01-13 Thread shelarcy
On Wed, 12 Jan 2005 12:03:44 -0800, John Velman [EMAIL PROTECTED] wrote:
 Your code works fine on Linux.  :-)

 Oh, by the way, I compiled my wxHaskell with GHC 6.2.2
 On Wed, Jan 12, 2005 at 04:16:33PM +0100, Dmitri Pissarenko wrote:
 I've downloaded wxHaskell, ran the wxhaskell-register.bat file and now  
 try to build a minimal wxHaskell program.

 For this purpose, I tried to start GHCi using following command

 ghci -package wx GuiTest.hs

Hmm. I think this problem is specially on Windows binary by using GHCi.
If you use GHC, programm may be compiled without following error message.

 GHCi crashed with following error messages:
 error-messages
 GHC Interactive, version 6.2.2, for Haskell 98.
 http://www.haskell.org/ghc/
 Type :? for help.

 Loading package base ... linking ... done.
 Loading package haskell98 ... linking ... done.
 Loading package lang ... linking ... done.
 Loading package concurrent ... linking ... done.
 Loading package QuickCheck ... linking ... done.
 Loading package readline ... linking ...
 C:/ghc/ghc-6.2.2/HSreadline.o: unknown symbol `_rl_redisplay_function'
 ghc.exe: unable to load package `readline'
 /error-messages

I saw this error message in other programs what GHCi on Windows call
readline
package automaticly. ex. HaXml program. (So I don't want to use HaXml
program
on windows.)
This is GHCi bug.


-- 
shelarcy shelarcy capella.freemail.ne.jp
http://page.freett.com/shelarcy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Keean Schupke
Ketil Malde wrote:
Keean Schupke [EMAIL PROTECTED] writes:
 

No I meant Channels (from Data.Concurrent)... you can use a structure like:
   

Yes, I realize that (although I haven't yet used Data.Concurrent).  It
seemed to me, though, that streams are related to channels, and that
it may be possible to use the same (or a slightly more generalized)
abstraction?  (I should perhasp experiment a bit with concurrent
programming and streams, and it'll surely become apparent how and why
I'm mistaken :-) 

-kzm
 

I don't necessarily think you are mistaken, but why re-invent the wheel
when channels are almost ideal for the job (inter-thread FIFO's)...
At the end of the day streams between processes are channels... in effect
(non seekable) streams are extending channels to IO.
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Signature of a function

2005-01-13 Thread Conor McBride
Hi folks
The main thing I like about type signatures is that they help the
computer write the boring bits of my programs for me.
I've said it before and I'll say it again, no doubt: when we talk
about 'type inference', we should distinguish two aspects:
  (1) the machine doesn't know your plan and tries to guess it
(let-rule style, ie finding the abstraction)
  (2) the machine does know your plan and is fleshing out the details
(var-rule style, ie finding the instantiation)
You can only make (1) fully automatic at the cost of compulsory
ignorance, dumbing down the collection of possible plans to those
which are guessable by a machine. I find this unpleasantly
restrictive. I at least want a manual override, which Haskell pretty
much provides. But as types get more expressive, it's often the
case that you can give your programs much more useful types than the
machine is ever going to guess. Possibly even a type which explains
what a function's output has to do with its input.
You can make (2) very powerful indeed. Even in the conventional batch
mode of edit-then-compile, you can use overloading to shift the burden
of programming from a large amount of tedious plumbing in the program
text to a smaller class constraint in the signature. I often find myself
using newtypes to explain which structure of my data I want to exploit,
then leaving instance inference to exploit it in the 'obvious' way.
There are better reasons to write type signatures than that the compiler
is too dumb or that the nuns will whip us if we don't. Type signatures
enable chunks of program inference, which is much more useful than aspect
(1) of type inference.
Types can be seen as a highly expressive and compact language of
design statements for both humans and machines to read: this design
statement determines the space of essential choices for the programmer,
and programming can, if we choose, consist of navigating that space.
Machines can map that space out for us, and they can fill in all the
no-choice bits and pieces once we decide which way to go.
I'm not advocating compulsory refinement editing. I'm saying that type
signatures currently feel ephemeral only because today's
program-construction tools fail to take positive advantage of
the fact that machines can manipulate programs in a typed way.
Cheers
Conor
--
http://www.cs.nott.ac.uk/~ctm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Marcin 'Qrczak' Kowalczyk
Ketil Malde [EMAIL PROTECTED] writes:

 It seemed to me, though, that streams are related to channels,

I'm not sure what exactly do you mean by streams (because they are
only being designed), but differences are:

- A stream is either an input stream or an output stream, while a
  single channel supports reading from one end and writing to the
  other end.

- A stream passes around bytes, which are usually grouped in blocks
  for efficiency. A channel is polymorphic wrt. the element type and
  elements are always processed one by one.

- A stream may be backed by an OS file, pipe, socket etc., while
  a channel exists purely in Haskell.

- A channel is never closed. Reading more data than have been put
  blocks until someone puts more data. A stream can reach its end,
  which is a condition a reader can detect. A stream backed by a pipe
  is similar to a channel of bytes in that the reader blocks until
  someone puts more data, but it can be closed too, which causes the
  reader to observe end of file. A writer to a stream can block too
  when the internal buffer in the kernel is full.

- A stream can be inherited by child processes, and it generally
  continues to work by being linked to the same data sink or source as
  before. A channel is inherited as a whole: there is no communication
  between the two versions of the channel in the two processes.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Signature of a function

2005-01-13 Thread Keean Schupke
Conor McBride wrote:
Types can be seen as a highly expressive and compact language of
design statements for both humans and machines to read: this design
statement determines the space of essential choices for the programmer,
and programming can, if we choose, consist of navigating that space.
Machines can map that space out for us, and they can fill in all the
no-choice bits and pieces once we decide which way to go.
For me this is the most important aspect. As programs become more complex,
and as optimisation techniques are applied (or algorithms changed), Types
can act as 'contracts'. Infact I would like to see type expressiveness 
expanded...

Imagine for examle (and this can be done in Haskell with the HList 
library) adding
a static constraint requiring proof at compile time that a list was 
ordered (according
to some criteria:

   mysort :: (HList a, HOrderedList b) = a - b
Now the definition of the constraint for orderedness is quite simple, 
and easy
to understand (as as it plays no part in the final program efficiency is 
not an
issue) - we are now free to write a heap sort or whatever, knowing it 
will only
compile if it obeys the constraint.

Obviously the above only works when the input list is statically 
determined at
compile time...

We can easily insert run-time checks in code - but it would be much 
better to
have the compiler proove that the code obeys the criteria under all 
circumstances.

In other words rather than saying for a specific list the result should 
be ordered,
it should be ordered forall a.

   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Ketil Malde
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes:

 Ketil Malde [EMAIL PROTECTED] writes:

 It seemed to me, though, that streams are related to channels,

 I'm not sure what exactly do you mean by streams (because they are
 only being designed), but differences are:

Sorry for being unclear, I was thinking in relation to the new-io
proposal Simon M. recently posted on the lists (I put all Haskell mail
in the same folder, it could have been a ghc list or haskell@).

 - A stream passes around bytes, which are usually grouped in blocks
   for efficiency. A channel is polymorphic wrt. the element type and
   elements are always processed one by one.

Perhaps I'm confused, but while Stream.StreamInputStream is a stream
of Word8, Text.TextInputStream provides a stream of Chars.

Thanks for the explanation!

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with wxHaskell

2005-01-13 Thread Dmitri Pissarenko
Hello!
Thanks for your answer!
I solved the problem by using GHC 6.2.1 instead of GHC 6.2.2 (under Windows).
Best regards
Dmitri Pissarenko
--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with wxHaskell

2005-01-13 Thread Michael Walter
Is someone aware of how to make it work with 6.2.2?

Thanks,
Michael


On Thu, 13 Jan 2005 18:09:20 +0100, Dmitri Pissarenko
[EMAIL PROTECTED] wrote:
 Hello!
 
 Thanks for your answer!
 
 I solved the problem by using GHC 6.2.1 instead of GHC 6.2.2 (under Windows).
 
 Best regards
 
 Dmitri Pissarenko
 --
 Dmitri Pissarenko
 Software Engineer
 http://dapissarenko.com
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsec and type (IO t) error

2005-01-13 Thread Greg Buchholz

This is probably an easy question, but I'm having a problem with
parsec in the IO monad.  The essential parts of my program looks like
this...

import Text.ParserCombinators.Parsec

main = do input - getContents
  putStr $ show $ parse_text shape_parse input
  --(cam, sh) - parse_text shape_parse input 
  --putStr $ (show cam) ++ \n ++ (show sh)
  putStr \n

parse_text p input = case (parse p input) of
Left err - error $ Invalid input++(show err)
Right x  - x

shape_parse = do cam - camera_parse
 shapes - many1 (sphere_parse | plane_parse)
 return (cam, shapes)

-- blah, blah, blah, etc.

  This works fine in GHC.  The types for parse_text and shape_parse
are...

*Main :t parse_text
parse_text :: forall a tok. GenParser tok () a - [tok] - a
*Main :t shape_parse
shape_parse :: forall st. GenParser Char st (Camera, [Shape])
*Main 

Now when I change main to...

main = do input - getContents
  --putStr $ show $ parse_text shape_parse input
  (cam, sh) - parse_text shape_parse input
  putStr $ (show cam) ++ \n ++ (show sh)
  putStr \n

 I get the following message from GHCi...

p2.hs:38:
Couldn't match `IO t' against `(Camera, [Shape])'
Expected type: GenParser Char () (IO t)
Inferred type: GenParser Char () (Camera, [Shape])
In the first argument of `parse_text', namely `shape_parse'
In a 'do' expression: (cam, sh) - parse_text shape_parse input


I'm probably missing something silly.  Any hint would be appreciated.

Thanks,

Greg Buchholz

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec and type (IO t) error

2005-01-13 Thread Greg Buchholz
Mike Gunter wrote:
 
 I'd guess that
  let (cam, sh) = parse_text shape_parse input
 is what you want?  (Completely untested ...)


Yep.  That did it. 

Thanks,

Greg Buchholz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Question about instance

2005-01-13 Thread John Velman
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: package readline unknown symbol problem on GHCi 6.2.2 Windows binary (Was: [Haskell-cafe] Problem with wxHaskell

2005-01-13 Thread Jinwoo Lee
You can remove that error message by including following in package.conf 
file.

Package
   {name = readline,
auto = True,
import_dirs = [$libdir/imports],
source_dirs = [],
library_dirs = [$libdir],
hs_libraries = [HSreadline],
extra_libraries = [readline, advapi32],
include_dirs = [],
c_includes = [HsReadline.h],
package_deps = [base],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = [],
framework_dirs = [],
extra_frameworks = []},
Jinwoo Lee
Always remember that you are unique.  Just like everyone else.
[EMAIL PROTECTED]

shelarcy wrote:
On Wed, 12 Jan 2005 12:03:44 -0800, John Velman [EMAIL PROTECTED] wrote:
Your code works fine on Linux.  :-)
Oh, by the way, I compiled my wxHaskell with GHC 6.2.2
On Wed, Jan 12, 2005 at 04:16:33PM +0100, Dmitri Pissarenko wrote:
I've downloaded wxHaskell, ran the wxhaskell-register.bat file and 
now  try to build a minimal wxHaskell program.

For this purpose, I tried to start GHCi using following command
ghci -package wx GuiTest.hs

Hmm. I think this problem is specially on Windows binary by using GHCi.
If you use GHC, programm may be compiled without following error message.
GHCi crashed with following error messages:
error-messages
GHC Interactive, version 6.2.2, for Haskell 98.
http://www.haskell.org/ghc/
Type :? for help.
Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package lang ... linking ... done.
Loading package concurrent ... linking ... done.
Loading package QuickCheck ... linking ... done.
Loading package readline ... linking ...
C:/ghc/ghc-6.2.2/HSreadline.o: unknown symbol `_rl_redisplay_function'
ghc.exe: unable to load package `readline'
/error-messages

I saw this error message in other programs what GHCi on Windows call
readline
package automaticly. ex. HaXml program. (So I don't want to use HaXml
program
on windows.)
This is GHCi bug.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with wxHaskell

2005-01-13 Thread Jinwoo Lee
You can remove that error message by including following in package.conf 
file.

Package
  {name = readline,
   auto = True,
   import_dirs = [$libdir/imports],
   source_dirs = [],
   library_dirs = [$libdir],
   hs_libraries = [HSreadline],
   extra_libraries = [readline, advapi32],
   include_dirs = [],
   c_includes = [HsReadline.h],
   package_deps = [base],
   extra_ghc_opts = [],
   extra_cc_opts = [],
   extra_ld_opts = [],
   framework_dirs = [],
   extra_frameworks = []},
Jinwoo Lee
Always remember that you are unique.  Just like everyone else.
[EMAIL PROTECTED]

Michael Walter wrote:
Is someone aware of how to make it work with 6.2.2?
Thanks,
Michael
On Thu, 13 Jan 2005 18:09:20 +0100, Dmitri Pissarenko
[EMAIL PROTECTED] wrote:
 

Hello!
Thanks for your answer!
I solved the problem by using GHC 6.2.1 instead of GHC 6.2.2 (under Windows).
Best regards
Dmitri Pissarenko
--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
   

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Question about instance

2005-01-13 Thread John Velman
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 [EMAIL PROTECTED]
 To: haskell-cafe@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@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe