Re: Show class on ADT with function

2000-05-10 Thread John Launchbury

Note that these have omitted the behavior of the function on bottom, so even on a 
finite domains, the description is not complete.

john.


[EMAIL PROTECTED] wrote:
> 
> George writes:
> > There is no problem with Showing functions with finite domains.
> > For example, try:
> 
> > module ShowFun where
> > instance (Show a) => Show (Bool -> a) where
> >show f = show ((f  True),(f False))
> > instance (Show a) => (Show (Int -> a))
> 
> Why stop there?  Eq and Read too, though they do become tricky at Int->Int.
> 
> 
> Ian Stark http://www.dcs.ed.ac.uk/home/stark
> LFCS, Division of Informatics, The University of Edinburgh, Scotland






Re: Show class on ADT with function

2000-05-08 Thread Ian . Stark

George writes:
> There is no problem with Showing functions with finite domains.
> For example, try:

> module ShowFun where
> instance (Show a) => Show (Bool -> a) where
>show f = show ((f  True),(f False))
> instance (Show a) => (Show (Int -> a))

Why stop there?  Eq and Read too, though they do become tricky at Int->Int.


Ian Stark http://www.dcs.ed.ac.uk/home/stark
LFCS, Division of Informatics, The University of Edinburgh, Scotland




Re: Show class on ADT with function

2000-05-05 Thread George Russell

Marcin 'Qrczak' Kowalczyk wrote:
> Show instance for functions should not be needed. It is only for lazy
> programmers who want to make a quick dirty instance, for debugging
> perhaps.
And why not?  There is no problem with Showing functions with finite domains.
For example, try:

module ShowFun where

instance (Show a) => Show (Bool -> a) where
   show f = show ((f True),(f False))

instance (Show (a -> b -> c)) => Show ((a,b) -> c) where
   show f = show (\ a b -> f (a,b))

If you load this into Hugs (with -98) then you will be able to show
functions like && and not,and much more complicated ones like
(\ (a,(b,c)) (d,e) -> length (filter id [a,b,c,d,e]))

Indeed since show returns a string which can be infinite I suppose you
can just as well define

instance (Show a) => (Show (Int -> a))

But you will need to be clever about interleaving if you want to be able
to show functions of type Int -> Int -> a in such a way that all strings
are distinguishable.

(I realise this message has no serious purpose whatsoever and apologise
to people whose time it has wasted.  But it's the weekend after all.)




Re: Show class on ADT with function

2000-05-05 Thread Marcin 'Qrczak' Kowalczyk

Fri, 05 May 2000 16:17:42 +0200, Sven Panne <[EMAIL PROTECTED]> 
pisze:

> > data Fn = Fn (Float -> Float) Int
> > deriving Show
> 
> Functions are not an instance of Show, so you have to supply
> 
>instance Show (a -> b) where

Better supply a Show instance for Fn, not by deriving, but by
instance Show Fn where ...

Show instance for functions should not be needed. It is only for lazy
programmers who want to make a quick dirty instance, for debugging
perhaps.

-- 
 __("$ P+++ L++>$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+>++ DI D- G+ e> h! r--%>++ y-





Re: Show class on ADT with function

2000-05-05 Thread Sven Panne

Mike Jones wrote:
> [...]
> data Fn = Fn (Float -> Float) Int
> deriving Show
> 
> But, I get the error from GHC as follows:
> 
> Stimulus.hs:12:
> No instance for `Show (Float -> Float)'
> When deriving classes for `Fn'
> [...]

Functions are not an instance of Show, so you have to supply

   instance Show (a -> b) where
  showsPrec _ _ = showString ""

or add `import ShowFunctions' (in the upcoming GHC 4.07's package lang).

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne




Show class on ADT with function

2000-05-05 Thread Mike Jones

Hi,

I want to put a function in an ADT and make the ADT an instance of Show.
Like the following small example:

data Fn = Fn (Float -> Float) Int
deriving Show

But, I get the error from GHC as follows:

Stimulus.hs:12:
No instance for `Show (Float -> Float)'
When deriving classes for `Fn'

Compilation had errors

make: *** [Stimulus.o] Error 1

Is there any way to do this? Note that it would be ok to generate blank
text.

Thanks,

Mike