summaryrefslogtreecommitdiff
path: root/testsuite/tests/gadt/karl2.hs
blob: de8390f0425c2718f0df995c375cb016f0775ccc (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
{-# LANGUAGE GADTs, KindSignatures #-}

module Expr0 where

-- See #301
-- This one *does* use GADTs (Fct)

import Data.Kind (Type)

data Expr :: Type -> Type where
  Const :: Show a => a -> Expr a
  Apply :: Fct a b -> Expr a -> Expr b

data Fct :: Type -> Type -> Type where
  Succ :: Fct Int Int
  EqZero :: Fct Int Bool
  Add :: Fct Int (Int -> Int)

------------------------------
e1 :: Expr Int
e1 = Apply Succ (Const 41)

e2 :: Expr Bool
e2 = Apply EqZero e1

e3 :: Expr (Int -> Int)
e3 = Apply Add e1

------------------------------
eval :: Expr a -> a
eval (Const c) = c
eval (Apply f a) = evalFct f $ eval a

evalFct :: Fct a b -> a -> b
evalFct Succ = succ
evalFct EqZero = (0 ==)
evalFct Add = (+)


{-  Up to here, everything works nicely:

    \begin{verbatim}
    *Expr0> eval e1
    42
    *Expr0> eval e2
    False
    *Expr0> eval e3 5
    47
    \end{verbatim}

    But let us now try to define a |Show| instance.
    For |Fct|, this is not a problem:
-}

instance Show (Fct a b) where
  show Succ = "S"
  show EqZero = "isZero"
  show Add = "add"

showsExpr :: Expr a -> ShowS
showsExpr (Const c) = shows c
showsExpr (Apply f a) =
    ('(' :) . shows f . (' ' :) . showsExpr a . (')' :)

instance Show (Expr a) where
  showsPrec _ (Const c) = shows c
  showsPrec _ (Apply f a) =
    ('(' :) . shows f . (' ' :) . shows a . (')' :)

{- But we used to get a complaint about the |Const| alternative (then
   line 56) that documents that the constraint in the type of |Const|
   must have been ignored:

   \begin{verbatim}
       No instance for (Show a)
         arising from use of `shows' at Expr0.lhs:56:22-26
       Probable fix: add (Show a) to the type signature(s) for `showsExpr'
       In the definition of `showsExpr': showsExpr (Const c) = shows c
   \end{verbatim}

   But if we do that, the recursive call is of course still unsatisfied:
   \begin{verbatim}
       No instance for (Show a)
         arising from use of `showsExpr' at Expr0.lhs:65:34-42
       Probable fix: add (Show a) to the existential context for `Apply'
       In the first argument of `(.)', namely `showsExpr a'
       In the second argument of `(.)', namely `(showsExpr a) . ((')' :))'
       In the second argument of `(.)', namely
           `((' ' :)) . ((showsExpr a) . ((')' :)))'
   \end{verbatim}

   Following also the advice given in this last error message
   actually makes GHC accept this, and then we can say:

   \begin{verbatim}
   *Expr0> showsExpr e1 ""
   "(S 41)"
   *Expr0> showsExpr e2 ""
   "(isZero (S 41))"
   \end{verbatim}

   However, following this advice is counterintuitive
   and should be unnecessary
   since the |Show| instance for argument types
   is only ever used in the const case.
   We get:

   \begin{verbatim}
   *Expr0> showsExpr e3 ""

   <interactive>:1:0:
       No instance for (Show (Int -> Int))
         arising from use of `showsExpr' at <interactive>:1:0-8
       Probable fix: add an instance declaration for (Show (Int -> Int))
       In the definition of `it': it = showsExpr e3 ""
   \end{verbatim}

   But of course we would expect the following:

   \begin{verbatim}
   *Expr0> showsExpr e3 ""
   "(add (S 41))"
   \end{verbatim}


   \bigskip
   The error messages are almost the same
   if we define a |Show| instance directly
   (line 90 was the |Const| alternative):

   \begin{verbatim}
       Could not deduce (Show a) from the context (Show (Expr a))
         arising from use of `shows' at Expr0.lhs:90:26-30
       Probable fix: add (Show a) to the class or instance method `showsPrec'
   \end{verbatim}
-}