module Main ( main ) where
-import GHC.Exts
+import GHC.Exts hiding (IsList(..))
import GHC.Prim
import GHC.ST
import Control.Monad
import Control.Monad.Trans.State.Strict
import Control.Monad.Trans.Class
-import GHC.Exts
+import GHC.Exts hiding (IsList(..))
import GHC.ST hiding (liftST)
import Prelude hiding (length, read)
import qualified Prelude as P
module Main ( main ) where
import GHC.Word
-import GHC.Exts
+import GHC.Exts hiding (IsList(..))
import GHC.Prim
import GHC.ST
"AlternativeLayoutRuleTransitional",
"ExplicitNamespaces",
"TypeHoles",
+ "OverloadedLists",
"EmptyCase",
"AutoDeriveTypeable"]
-werror.hs:6:1:
- Warning: Top-level binding with no type signature: main :: IO ()
+werror.hs:6:1: Warning:
+ Top-level binding with no type signature: main :: IO ()
-werror.hs:7:13:
- Warning: This binding for `main' shadows the existing binding
- defined at werror.hs:6:1
+werror.hs:7:13: Warning:
+ This binding for `main' shadows the existing binding
+ defined at werror.hs:6:1
werror.hs:7:13: Warning: Defined but not used: `main'
werror.hs:10:1: Warning: Defined but not used: `f'
-werror.hs:10:1:
- Warning: Top-level binding with no type signature:
- f :: forall t a. [t] -> [a]
+werror.hs:10:1: Warning:
+ Top-level binding with no type signature:
+ f :: forall t t1. [t] -> [t1]
-werror.hs:10:1:
- Warning: Pattern match(es) are overlapped
- In an equation for `f': f [] = ...
+werror.hs:10:1: Warning:
+ Pattern match(es) are overlapped
+ In an equation for `f': f [] = ...
-werror.hs:10:1:
- Warning: Pattern match(es) are non-exhaustive
- In an equation for `f': Patterns not matched: _ : _
+werror.hs:10:1: Warning:
+ Pattern match(es) are non-exhaustive
+ In an equation for `f': Patterns not matched: _ : _
<no location info>:
Failing due to -Werror.
<interactive>:5:1:
- No instance for (Show (t -> a)) arising from a use of `print'
+ No instance for (Show (t -> t1)) arising from a use of `print'
In a stmt of an interactive GHCi command: print it
Breakpoint 0 activated at ../Test3.hs:2:18-31
Stopped at ../Test3.hs:2:18-31
-_result :: [a] = _
-f :: t -> a = _
+_result :: [t1] = _
+f :: t -> t1 = _
x :: t = _
xs :: [t] = [_]
Stopped at ../QSort.hs:(4,1)-(6,55)
-_result :: [a] = _
+_result :: [t] = _
Stopped at ../QSort.hs:5:16-51
_result :: [Integer] = _
a :: Integer = 1
<interactive>:6:1:
- No instance for (Show a) arising from a use of `print'
- Cannot resolve unknown runtime type `a'
+ No instance for (Show t1) arising from a use of `print'
+ Cannot resolve unknown runtime type `t1'
Use :print or :force to determine these types
- Relevant bindings include it :: a (bound at <interactive>:6:1)
+ Relevant bindings include it :: t1 (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'
In a stmt of an interactive GHCi command: print it
<interactive>:8:1:
- No instance for (Show a) arising from a use of `print'
- Cannot resolve unknown runtime type `a'
+ No instance for (Show t1) arising from a use of `print'
+ Cannot resolve unknown runtime type `t1'
Use :print or :force to determine these types
- Relevant bindings include it :: a (bound at <interactive>:8:1)
+ Relevant bindings include it :: t1 (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'
Stopped at ../Test3.hs:(1,1)-(2,31)
-_result :: [a] = _
+_result :: [t1] = _
Stopped at ../Test3.hs:2:18-31
-_result :: [a] = _
-f :: Integer -> a = _
+_result :: [t1] = _
+f :: Integer -> t1 = _
x :: Integer = 1
xs :: [Integer] = [2,3]
xs :: [Integer] = [2,3]
x :: Integer = 1
-f :: Integer -> a = _
-_result :: [a] = _
-y = (_t1::a)
+f :: Integer -> t1 = _
+_result :: [t1] = _
+y = (_t1::t1)
y = 2
xs :: [Integer] = [2,3]
x :: Integer = 1
Breakpoint 0 activated at ../QSort.hs:(4,1)-(6,55)
Stopped at ../QSort.hs:(4,1)-(6,55)
-_result :: [a] = _
+_result :: [t] = _
Stopped at ../QSort.hs:5:16-51
_result :: [Integer] = _
a :: Integer = 3
-9 : mymap (../Test3.hs:(1,1)-(2,31))
<end of history>
Logged breakpoint at ../Test3.hs:(1,1)-(2,31)
-_result :: [a]
-_result :: [a] = _
+_result :: [t1]
+_result :: [t1] = _
Logged breakpoint at ../Test3.hs:2:22-31
-_result :: [a]
-f :: t -> a
+_result :: [t1]
+f :: t -> t1
xs :: [t]
xs :: [t] = []
-f :: t -> a = _
-_result :: [a] = _
+f :: t -> t1 = _
+_result :: [t1] = _
*** Ignoring breakpoint
_result = []
Logged breakpoint at ../Test3.hs:2:18-20
-_result :: a
-f :: Integer -> a
+_result :: t1
+f :: Integer -> t1
x :: Integer
Logged breakpoint at ../Test3.hs:2:22-31
-_result :: [a]
+_result :: [t1]
-\r
-T5892a.hs:12:8: Warning:\r
- Fields of `Version' not initialised: Data.Version.versionTags\r
- In the expression: Version {..}\r
- In the expression: let versionBranch = [] in Version {..}\r
- In an equation for `foo':\r
- foo (Version {..}) = let versionBranch = [] in Version {..}\r
-\r
-<no location info>: \r
-Failing due to -Werror.\r
+
+T5892a.hs:12:8: Warning:
+ Fields of `Version' not initialised: Data.Version.versionTags
+ In the expression: Version {..}
+ In the expression: let versionBranch = [] in Version {..}
+ In an equation for `foo':
+ foo (Version {..}) = let versionBranch = ... in Version {..}
+
+<no location info>:
+Failing due to -Werror.
Exception when trying to run compile-time code:
TH_exn1.hs:(9,4)-(10,23): Non-exhaustive patterns in case
- Code: case reverse "no" of { [] -> return (GHC.Types.[]) }
+ Code: case reverse "no" of { [] -> return [] }
T2534.hs:3:19:
- Couldn't match expected type `a -> a -> b' with actual type `[a0]'
+ Couldn't match expected type `a -> a -> b' with actual type `[t0]'
Relevant bindings include
foo :: a -> a -> b (bound at T2534.hs:3:1)
In the second argument of `foldr', namely `[]'
-\r
-T5858.hs:11:7:\r
- No instance for (InferOverloaded ([a0], [a1]))\r
- arising from a use of `infer'\r
- The type variables `a0', `a1' are ambiguous\r
- Note: there is a potential instance available:\r
- instance t1 ~ String => InferOverloaded (t1, t1)\r
- -- Defined at T5858.hs:8:10\r
- In the expression: infer ([], [])\r
- In an equation for `foo': foo = infer ([], [])\r
+
+T5858.hs:11:7:
+ No instance for (InferOverloaded ([t0], [t1]))
+ arising from a use of `infer'
+ The type variables `t0', `t1' are ambiguous
+ Note: there is a potential instance available:
+ instance t1 ~ String => InferOverloaded (t1, t1)
+ -- Defined at T5858.hs:8:10
+ In the expression: infer ([], [])
+ In an equation for `foo': foo = infer ([], [])
tcfail001.hs:9:2:
- Couldn't match expected type `[t0] -> [a0]' with actual type `[a]'
+ Couldn't match expected type `[t0] -> [t1]' with actual type `[a]'
Relevant bindings include op :: [a] (bound at tcfail001.hs:9:2)
The equation(s) for `op' have one argument,
but its type `[a]' has none
tcfail012.hs:3:8:
- Couldn't match expected type `Bool' with actual type `[a0]'
+ Couldn't match expected type `Bool' with actual type `[t0]'
In the expression: []
In a pattern binding: True = []