Defining show for a function type.

I am a haskell-beginner and I wish to write a Forth-like interpreter. (Only for practice, no usefulness.) I would like use a list (as stack) that can contain several kinds of values. data Element = Int Int | Float Float | Func : Machine -> Machine | ... Now I would like to have this type be an instance of the class Show, so that I can see what the stack contains in ghci. "deriving Show" is impossible as Func is not instance of Show. Can I make it instance of Show? I just want to define something like show (Func _) = "Function, cannot show" and I am not interested in actually displaying any information about the function, but I am interested in getting information about elements of other kinds. So far I have just guessed, but failed to produce anything that does not give an error stating that my function is not of the form (T a b c) where T is not an alias and a b c are simple type variables (or so). Any help appreciated! Johan

Hi, you can make every function being an instance of class Show, this works for me: instance Show (a -> b) where show _ = "FUNCTION" data Element = Int Int | Float Float | Func (Machine -> Machine) deriving Show David Johan Grönqvist wrote:
I am a haskell-beginner and I wish to write a Forth-like interpreter. (Only for practice, no usefulness.)
I would like use a list (as stack) that can contain several kinds of values.
data Element = Int Int | Float Float | Func : Machine -> Machine | ...
Now I would like to have this type be an instance of the class Show, so that I can see what the stack contains in ghci.
"deriving Show" is impossible as Func is not instance of Show. Can I make it instance of Show? I just want to define something like
show (Func _) = "Function, cannot show"
and I am not interested in actually displaying any information about the function, but I am interested in getting information about elements of other kinds.
So far I have just guessed, but failed to produce anything that does not give an error stating that my function is not of the form (T a b c) where T is not an alias and a b c are simple type variables (or so).
Any help appreciated!
Johan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Johan Grönqvist wrote:
I would like use a list (as stack) that can contain several kinds of values.
data Element = Int Int | Float Float | Func : Machine -> Machine | ...
Now I would like to have this type be an instance of the class Show, so that I can see what the stack contains in ghci.
"deriving Show" is impossible as Func is not instance of Show. Can I make it instance of Show?
Of course you can: instance Show Element where showsPrec p (Int i) = showsPrec p i showsPrec p (Float f) = showsPrec p f showsPrec _ (Func _) = ("<<function>>" ++) ... Udo. -- Alcohol is the anesthesia by which we endure the operation of life. -- George Bernard Shaw

johan.gronqvist:
I am a haskell-beginner and I wish to write a Forth-like interpreter. (Only for practice, no usefulness.)
I would like use a list (as stack) that can contain several kinds of values.
data Element = Int Int | Float Float | Func : Machine -> Machine | ...
Now I would like to have this type be an instance of the class Show, so that I can see what the stack contains in ghci.
Here's an interesting, I think, show for functions that we use in
lambdabot's Haskell interpreter environment:
module ShowQ where
import Language.Haskell.TH
import System.IO.Unsafe
import Data.Dynamic
instance (Typeable a, Typeable b) => Show (a -> b) where
show e = '<' : (show . typeOf) e ++ ">"
instance Ppr a => Show (Q a) where
show e = unsafePerformIO $ runQ e >>= return . pprint
which generates results like:
dons:: > toUpper
lambdabot::

On Jul 10, 2006, at 8:44 AM, Johan Grönqvist wrote:
"deriving Show" is impossible as Func is not instance of Show. Can I make it instance of Show? I just want to define something like ... and I am not interested in actually displaying any information about the function, ...
Were you interested in "seeing" the function, you could do so, at least for finite, total functions (you can also enumerate them, compare them for equality, etc.). See my haskell-cafe message at http://www.haskell.org/pipermail/haskell-cafe/2006-April/015197.html. By way of example, and quoting a sample interaction from that message:
not == not True not == id False id == (not . not) True fromEnum not 1 not == toEnum 1 True not (\x -> case x of False -> True; True -> False) not == (\x -> case x of False -> True; True -> False) True id :: Bool -> Bool (\x -> case x of False -> False; True -> True) const True :: Bool -> Bool (\x -> case x of False -> True; True -> True)
-- Fritz

On 7/10/06, Fritz Ruehr
Were you interested in "seeing" the function, you could do so, at least for finite, total functions (you can also enumerate them, compare them for equality, etc.). See my haskell-cafe message at http://www.haskell.org/pipermail/haskell-cafe/2006-April/015197.html.
Hmm, interesting. How does it handle curried functions?

On Jul 11, 2006, at 8:27 AM, ihope wrote:
On 7/10/06, Fritz Ruehr
wrote: Were you interested in "seeing" the function, you could do so, at least for finite, total functions (you can also enumerate them, compare them for equality, etc.). See my haskell-cafe message at <http://www.haskell.org/pipermail/haskell-cafe/2006-April/ 015197.html>.
Hmm, interesting. How does it handle curried functions?
The trick is to define appropriate instances of Bounded, Enum, Eq, Ord and Show for function types, like this (and similarly for Bounded (a,b) and Enum (a,b)):
instance (Enum a, Bounded a, Enum b, Bounded b) => Bounded (a -> b) where ... instance (Enum a, Bounded a, Enum b, Bounded b) => Enum (a -> b) where ... instance (Enum a, Bounded a, Eq b) => Eq (a -> b) where ... instance (Enum a, Bounded a, Enum b, Bounded b, Eq b) => Ord (a -> b) where ... instance (Enum a, Bounded a, Show a, Show b) => Show (a -> b) where ...
Then curried functions of arbitrarily high order are handled automatically, so long as the "base" types are suitably Enum, Bounded, Showable, etc. In other words, a function of type (Bool,Bool) -> (Bool -> Bool) -> Bool -> Bool (or whatever) is resolved in stages, working down to the "base" type of Bool. Note of course that the Show form for such a function gives only an *extensional* description, in terms of argument-result pairs: there's no way to get the original function definition back, short of resorting to tricks (i.e, by defining something function-like, from which a function can be extracted, but which internally "stores" its means of definition). -- Fritz PS: I can email you the source if you're really interested ... but it's more instructive to at least try it yourself :) .

"Johan" == Johan Grönqvist
writes:
Johan> I am a haskell-beginner and I wish to write a Forth-like Johan> interpreter. (Only for practice, no usefulness.) Johan> I would like use a list (as stack) that can contain several Johan> kinds of values. Johan> data Element = Int Int | Float Float | Func : Machine -> Johan> Machine | ... Johan> Now I would like to have this type be an instance of the class Johan> Show, so that I can see what the stack contains in ghci. Johan> "deriving Show" is impossible as Func is not instance of Johan> Show. Can I make it instance of Show? I just want to define Johan> something like Johan> show (Func _) = "Function, cannot show" err, why not just write instance Show Element where ... show (Func _) = "Function, cannot show" E.g: data Foo = Bar | Foo (Int -> Int -> Int) instance Show Foo where show Bar = "Bar" show (Foo _) = "Func!" main = do putStrLn $ show Bar putStrLn $ show $ Foo (+) -- WBR, Max Vasin. NP: Nothing playing right now
participants (7)
-
David Sabel
-
dons@cse.unsw.edu.au
-
Fritz Ruehr
-
ihope
-
Johan Grönqvist
-
Max Vasin
-
Udo Stenzel