Skip to content
Snippets Groups Projects
Commit f1557f3b authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

A ton of error message wibbles

Notably
 * Showing relevant bindings
 * Not suggesting add instance (Num T); see Trac #7222
parent 7095121c
No related branches found
No related tags found
No related merge requests found
Showing
with 153 additions and 141 deletions
......@@ -2,7 +2,5 @@
annfail05.hs:11:1:
No instance for (Data.Data.Data NoInstances)
arising from an annotation
Possible fix:
add an instance declaration for (Data.Data.Data NoInstances)
In the expression: NoInstances
In the annotation: {-# ANN f NoInstances #-}
......@@ -2,13 +2,10 @@
annfail08.hs:9:1:
No instance for (Data.Data.Data (a0 -> a0))
arising from an annotation
Possible fix:
add an instance declaration for (Data.Data.Data (a0 -> a0))
In the expression: (id + 1)
In the annotation: {-# ANN f (id + 1) #-}
annfail08.hs:9:15:
No instance for (Num (a0 -> a0)) arising from a use of `+'
Possible fix: add an instance declaration for (Num (a0 -> a0))
In the expression: (id + 1)
In the annotation: {-# ANN f (id + 1) #-}
T5380.hs:7:27:
Couldn't match expected type `not_bool' with actual type `Bool'
`not_bool' is a rigid type variable bound by
the type signature for
testB :: not_bool -> (() -> ()) -> () -> not_unit
at T5380.hs:6:10
In the expression: b
In the expression: proc () -> if b then f -< () else f -< ()
In an equation for `testB':
testB b f = proc () -> if b then f -< () else f -< ()
T5380.hs:7:34:
Couldn't match type `not_unit' with `()'
`not_unit' is a rigid type variable bound by
the type signature for
testB :: not_bool -> (() -> ()) -> () -> not_unit
at T5380.hs:6:10
Expected type: () -> not_unit
Actual type: () -> ()
In the expression: f
In the expression: proc () -> if b then f -< () else f -< ()
In an equation for `testB':
testB b f = proc () -> if b then f -< () else f -< ()
T5380.hs:7:27:
Couldn't match expected type `not_bool' with actual type `Bool'
`not_bool' is a rigid type variable bound by
the type signature for
testB :: not_bool -> (() -> ()) -> () -> not_unit
at T5380.hs:6:10
Relevant bindings include
testB :: not_bool -> (() -> ()) -> () -> not_unit
(bound at T5380.hs:7:1)
b :: not_bool (bound at T5380.hs:7:7)
In the expression: b
In the expression: proc () -> if b then f -< () else f -< ()
In an equation for `testB':
testB b f = proc () -> if b then f -< () else f -< ()
T5380.hs:7:34:
Couldn't match type `not_unit' with `()'
`not_unit' is a rigid type variable bound by
the type signature for
testB :: not_bool -> (() -> ()) -> () -> not_unit
at T5380.hs:6:10
Expected type: () -> not_unit
Actual type: () -> ()
Relevant bindings include
testB :: not_bool -> (() -> ()) -> () -> not_unit
(bound at T5380.hs:7:1)
In the expression: f
In the expression: proc () -> if b then f -< () else f -< ()
In an equation for `testB':
testB b f = proc () -> if b then f -< () else f -< ()
......@@ -3,7 +3,6 @@ T2851.hs:9:15:
No instance for (Show (F a))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Show (F a))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Show (D a))
......@@ -3,7 +3,6 @@ T3621.hs:21:21:
No instance for (MonadState state (State s))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (MonadState state (State s))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (MonadState state (WrappedState s))
......@@ -2,6 +2,8 @@
T5287.hs:6:29:
No instance for (A e oops)
arising from the 'deriving' clause of a data type declaration
The type variable `oops' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
......
drvfail-foldable-traversable1.hs:9:23:
No instance for (Functor Trivial1)
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Functor Trivial1)
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Traversable Trivial1)
drvfail-foldable-traversable1.hs:13:22:
No instance for (Foldable Trivial2)
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Foldable Trivial2)
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Traversable Trivial2)
drvfail-foldable-traversable1.hs:17:22:
Can't make a derived instance of `Foldable Infinite':
Constructor `Infinite' must not contain function types
In the data declaration for `Infinite'
drvfail-foldable-traversable1.hs:21:22:
Can't make a derived instance of `Traversable (Cont r)':
Constructor `Cont' must not contain function types
In the data declaration for `Cont'
drvfail-foldable-traversable1.hs:9:23:
No instance for (Functor Trivial1)
arising from the 'deriving' clause of a data type declaration
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Traversable Trivial1)
drvfail-foldable-traversable1.hs:13:22:
No instance for (Foldable Trivial2)
arising from the 'deriving' clause of a data type declaration
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Traversable Trivial2)
drvfail-foldable-traversable1.hs:17:22:
Can't make a derived instance of `Foldable Infinite':
Constructor `Infinite' must not contain function types
In the data declaration for `Infinite'
drvfail-foldable-traversable1.hs:21:22:
Can't make a derived instance of `Traversable (Cont r)':
Constructor `Cont' must not contain function types
In the data declaration for `Cont'
drvfail-functor2.hs:1:29: Warning:
-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
drvfail-functor2.hs:7:14:
Can't make a derived instance of `Functor InFunctionArgument':
Constructor `InFunctionArgument' must not use the type variable in a function argument
In the newtype declaration for `InFunctionArgument'
drvfail-functor2.hs:10:14:
Can't make a derived instance of `Functor OnSecondArg':
Constructor `OnSecondArg' must use the type variable only as the last argument of a data type
In the newtype declaration for `OnSecondArg'
drvfail-functor2.hs:15:14:
Cannot derive well-kinded instance of form `Functor (NoArguments ...)'
Class `Functor' expects an argument of kind `* -> *'
In the newtype declaration for `NoArguments'
drvfail-functor2.hs:20:14:
Can't make a derived instance of `Functor StupidConstraint':
Data type `StupidConstraint' must not have a class context (Eq a)
In the data declaration for `StupidConstraint'
drvfail-functor2.hs:26:14:
No instance for (Functor NoFunctor)
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Functor NoFunctor)
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Functor UseNoFunctor)
drvfail-functor2.hs:1:29: Warning:
-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
drvfail-functor2.hs:7:14:
Can't make a derived instance of `Functor InFunctionArgument':
Constructor `InFunctionArgument' must not use the type variable in a function argument
In the newtype declaration for `InFunctionArgument'
drvfail-functor2.hs:10:14:
Can't make a derived instance of `Functor OnSecondArg':
Constructor `OnSecondArg' must use the type variable only as the last argument of a data type
In the newtype declaration for `OnSecondArg'
drvfail-functor2.hs:15:14:
Cannot derive well-kinded instance of form `Functor (NoArguments ...)'
Class `Functor' expects an argument of kind `* -> *'
In the newtype declaration for `NoArguments'
drvfail-functor2.hs:20:14:
Can't make a derived instance of `Functor StupidConstraint':
Data type `StupidConstraint' must not have a class context (Eq a)
In the data declaration for `StupidConstraint'
drvfail-functor2.hs:26:14:
No instance for (Functor NoFunctor)
arising from the 'deriving' clause of a data type declaration
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Functor UseNoFunctor)
......@@ -3,7 +3,6 @@ drvfail001.hs:16:33:
No instance for (Show (f (f a)))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Show (f (f a)))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Show (SM f a))
......@@ -2,8 +2,9 @@
drvfail002.hs:19:23:
No instance for (X T c)
arising from the 'deriving' clause of a data type declaration
The type variable `c' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Possible fix:
add an instance declaration for (X T c)
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Show S)
......@@ -3,7 +3,6 @@ drvfail003.hs:16:56:
No instance for (Show (v (v a)))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Show (v (v a)))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Show (Square_ v w a))
......@@ -3,7 +3,6 @@ drvfail004.hs:8:12:
No instance for (Eq (Foo a b))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Eq (Foo a b))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Ord (Foo a b))
......@@ -3,7 +3,6 @@ drvfail007.hs:4:38:
No instance for (Eq (Int -> Int))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Eq (Int -> Int))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Eq Foo)
......@@ -3,7 +3,6 @@ drvfail012.hs:5:33:
No instance for (Eq (Ego a))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Eq (Ego a))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Ord (Ego a))
......@@ -3,16 +3,14 @@ drvfail013.hs:4:70:
No instance for (Eq (m (Maybe a)))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Eq (m (Maybe a)))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Eq (MaybeT m a))
drvfail013.hs:6:70:
No instance for (Eq (m (Maybe a)))
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Eq (m (Maybe a)))
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Eq (MaybeT' m a))
A.hs:6:15:
No instance for (Show (Fields v)) arising from a use of `show'
Possible fix: add an instance declaration for (Show (Fields v))
In the expression: show a
In an equation for `showField': showField a = show a
......@@ -5,6 +5,12 @@ T3169.hs:13:22:
bound by the instance declaration at T3169.hs:10:10-36
Expected type: Map a (Map b elt)
Actual type: Map (a, b) elt
Relevant bindings include
lookup :: (a, b) -> Map (a, b) elt -> Maybe elt
(bound at T3169.hs:12:3)
a :: a (bound at T3169.hs:12:11)
b :: b (bound at T3169.hs:12:13)
m :: Map (a, b) elt (bound at T3169.hs:12:17)
In the second argument of `lookup', namely `m'
In the expression: lookup a m :: Maybe (Map b elt)
In the expression:
......@@ -21,6 +27,11 @@ T3169.hs:13:22:
at T3169.hs:12:3
Expected type: Map a (Map b elt)
Actual type: Map (a, b) elt
Relevant bindings include
lookup :: (a, b) -> Map (a, b) elt -> Maybe elt
(bound at T3169.hs:12:3)
b :: b (bound at T3169.hs:12:13)
m :: Map (a, b) elt (bound at T3169.hs:12:17)
In the second argument of `lookup', namely `m'
In the expression: lookup a m :: Maybe (Map b elt)
In the expression:
......
rw.hs:14:47:
Couldn't match expected type `a' with actual type `Int'
`a' is a rigid type variable bound by
the type signature for writeInt :: T a -> IORef a -> IO ()
at rw.hs:12:12
In the second argument of `writeIORef', namely `(1 :: Int)'
In the expression: writeIORef ref (1 :: Int)
In a case alternative: ~(Li x) -> writeIORef ref (1 :: Int)
rw.hs:19:51:
Couldn't match type `a' with `Bool'
`a' is a rigid type variable bound by
the type signature for readBool :: T a -> IORef a -> IO ()
at rw.hs:16:12
Expected type: a -> Bool
Actual type: Bool -> Bool
In the second argument of `(.)', namely `not'
In the second argument of `(>>=)', namely `(print . not)'
In the expression: readIORef ref >>= (print . not)
rw.hs:14:47:
Couldn't match expected type `a' with actual type `Int'
`a' is a rigid type variable bound by
the type signature for writeInt :: T a -> IORef a -> IO ()
at rw.hs:12:12
Relevant bindings include
writeInt :: T a -> IORef a -> IO () (bound at rw.hs:13:1)
v :: T a (bound at rw.hs:13:10)
ref :: IORef a (bound at rw.hs:13:12)
In the second argument of `writeIORef', namely `(1 :: Int)'
In the expression: writeIORef ref (1 :: Int)
In a case alternative: ~(Li x) -> writeIORef ref (1 :: Int)
rw.hs:19:51:
Couldn't match type `a' with `Bool'
`a' is a rigid type variable bound by
the type signature for readBool :: T a -> IORef a -> IO ()
at rw.hs:16:12
Expected type: a -> Bool
Actual type: Bool -> Bool
Relevant bindings include
readBool :: T a -> IORef a -> IO () (bound at rw.hs:17:1)
v :: T a (bound at rw.hs:17:10)
ref :: IORef a (bound at rw.hs:17:12)
In the second argument of `(.)', namely `not'
In the second argument of `(>>=)', namely `(print . not)'
In the expression: readIORef ref >>= (print . not)
<interactive>:5:1:
No instance for (Show (t -> a)) arising from a use of `print'
Possible fix: add an instance declaration for (Show (t -> a))
In a stmt of an interactive GHCi command: print it
......@@ -3,6 +3,7 @@
No instance for (Show a) arising from a use of `print'
Cannot resolve unknown runtime type `a'
Use :print or :force to determine these types
Relevant bindings include it :: a (bound at <interactive>:6:1)
Note: there are several potential instances:
instance Show Double -- Defined in `GHC.Float'
instance Show Float -- Defined in `GHC.Float'
......@@ -15,6 +16,7 @@
No instance for (Show a) arising from a use of `print'
Cannot resolve unknown runtime type `a'
Use :print or :force to determine these types
Relevant bindings include it :: a (bound at <interactive>:8:1)
Note: there are several potential instances:
instance Show Double -- Defined in `GHC.Float'
instance Show Float -- Defined in `GHC.Float'
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment