2

I'm trying to construct a datatype that is essentially a binary tree whose: each node's left branch is a function that can act on the variable in each node's right branch. I'm new to Haskell, and I'm not sure I'm going about this the right way, but my current problem is that I can't figure out how to add my type to the Show typeclass. Here is my attempt:

{-# LANGUAGE ExistentialQuantification #-}
-- file: TS.hs                                                                                                                                                       

data TypeSentence a = forall b. Apply (TypeSentence (b->a)) (TypeSentence b)
                    | Expr a

instance (Show a) => (Show (TypeSentence a)) where
        show (Expr x) = show x
        show (Apply x y) = (show x) ++ " " ++ (show y)

instance (Show (TypeSentence b->a)) where
    show (Expr x) = show "hello"

x = Expr 1
f = Expr (+1)
s = Apply f x

However, when I load this into ghci I get the following error:

TS.hs:9:24:                                                                                                                                                          
     Could not deduce (Show (b -> a)) from the context ()                                                                                                             
     arising from a use of `show' at TS.hs:9:24-29                                                                                                                  
      Possible fix:                                                                                                                                                    
      add (Show (b -> a)) to the context of the constructor `Apply'                                                                                                  
      or add an instance declaration for (Show (b -> a))                                                                                                             
        In the first argument of `(++)', namely `(show x)'                                                                                                               
        In the expression: (show x) ++ " " ++ (show y)                                                                                                                   
        In the definition of `show':                                                                                                                                     
           show (Apply x y) = (show x) ++ " " ++ (show y)                                                                                                               
 Failed, modules loaded: none. 

Any ideas how I go about adding the Show (b->a) declaration?

Thanks.

Eyal
  • 1,094
  • 10
  • 16
  • There's no way to make a `Show` instance for _general functions_, how do you imagine that should work? I don't think you actually want this, either. — Anyway, first of all this tree of yours does not do what you say: `b->a` can act on a `b`, but in the other branch there's an `a`. I believe you want to put a `b` there? – leftaroundabout Jun 28 '12 at 19:31
  • yep, you're right. fixed that. I would like to define Show on a general function so that it if the function has a Show instance then it it shows that and if not it recurses in the definition until it bottoms out at primitive functions that have show instances. – Eyal Jun 28 '12 at 19:35
  • 1
    Did you want to write `instance Show (TypeSentence (b->a))`? Note the brackets – sdcvvc Jun 28 '12 at 19:36
  • 2
    `import Text.Show.Functions` gives you a `Show` instance for functions (`show _ = ""`). – Daniel Fischer Jun 28 '12 at 19:36
  • Now what kind of output would you like e.g. your `s = Apply (Expr(+1)) (Expr 1)` to produce? – leftaroundabout Jun 28 '12 at 19:38
  • @leftaroundabout This would be nice: `(+1) 1` – Eyal Jun 28 '12 at 19:43
  • 1
    @Eyal: That's impossible, as it violates referential transparency. Having some `f :: (a -> b) -> String` such that `f (+ 1) = "(+ 1)"` and `f $ \x -> x + 1 = "\\x -> x + 1"` would allow us to distinguish two equal functions; and function equality is undecidable, which prevents us from finding some "canonical form" to show. – Antal Spector-Zabusky Jun 28 '12 at 19:47
  • If a useful `Show` instance for `(a → b)` could possibly exist, it would be in the Prelude ;) – n. m. could be an AI Jun 28 '12 at 19:48
  • @AntalS-Z: Perhaps you could expand? What if I don't care about the "canonical form?" All I care about is that once I've created this tree of expressions there is some way to display it. – Eyal Jun 28 '12 at 19:55
  • @Eyal The language only guarantees that `(+1) x` will evaluate to the same thing as `x + 1` for any choice of `x`. It does not guarantee anything about what the resulting value is made of. For example, one of the things GHC will do is replace this occurrence of `(+)` with a completely different function called `plusInteger`. It is valid to change a program this way because there's no observable difference. – Heatsink Jun 28 '12 at 20:37

4 Answers4

7

There are a few problems with your code as written, so I'm going to go through them one by one.

  1. You can't add a particularly informative instance for Show (a -> b). Consider how you'd have to write it:

    instance Show (a -> b) where
      show f = error "What goes here?"
    

    Since f is a function, there's nothing you can do with it other than apply it to a value; and since a is a fully-polymorphic type, you can't create a value of type a to apply f to. So your only option is something like

    instance Show (a -> b) where
      show _ = "<function>"
    

    As Daniel Fischer said in a comment, this is available in the Text.Show.Functions module. I wouldn't actually bother with this, though; I'd just write something like

    instance Show a => Show (TypeSentence a) where
      show (Apply _ x) = "Apply _ " ++ show x -- This still won't work; see below
      show (Expr x)    = "Expr " ++ show x
    

    Since show can only return the one string for any function, just inline that directly.

  2. Even then, though, you still can't write that Show instance. If you try to compile the instance above, you get the following error:

    TS.hs:8:36:
        Could not deduce (Show b) arising from a use of `show'
        from the context (Show a)
          bound by the instance declaration
          at TS.hs:7:10-40
        Possible fix:
          add (Show b) to the context of
            the data constructor `Apply'
            or the instance declaration
        In the second argument of `(++)', namely `show x'
        In the expression: "Apply _ " ++ show x
        In an equation for `show': show (Apply _ x) = "Apply _ " ++ show x
    

    The problem is that, in your definition of TypeSentence, Apply hides a variable (bound as x in the definition of show) of TypeSentence parametrized by some arbitrary existentially-hidden type b. But there's no guarantee that b is showable, so show x won't type check, which is the error produced above: there's no instance for Show b, because b is arbitrary. So to get rid of that, the simplest approach would be

    instance Show a => Show (TypeSentence a) where
      show (Apply _ _) = "Apply _ _"
      show (Expr x)    = "Expr " ++ show x
    

    And that's not particularly useful. So maybe there's not a good Show instance for TypeSentence. (And that's fine. Many useful types don't have Show instances.)

  3. This one's unrelated to everything else. The instance Show (TypeSentence b -> a) declaration tries to declare an instance of Show for functions from TypeSentence b to a; if you reparenthesize that as instance Show (TypeSentence (b -> a)), you still need both the FlexibleInstances and OverlappingInstances extension to get that to compile. So that you should probably just axe.

Antal Spector-Zabusky
  • 36,191
  • 7
  • 77
  • 140
4

Well, let's reason this through. Your proposed Show instance's show method will be called with some function f :: b -> a.

instance Show (b -> a) where
    show f = ...

What can your show method do? Well, it must produce some String, but how will it do it?

Well, since the type of f is b -> a, the only thing you can do with f is apply it to something of type b. Yet show has no argument of type b, and your Show class doesn't have any constants of type b, so the only thing that this show method could do with f is apply it to undefined. Which may or may not produce an error, depending on whether f is strict or not—which you have no control over, and I'm sure you don't want show to error out on some arguments anyway.

But in any case, even if you did get a result from f undefined, this result it would have type a, and there really is nothing your definition can do with an a anyway, since you don't have any functions of type a -> whatever available. (And if you did have one, unless whatever was String, you'd still be in the same position.)

So there's nothing sensible you can do with f, and since you have no other arguments, this means that the only thing your method can do is return a value that doesn't depend on f or any other argument. Thus, your method's return value has to be a constant, or undefined. Since using undefined would be silly, the only sensible thing this show method can do is return a constant String:

instance Show (b -> a) where
    show _ = "<function>"

As Daniel Fischer mentions in his comment to your question, this is already available in Text.Show.Functions.

But the lesson here is to take this as an example on how to reason through your question. This is one of the neat things about Haskell: you can often prove what a function can, can't or must do just by looking at the types. For example, if you have foo :: (a -> b) -> [a] -> [b], assuming foo is not silly enough doesn't use undefined gratuitously, you can infer that the bs in the [b] result are obtained by applying the a -> b type argument to elements of the [a] argument. There is no other way for foo to produce values of type b. (If you didn't guess already, the most natural function of that type is map :: (a -> b) -> [a] -> [b].)

Luis Casillas
  • 29,802
  • 7
  • 49
  • 102
1

I think the @Davorak 's comment is what you want.

https://stackoverflow.com/a/15846061/6289448

I just share it here. Pass test in ghc 8.6.5.

There is a partial solution that goes beyond just a fixed string for all functions using Data.Typeable.

{-# LANGUAGE ScopedTypeVariables #-}

import Data.Typeable

instance (Typeable a, Typeable b) => Show (a->b) where
  show _ = show $ typeOf (undefined :: a -> b)

in ghci

> let test :: Int->Int; test x = x + x
> test
Int -> Int

Unfortunately without a type signature the type will go to it default.

> let test x = x + x
> test
Integer -> Integer

This solution works on multiple function arities because a -> b -> c is the same as a -> (b -> c) which you might as well write as a -> d where d = b -> c.

> let m10 a b c d e f g h i j = a * b * c * d * e * f * g * h* i * j
> m10
Integer -> Integer -> Integer -> Integer -> Integer -> Integer -> Integer
        -> Integer -> Integer -> Integer -> Integer

This method does not work however when it is unknown if parameters of the function have the typeable class however so while map (+1) will work map will not.

> map (+1)
[Integer] -> [Integer]
> map

<interactive>:233:1:
...

After glancing at the internals of Data.Data and an experiment or two it seems like it could be refactored to be a little more generalized cover more functions.



If you dont like implemention above, just implement it by yourself! (Let me know If there's a better way, please!)

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE ScopedTypeVariables #-}

newtype GenType a =
    GenType
        { asTypeStr :: String
        }

class GenTypeArbitrary a where
    gtArbitrary :: a -> GenType a

instance GenTypeArbitrary String where
    gtArbitrary :: String -> GenType String
    gtArbitrary _ = GenType "String123"

instance GenTypeArbitrary Bool where
    gtArbitrary :: Bool -> GenType Bool
    gtArbitrary _ = GenType "Bool123"

instance GenTypeArbitrary Int where
    gtArbitrary :: Int -> GenType Int
    gtArbitrary _ = GenType "Int123"

instance (GenTypeArbitrary a, GenTypeArbitrary b) => GenTypeArbitrary (a -> b) where
    gtArbitrary :: (GenTypeArbitrary a, GenTypeArbitrary b) => (a -> b) -> GenType (a -> b)
    gtArbitrary _ = GenType $ aTypeStr' ++ " --> " ++ bTypeStr
      where
        aTypeStr = asTypeStr (gtArbitrary (undefined :: a))
        aTypeStr' =
            if "-->" `isInfixOf` aTypeStr
                then "(" ++ aTypeStr ++ ")"
                else aTypeStr
        bTypeStr = asTypeStr (gtArbitrary (undefined :: b))

instance  (GenTypeArbitrary a, GenTypeArbitrary b) => Show (a -> b) where
  show f = asTypeStr $ gtArbitrary f

test1 :: Int -> String
test1 x = ""

test2 :: Int -> String -> Int -> Bool -> Bool
test2 _ _ _ _ = False

test3 :: Int -> ((String -> Int) -> Bool) -> Bool
test3 _ _ = False

test4 :: Int -> (Bool -> (String -> Int)) -> Bool
test4 _ _ = False


λ > show  (test4)
    "Int123 --> (Bool123 --> String123 --> Int123) --> Bool123"
it :: String


...


λ > show  (test3)
    "Int123 --> ((String123 --> Int123) --> Bool123) --> Bool123"
it :: String


lihansey
  • 210
  • 2
  • 5
0

If your function's domain is a finite set then you can print the value of your function at all the points. In Haskell you can do that with the typeclasses Ix and Bounded by using a function like:

rangeF :: (Ix a, Bounded a) => [a]
rangeF = range (minBound, maxBound)
Nicolas Dudebout
  • 9,172
  • 2
  • 34
  • 43