[Haskell-cafe] Defining show for a function type.
Donald Bruce Stewart
dons at cse.unsw.edu.au
Mon Jul 10 22:01:26 EDT 2006
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:: <Char -> Char>
dons:: > \x -> x+1::Int
lambdabot:: <Int -> Int>
dons:: > map
lambdabot:: Add a type signature
Note that also the standard libraries come with Text.Show.Functions
-- Don
More information about the Haskell-Cafe
mailing list