diff --git a/ghc/compiler/tests/typecheck/Makefile b/ghc/compiler/tests/typecheck/Makefile deleted file mode 100644 index 56331779c65635a4ef07bc8617266e337cef23f7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/Makefile +++ /dev/null @@ -1,6 +0,0 @@ -TOP = ../../.. -include $(TOP)/mk/boilerplate.mk - -SUBDIRS = should_fail should_succeed stress - -include $(TOP)/mk/target.mk diff --git a/ghc/compiler/tests/typecheck/should_fail/Digraph.hs b/ghc/compiler/tests/typecheck/should_fail/Digraph.hs deleted file mode 100644 index a52d489b2c0b3aac79ed1e7652de93c3e9b3e03c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/Digraph.hs +++ /dev/null @@ -1,56 +0,0 @@ ---!!! trying to have a polymorphic type sig where inappropriate --- -module Digraph where - -data MaybeErr val err = Succeeded val | Failed err deriving () - -type Edge vertex = (vertex, vertex) -type Cycle vertex = [vertex] - -stronglyConnComp :: Eq vertex => [Edge vertex] -> [vertex] -> [[vertex]] - -stronglyConnComp es vs - = snd (span_tree (new_range reversed_edges) - ([],[]) - ( snd (dfs (new_range es) ([],[]) vs) ) - ) - where - -- *********** the offending type signature ************** - reversed_edges :: Eq v => [Edge v] - reversed_edges = map swap es - - -- WRONGOLA: swap :: Eq v => Edge v -> Edge v - swap (x,y) = (y, x) - - -- WRONGOLA?: new_range :: Eq v => [Edge v] -> v -> [v] - - new_range [] w = [] - new_range ((x,y):xys) w - = if x==w - then (y : (new_range xys w)) - else (new_range xys w) - - {- WRONGOLA?: - span_tree :: Eq v => (v -> [v]) - -> ([v], [[v]]) - -> [v] - -> ([v], [[v]]) - -} - - span_tree r (vs,ns) [] = (vs,ns) - span_tree r (vs,ns) (x:xs) - | x `elem` vs = span_tree r (vs,ns) xs - | otherwise = span_tree r (vs',(x:ns'):ns) xs - where - (vs',ns') = dfs r (x:vs,[]) (r x) - -dfs :: Eq v => (v -> [v]) - -> ([v], [v]) - -> [v] - -> ([v], [v]) - -dfs r (vs,ns) [] = (vs,ns) -dfs r (vs,ns) (x:xs) | x `elem` vs = dfs r (vs,ns) xs - | otherwise = dfs r (vs',(x:ns')++ns) xs - where - (vs',ns') = dfs r (x:vs,[]) (r x) diff --git a/ghc/compiler/tests/typecheck/should_fail/Digraph.stderr b/ghc/compiler/tests/typecheck/should_fail/Digraph.stderr deleted file mode 100644 index 03ae28a44cb6a317037800af3f052f456205aa87..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/Digraph.stderr +++ /dev/null @@ -1,58 +0,0 @@ - -Digraph.hs:19: A type signature is more polymorphic than the inferred type - Some type variables in the inferred type can't be forall'd, namely: - `v{-a13W-}' - Possible cause: the RHS mentions something subject to the monomorphism restriction - When checking signature for `reversed_edges' - In an equation for function `stronglyConnComp': - `stronglyConnComp es vs = PrelTup.snd - (span_tree - (new_range - reversed_edges) - (PrelBase.[], (PrelBase.[])) - (PrelTup.snd - (dfs (new_range - es) - (PrelBase.[], (PrelBase.[])) - vs))) - where - span_tree - r (vs, ns) PrelBase.[] - = (vs, (ns)) - span_tree - r (vs, ns) (x PrelBase.: xs) - | [x PrelList.elem vs] = - span_tree - r (vs, (ns)) xs - | [PrelBase.otherwise] = - span_tree - r - (vs', ((x PrelBase.: ns') PrelBase.: ns)) - xs - where - (vs', ns') - = dfs r - (x PrelBase.: vs, (PrelBase.[])) - (r x) - new_range - PrelBase.[] w - = PrelBase.[] - new_range - ((x, y) PrelBase.: xys) w - = if x PrelBase.== w then - (y - PrelBase.: (new_range - xys w)) - else - (new_range - xys w) - swap - (x, y) = (y, (x)) - reversed_edges :: - _forall_ [v] {PrelBase.Eq v} => [Edge v] - reversed_edges - = PrelBase.map - swap es' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/Makefile b/ghc/compiler/tests/typecheck/should_fail/Makefile deleted file mode 100644 index accc024441fdbb419ec62147438869f7a22fd329..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/Makefile +++ /dev/null @@ -1,34 +0,0 @@ -TOP = ../../../.. -include $(TOP)/mk/boilerplate.mk - -HS_SRCS = $(wildcard *.hs) - -SRC_RUNTEST_OPTS += -o1 $*.stdout -o2 $*.stderr -x 1 -HC_OPTS += -noC -ddump-tc -dppr-user - -%.o : %.hs - -%.o : %.hs - $(RUNTEST) $(HC) $(RUNTEST_OPTS) -- $(HC_OPTS) -c $< -o $@ -osuf $(subst .,,$(suffix $@)) - -all :: $(HS_OBJS) - -# Not all of them fail, allthough they're advertised as doing so.. -tcfail021_RUNTEST_OPTS = -x 0 -tcfail041_RUNTEST_OPTS = -x 0 -tcfail045_HC_OPTS = -fglasgow-exts -tcfail059_HC_OPTS = -hi -tcfail059_RUNTEST_OPTS = -x 0 -tcfail060_HC_OPTS = -hi -tcfail060_RUNTEST_OPTS = -x 0 -tcfail061_HC_OPTS = -hi -tcfail062_HC_OPTS = -hi -tcfail063_HC_OPTS = -hi -tcfail064_HC_OPTS = -hi -tcfail065_HC_OPTS = -hi -tcfail066_HC_OPTS = -hi -tcfail066_RUNTEST_OPTS = -x 0 -tcfail067_HC_OPTS = -hi -tcfail068_HC_OPTS = -fglasgow-exts - -include $(TOP)/mk/target.mk diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail001.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail001.hs deleted file mode 100644 index dafb83af1e76576970af2d51401a074644c59964..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail001.hs +++ /dev/null @@ -1,9 +0,0 @@ ---!!! This should fail with a type error: the instance method ---!!! has a function type when it should have the type [a]. -module Test where - -class A a where - op :: a - -instance (A a, A a) => A [a] where - op [] = [] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail001.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail001.stderr deleted file mode 100644 index 3a60d3776ce03c5b834662a79f0b8d5b34bc2504..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail001.stderr +++ /dev/null @@ -1,21 +0,0 @@ - -tcfail001.hs:9:warning: - Duplicate class assertion `[(`A', - `a'), - (`A', - `a')]' in context: - [(`A', - `a'), - (`A', - `a')] - -tcfail001.hs:9: Couldn't match the type - `PrelBase.[]' against `GHC.-> [t{-anj-}]' - Expected: `[a{-ani-}]' - Inferred: `[t{-anj-}] -> [t{-ank-}]' - In an equation for function `op': - `op PrelBase.[] - = PrelBase.[]' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail002.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail002.hs deleted file mode 100644 index b1fdd165b432034d39080247b7f991689f7a5ee3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail002.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldFail where - -c (x:y) = x -c z = z diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail002.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail002.stderr deleted file mode 100644 index 2848f77726c944495ebbefed9aa1b840cddf9f46..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail002.stderr +++ /dev/null @@ -1,10 +0,0 @@ - -tcfail002.hs:4: Cannot construct the infinite type (occur check) - `t{-amM-}' = `[t{-amM-}]' - Expected: `[t{-amM-}] -> t{-amM-}' - Inferred: `[t{-amM-}] -> [t{-amM-}]' - In an equation for function `c': - `c z = z' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail003.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail003.hs deleted file mode 100644 index 8458014c1bfffc1c7216bdcdf7633f226b3ac6de..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail003.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -(d:e) = [1,'a'] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail003.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail003.stderr deleted file mode 100644 index cdec675bec60fcd1610e0955374ccfa4e4970599..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail003.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail003.hs:3: No instance for: - `PrelBase.Num PrelBase.Char' - tcfail003.hs:3: - at an overloaded literal: 1 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail004.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail004.hs deleted file mode 100644 index 513680bd12263915c6e71b6c5a99e9cb3fd08e40..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail004.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -(f,g) = (1,2,3) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail004.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail004.stderr deleted file mode 100644 index b5ea7517ea6ae97143e3c19af96e553f0e5a27f4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail004.stderr +++ /dev/null @@ -1,11 +0,0 @@ - -tcfail004.hs:3: Couldn't match the type - `PrelTup.(,)' against `PrelTup.(,,) t{-aXz-}' - Expected: `(t{-aXt-}, t{-aXw-})' - Inferred: `(t{-aXz-}, t{-aXC-}, t{-aXF-})' - In a pattern binding: - (`f', `g') - = `(1, 2, 3)' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail005.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail005.hs deleted file mode 100644 index ca211e12165b7b388439710f57d4258703db4f49..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail005.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -(h:i) = (1,'a') diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail005.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail005.stderr deleted file mode 100644 index ebce13fa45a75c02e34d7f93aa4bd49a28c64d6a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail005.stderr +++ /dev/null @@ -1,11 +0,0 @@ - -tcfail005.hs:3: Couldn't match the type - `PrelBase.[]' against `PrelTup.(,) t{-aWN-}' - Expected: `[t{-aWJ-}]' - Inferred: `(t{-aWN-}, PrelBase.Char)' - In a pattern binding: - (`h' `PrelBase.:' `i') - = `(1, ('a'))' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail006.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail006.hs deleted file mode 100644 index 37fd1f9c358ffe3bfdb312e3de971275c384aa64..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail006.hs +++ /dev/null @@ -1,5 +0,0 @@ -module ShouldFail where - -(j,k) = case (if True then True else False) of - True -> (True,1) - False -> (1,True) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail006.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail006.stderr deleted file mode 100644 index 02d96f4464cae59a9f65ab883e00f06feb5ed843..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail006.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail006.hs:4: No instance for: - `PrelBase.Num PrelBase.Bool' - tcfail006.hs:4: - at an overloaded literal: 1 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail007.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail007.hs deleted file mode 100644 index ee24983aff055d3cbf490134545d5893a42ea489..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail007.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldFail where - -n x | True = x+1 - | False = True diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail007.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail007.stderr deleted file mode 100644 index cbf5b51eeb943a948f9fd7edf89ecf8906647180..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail007.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail007.hs:4: No instance for: - `PrelBase.Num PrelBase.Bool' - tcfail007.hs:4: - at a use of an overloaded identifier: `PrelBase.+' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail008.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail008.hs deleted file mode 100644 index dbc9d0c911f2eced74d5657601817361088c216d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail008.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -o = 1:2 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail008.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail008.stderr deleted file mode 100644 index ce2d768fe93674bd67b243de7a6d912ac114938a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail008.stderr +++ /dev/null @@ -1,18 +0,0 @@ - -tcfail008.hs:3: No instance for: - `PrelBase.Num [t{-aHf-}]' - tcfail008.hs:3: - at an overloaded literal: 2 - -tcfail008.hs:3: No instance for: - `PrelBase.Num [t{-aHf-}]' - tcfail008.hs:3: - at an overloaded literal: 2 - -tcfail008.hs:3: No instance for: - `PrelBase.Num [PrelBase.Int]' - tcfail008.hs:3: - at an overloaded literal: 2 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail009.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail009.hs deleted file mode 100644 index e8afa0fbf7ef80920ee84c0126247184f0195480..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail009.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -p = [(1::Int)..(2::Integer)] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail009.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail009.stderr deleted file mode 100644 index b293ca4dff4e7f0b8f78a40fda3dbfa4b5157ccb..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail009.stderr +++ /dev/null @@ -1,12 +0,0 @@ - -tcfail009.hs:3: Couldn't match the type - `PrelBase.Integer' against `PrelBase.Int' - Expected: `PrelBase.Int' - Inferred: `PrelBase.Integer' - In an arithmetic sequence: - `[(1 :: - PrelBase.Int) .. (2 :: - PrelBase.Integer)]' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail010.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail010.hs deleted file mode 100644 index 8b793355da2f1bb924ac2fffe1b52e117b0ded1d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail010.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -q = \ (y:z) -> z+2 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail010.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail010.stderr deleted file mode 100644 index 986ac2a21b32151cdd3bac51f6525a3e259bb2ac..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail010.stderr +++ /dev/null @@ -1,13 +0,0 @@ - -tcfail010.hs:3: No instance for: - `PrelBase.Num [t{-aHi-}]' - tcfail010.hs:3: - at a use of an overloaded identifier: `PrelBase.+' - -tcfail010.hs:3: No instance for: - `PrelBase.Num [t{-aHi-}]' - tcfail010.hs:3: - at a use of an overloaded identifier: `PrelBase.+' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail011.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail011.hs deleted file mode 100644 index 89f5c4bcd1eb1de97fb50cbc86ce45ff43ec29b1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail011.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -z = \y -> x x where x = y diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail011.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail011.stderr deleted file mode 100644 index 5cd8c3edb7bec7b231b5170119168e54149a2c89..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail011.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail011.hs:3: - Value not in scope: `y' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail012.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail012.hs deleted file mode 100644 index 67e5fa02568734c2edd84a23e3f73b7f0b42457a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail012.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -True = [] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail012.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail012.stderr deleted file mode 100644 index 2e525ce2fbee31c25786a2debf9328dac64d5da7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail012.stderr +++ /dev/null @@ -1,11 +0,0 @@ - -tcfail012.hs:3: Couldn't match the type - `PrelBase.Bool' against `[t{-amB-}]' - Expected: `PrelBase.Bool' - Inferred: `[t{-amB-}]' - In a pattern binding: - `PrelBase.True' - = `PrelBase.[]' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail013.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail013.hs deleted file mode 100644 index c9ccc52a64749f26873027ff8093d66331178f58..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail013.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldFail where - -f [] = 1 -f True = 2 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail013.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail013.stderr deleted file mode 100644 index 45fefc8b1ac2e69cb32556ad89b3400199618fc4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail013.stderr +++ /dev/null @@ -1,11 +0,0 @@ - -tcfail013.hs:4: Couldn't match the type - `[t{-aHg-}]' against `PrelBase.Bool' - Expected: `[t{-aHg-}] -> t{-aHi-}' - Inferred: `PrelBase.Bool -> t{-aHl-}' - In an equation for function `f': - `f PrelBase.True - = 2' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail014.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail014.hs deleted file mode 100644 index 7d9169936d6d19e7376ab7e230e255b5a8f06380..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail014.hs +++ /dev/null @@ -1,5 +0,0 @@ -module ShouldFail where - -f x = g+1 - where g y = h+2 - where h z = z z diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail014.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail014.stderr deleted file mode 100644 index 2515260d895ebfba1825648b24345a9d9ceae970..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail014.stderr +++ /dev/null @@ -1,21 +0,0 @@ - -tcfail014.hs:5: Cannot construct the infinite type (occur check) - `o{-aHw-}' = `o{-aHw-} -> o{-aIe-}' - Expected: `o{-aHw-}' - Inferred: `o{-aHw-} -> o{-aIe-}' - In the first argument of `z', namely - `z' - In an equation for function `h': - `h z = z z' - In an equation for function `g': - `g y = h PrelBase.+ 2 - where - h z = z z' - -tcfail014.hs:5: No instance for: - `PrelBase.Num (t{-aHZ-} -> t{-aI0-})' - tcfail014.hs:5: - at a use of an overloaded identifier: `PrelBase.+' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail015.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail015.hs deleted file mode 100644 index ae929e397379d8ac6bc641319d09336182d829b4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail015.hs +++ /dev/null @@ -1,9 +0,0 @@ -module ShouldFail where - -data AList a = ANull | ANode a (AList a) - -type IntList = AList Int - -g (ANull) = 2 -g (ANode b (ANode c d)) | b = c+1 - | otherwise = 4 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail015.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail015.stderr deleted file mode 100644 index 5ae8866d5cb4373b44bfe5ba4b2698d2e62965a5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail015.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail015.hs:7: No instance for: - `PrelBase.Num PrelBase.Bool' - tcfail015.hs:7: - at an overloaded literal: 2 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail016.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail016.hs deleted file mode 100644 index 2dfd4a50e0a558c14b5b6cf219cc06191303584a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail016.hs +++ /dev/null @@ -1,9 +0,0 @@ -module ShouldFail where - -type AnnExpr a = (a,Expr a) - -data Expr a = Var [Char] - | App (AnnExpr a) (AnnExpr a) - -g (Var name) = [name] -g (App e1 e2) = (g e1)++(g e2) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail016.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail016.stderr deleted file mode 100644 index 56889997069dec44c07c43d892ed75b1160afc36..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail016.stderr +++ /dev/null @@ -1,15 +0,0 @@ - -tcfail016.hs:9: Couldn't match the type - `PrelTup.(,) a{-aX1-}' against `Expr' - Expected: `Expr a{-aWV-}' - Inferred: `AnnExpr a{-aX1-}' - In the first argument of `g', namely - `e1' - In the first argument of `PrelBase.++', namely - (`g' `e1') - In an equation for function `g': - `g (App e1 e2) - = (g e1) PrelBase.++ (g e2)' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail017.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail017.hs deleted file mode 100644 index db3215dc196a306fe3b4ad036b54c59d4fc7719e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail017.hs +++ /dev/null @@ -1,13 +0,0 @@ - -module ShouldFail where - -class C a where - op1 :: a -> a - -class (C a) => B a where - op2 :: a -> a -> a - -instance (B a) => B [a] where - op2 xs ys = xs - - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail017.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail017.stderr deleted file mode 100644 index 4d854ce72a8f657c8c7cd0ac56322f6a486db45a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail017.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail017.hs:11: No instance for: - `C [a{-anj-}]' - tcfail017.hs:11: - in an instance declaration - When checking superclass constraints of an instance declaration - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail018.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail018.hs deleted file mode 100644 index d91306ac553b6454726b08dbfd5264c4e34d7ffa..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail018.hs +++ /dev/null @@ -1,5 +0,0 @@ - - -module ShouldSucc where - -(a:[]) = 1 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail018.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail018.stderr deleted file mode 100644 index df711e5e067bd65ad16c2b95d040673073df5e2d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail018.stderr +++ /dev/null @@ -1,13 +0,0 @@ - -tcfail018.hs:5: No instance for: - `PrelBase.Num [t{-aHg-}]' - tcfail018.hs:5: - at an overloaded literal: 1 - -tcfail018.hs:5: No instance for: - `PrelBase.Num [t{-aHg-}]' - tcfail018.hs:5: - at an overloaded literal: 1 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail019.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail019.hs deleted file mode 100644 index b3da9cdebcba0b097cb993b191358b337fc8ec1c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail019.hs +++ /dev/null @@ -1,21 +0,0 @@ - -module P where - -class A a where - p1 :: a -> a - p2 :: a -> a -> a - -class (A b) => B b where - p3 :: b - p4 :: b -> b - -class (A c) => C c where - p5 :: c -> c - p6 :: c -> Int - -class (B d,C d) => D d where - p7 :: d -> d - -instance D [a] where - p7 l = [] - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail019.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail019.stderr deleted file mode 100644 index 58cae59b350d69e3f952b59b2663d8bc8034f3fd..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail019.stderr +++ /dev/null @@ -1,27 +0,0 @@ - -tcfail019.hs:20: No instance for: - `B [a{-anU-}]' - tcfail019.hs:20: - in an instance declaration - When checking methods of an instance declaration - -tcfail019.hs:20: No instance for: - `C [a{-anU-}]' - tcfail019.hs:20: - in an instance declaration - When checking methods of an instance declaration - -tcfail019.hs:20: No instance for: - `B [a{-anU-}]' - tcfail019.hs:20: - in an instance declaration - When checking superclass constraints of an instance declaration - -tcfail019.hs:20: No instance for: - `C [a{-anU-}]' - tcfail019.hs:20: - in an instance declaration - When checking superclass constraints of an instance declaration - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail020.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail020.hs deleted file mode 100644 index 9697838fb1c2c396fcad4d38a065d7c0be2e21bd..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail020.hs +++ /dev/null @@ -1,17 +0,0 @@ - -module P where - -class A a where - p1 :: a -> a - p2 :: a -> a -> a - -class (A b) => B b where - p3 :: b - -instance (A a) => B [a] where - p3 = [] - -data X = XC --, causes stack dump - ---instance B Bool where --- p3 = True diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail020.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail020.stderr deleted file mode 100644 index ef738f036a6b45a6882602d752c384a653fe0e99..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail020.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail020.hs:12: No instance for: - `A [a{-aGH-}]' - tcfail020.hs:12: - in an instance declaration - When checking superclass constraints of an instance declaration - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail021.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail021.hs deleted file mode 100644 index f6758a1b2beba4443be009acd8eb95e7dcc4e008..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail021.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -f x x = 2 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail021.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail021.stderr deleted file mode 100644 index 1e8c603b17ed3b59401c4f53f37534532796b26b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail021.stderr +++ /dev/null @@ -1,17 +0,0 @@ - - ---================================================================================ -Typechecked: -AbsBinds -[`t{-aHp-}', `t{-aHr-}', `t{-aHm-}'] -[`d.Num'] -[([`t{-aHp-}', `t{-aHr-}', `t{-aHm-}'], `f', `f')] - `fromInt' = - `PrelBase.fromInt' - `t{-aHm-}' - `d.Num' - `lit' = - `fromInt' - `PrelBase.I#' - 2# - `f' `x' `x' = `lit' diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail022.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail022.hs deleted file mode 100644 index d5e51ed4fdc639ee97e4829c740373594c0f6597..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail022.hs +++ /dev/null @@ -1,6 +0,0 @@ - -f x = 2 - -g x = 6 - -f x = 3 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail022.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail022.stderr deleted file mode 100644 index 43d06b7c23dc75f110a07315c46a04d591b78175..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail022.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail022.hs:2: - Conflicting exports for local name: f - module Main - module Main - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail023.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail023.hs deleted file mode 100644 index ae2a3564610a6f4922a3aec719673d37046a7e05..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail023.hs +++ /dev/null @@ -1,13 +0,0 @@ - -data B = C - -class A a where - op :: a -> a - -instance A B where - op C = True - -instance A B where - op C = True - - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail023.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail023.stderr deleted file mode 100644 index 1626fb7129ae8ca43ea5a94f18e03bd8b0c7dee3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail023.stderr +++ /dev/null @@ -1,27 +0,0 @@ - -tcfail023.hs:2: Duplicate or overlapping instance declarations - Class `A' type `B' - at tcfail023.hs:8 and tcfail023.hs:11 - -tcfail023.hs:2: Duplicate or overlapping instance declarations - Class `A' type `B' - at tcfail023.hs:8 and tcfail023.hs:11 - -tcfail023.hs:11: Couldn't match the type - `B' against `PrelBase.Bool' - Expected: `B' - Inferred: `PrelBase.Bool' - In an equation for function `op': - `op C = PrelBase.True' - -tcfail023.hs:8: Couldn't match the type - `B' against `PrelBase.Bool' - Expected: `B' - Inferred: `PrelBase.Bool' - In an equation for function `op': - `op C = PrelBase.True' - -tcfail023.hs:2: Module Main must include a definition for `Main.main' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail024.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail024.hs deleted file mode 100644 index 3dc567811b692df6f61468baea88cfb3bb0c2414..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail024.hs +++ /dev/null @@ -1,4 +0,0 @@ - -data F = A | B - -data G = A | C diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail024.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail024.stderr deleted file mode 100644 index a48311261c0778d133d03130611d25ada75b532f..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail024.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -tcfail024.hs:2: Module Main must include a definition for `Main.main' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail025.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail025.hs deleted file mode 100644 index b342618e1551036e890d5e9cd6d3d6fdc146f2bb..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail025.hs +++ /dev/null @@ -1,6 +0,0 @@ - -type A = Int - -type B = Bool - -type A = [Bool] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail025.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail025.stderr deleted file mode 100644 index 6a0f830cc4c1d692981d444b0029e42a590a90cc..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail025.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail025.hs:2: - Conflicting exports for local name: A - module Main - module Main - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail026.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail026.hs deleted file mode 100644 index 725b0d1632997071815ffff631473c8746e4e672..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail026.hs +++ /dev/null @@ -1,9 +0,0 @@ - -class A a where - op1 :: a - -class B a where - op2 :: b -> b - -class A a where - op3 :: a diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail026.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail026.stderr deleted file mode 100644 index 23e90f7ae429efb8d5dec5a8a59d7a4b848ab88c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail026.stderr +++ /dev/null @@ -1,13 +0,0 @@ - -tcfail026.hs:2: - Conflicting exports for local name: A - module Main - module Main - -tcfail026.hs:6: - Class type variable ``a'' does not appear in method signature: - op2 :: - `b' -> `b' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail027.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail027.hs deleted file mode 100644 index b80430ba26e7279ee5836342c625fa135b05119e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail027.hs +++ /dev/null @@ -1,7 +0,0 @@ ---!!! tests for CycleErr in classes - -class (B a) => A a where - op1 :: a -> a - -class (A a) => B a where - op2 :: a -> a -> a diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail027.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail027.stderr deleted file mode 100644 index 617dd4b68b219cd86cb7589eace03af38331c7ca..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail027.stderr +++ /dev/null @@ -1,7 +0,0 @@ - -tcfail027.hs:3: Cycle in class declarations ... - `A' tcfail027.hs:4 - `B' tcfail027.hs:7 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail028.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail028.hs deleted file mode 100644 index 8e8c2946a0841c3f383033a36afb084fac2ddd2b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail028.hs +++ /dev/null @@ -1,3 +0,0 @@ ---!!! tests for ArityErr - -data A a b = B (A a) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail028.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail028.stderr deleted file mode 100644 index d61467c6b341918524cf7b96f571b98b84abced7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail028.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail028.hs:4: Couldn't match the kind - ka2865 -> * against * - When unifying two kinds - ka2865 -> * and * - In the data declaration for `A' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail029.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail029.hs deleted file mode 100644 index 4b8f2c6c891bad4a96f06daf0b51249218ce595c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail029.hs +++ /dev/null @@ -1,6 +0,0 @@ ---!!! tests for InstOpErr -module ShouldFail where - -data Foo = Bar | Baz - -f x = x > Bar diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail029.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail029.stderr deleted file mode 100644 index 26cac09bbcb300694aa2444d2cf45a4bee701d20..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail029.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail029.hs:6: No instance for: - `PrelBase.Ord Foo' - tcfail029.hs:6: - at a use of an overloaded identifier: `PrelBase.>' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail030.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail030.hs deleted file mode 100644 index 2aa8659940a0f160e271d7ebfab100fddc33a7f8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail030.hs +++ /dev/null @@ -1 +0,0 @@ ---!!! empty file diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail030.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail030.stderr deleted file mode 100644 index 3dbe460a581cd5cd4dd3ede626c7d7b5f016837a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail030.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -tcfail030.hs:0: Module Main must include a definition for `Main.main' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail031.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail031.hs deleted file mode 100644 index 6b9a0de12b89ec8db84514e11875502f81b3cfcc..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail031.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -f x = if 'a' then 1 else 2 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail031.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail031.stderr deleted file mode 100644 index a50843e3c9f4cc7227564295e6e9f28b3601d14b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail031.stderr +++ /dev/null @@ -1,12 +0,0 @@ - -tcfail031.hs:3: Couldn't match the type - `PrelBase.Bool' against `PrelBase.Char' - Expected: `PrelBase.Bool' - Inferred: `PrelBase.Char' - In a predicate expression: - `'a'' - In an equation for function `f': - `f x = if 'a' then 1 else 2' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail032.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail032.hs deleted file mode 100644 index 0e8884da3fe754d3f3deb3ec6f7f6c64e01f0b09..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail032.hs +++ /dev/null @@ -1,16 +0,0 @@ -{- This test gives the following not-very-wonderful error message. - - "tc_sig.hs", line 3: Type signature does not match the inferred type: - Signature: t76 -> Int - Inferred type: t75 - -It *is* an error, because x does not have the polytype - forall a. Eq a => a -> Int -becuase it is monomorphic, but the error message isn't very illuminating. --} - -module TcSig where - -f x = (x :: (Eq a) => a -> Int) - - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail032.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail032.stderr deleted file mode 100644 index 7229913fa8ae2fbfc1d7389ab058158a4efbf147..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail032.stderr +++ /dev/null @@ -1,11 +0,0 @@ - -tcfail032.hs:14: A type signature is more polymorphic than the inferred type - Some type variables in the inferred type can't be forall'd, namely: - `a{-aG1-}' - Possible cause: the RHS mentions something subject to the monomorphism restriction - In an expression with a type signature: - `x :: - _forall_ [a] {PrelBase.Eq a} => a -> PrelBase.Int' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail033.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail033.hs deleted file mode 100644 index fdc0aff8ed5a1ce0d349e6dfdaa51148149a8bf1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail033.hs +++ /dev/null @@ -1,4 +0,0 @@ --- from Jon Hill -module ShouldFail where - -buglet = [ x | (x,y) <- buglet ] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail033.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail033.stderr deleted file mode 100644 index 72b2c88befa13e5e2ded7d98a1926bd80a3c8901..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail033.stderr +++ /dev/null @@ -1,12 +0,0 @@ - -tcfail033.hs:4: Cannot construct the infinite type (occur check) - `t{-aKn-}' = `(t{-aKn-}, t{-aKq-})' - Expected: `a{-aKs-} (t{-aKn-}, t{-aKq-})' - Inferred: `a{-aKs-} t{-aKn-}' - In a pattern binding: - `buglet' - = `[ x | - (x, y) <- buglet ]' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail034.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail034.hs deleted file mode 100644 index 82aa18b41872cc2446c25314d973d24f73f7daef..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail034.hs +++ /dev/null @@ -1,39 +0,0 @@ -{- -From: Jon Hill <hilly@dcs.qmw.ac.uk@jess.gla.ac.uk@pp.dcs.glasgow.ac.uk> -To: glasgow-haskell-bugs -Subject: Unfriendly error message -Date: Thu, 25 Jun 1992 09:22:55 +0100 - -Hello again, - -I came across a rather nasty error message when I gave a function an -incorrect type signature (the context is wrong). I can remember reading -in the source about this problem - I just thought I'd let you know anyway :-) --} -module ShouldSucceed where - - -test::(Num a, Eq a) => a -> Bool -test x = (x `mod` 3) == 0 - -{- -granite> ndph bug002.ldh -Data Parallel Haskell Compiler, version 0.01 (Glasgow 0.07) - - -"<unknown>", line <unknown>: Cannot express dicts in terms of dictionaries available: -dicts_encl: - "<built-in>", line : dict.87 :: <Num a> - "<built-in>", line : dict.88 :: <Eq a> -dicts_encl': - "<built-in>", line : dict.87 :: <Num a> - "<built-in>", line : dict.88 :: <Eq a> -dicts: - "<built-in>", line : dict.87 :: <Num a> - "<built-in>", line : dict.88 :: <Eq a> -super_class_dict: "<built-in>", line : dict.80 :: <Integral a> -Fail: Compilation errors found - -dph: execution of the Haskell compiler had trouble - --} diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail034.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail034.stderr deleted file mode 100644 index ec4adbd32a49931af2b3e58da4a441f22eac73ad..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail034.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail034.hs:13: tcfail034.hs:17: Context required by inferred type, but missing on a type signature: - at a use of an overloaded identifier: `PrelNum.mod' - `PrelNum.Integral' `a{-aZO-}' - When checking signature(s) for: `test' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail035.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail035.hs deleted file mode 100644 index a12908ee5a246ed9f0ede3b95b7a6baa2aba0d6f..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail035.hs +++ /dev/null @@ -1,9 +0,0 @@ ---!!! instances with empty where parts: duplicate --- -module M where - -data NUM = ONE | TWO -instance Num NUM -instance Num NUM -instance Eq NUM -instance Show NUM diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail035.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail035.stderr deleted file mode 100644 index e94c4d02298d2812c930175f253d9e428262eea7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail035.stderr +++ /dev/null @@ -1,11 +0,0 @@ - -tcfail035.hs:3: Duplicate or overlapping instance declarations - Class `PrelBase.Num' type `NUM' - at tcfail035.hs:6 and tcfail035.hs:7 - -tcfail035.hs:3: Duplicate or overlapping instance declarations - Class `PrelBase.Num' type `NUM' - at tcfail035.hs:6 and tcfail035.hs:7 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail036.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail036.hs deleted file mode 100644 index eb9f9aff85b8767fb1670d1160385c4dc7559f46..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail036.hs +++ /dev/null @@ -1,10 +0,0 @@ ---!!! prelude class name in an instance-tycon position --- -module M where - -data NUM = ONE | TWO -instance Num NUM - where ONE + ONE = TWO -instance Num NUM -instance Eq Num ---instance Text Num diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail036.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail036.stderr deleted file mode 100644 index f374fcb967137e124f1c63238f48cecd947894c7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail036.stderr +++ /dev/null @@ -1,61 +0,0 @@ - -tcfail036.hs:9: Class used as a type constructor: `PrelBase.Num' - -tcfail036.hs:3: Duplicate or overlapping instance declarations - Class `PrelBase.Num' type `NUM' - at tcfail036.hs:7 and tcfail036.hs:8 - -tcfail036.hs:3: Duplicate or overlapping instance declarations - Class `PrelBase.Num' type `NUM' - at tcfail036.hs:7 and tcfail036.hs:8 - -tcfail036.hs:8: No instance for: - `PrelBase.Eq NUM' - tcfail036.hs:8: - in an instance declaration - When checking methods of an instance declaration - -tcfail036.hs:8: No instance for: - `PrelBase.Show NUM' - tcfail036.hs:8: - in an instance declaration - When checking methods of an instance declaration - -tcfail036.hs:8: No instance for: - `PrelBase.Eq NUM' - tcfail036.hs:8: - in an instance declaration - When checking superclass constraints of an instance declaration - -tcfail036.hs:8: No instance for: - `PrelBase.Show NUM' - tcfail036.hs:8: - in an instance declaration - When checking superclass constraints of an instance declaration - -tcfail036.hs:7: No instance for: - `PrelBase.Eq NUM' - tcfail036.hs:7: - in an instance declaration - When checking methods of an instance declaration - -tcfail036.hs:7: No instance for: - `PrelBase.Show NUM' - tcfail036.hs:7: - in an instance declaration - When checking methods of an instance declaration - -tcfail036.hs:7: No instance for: - `PrelBase.Eq NUM' - tcfail036.hs:7: - in an instance declaration - When checking superclass constraints of an instance declaration - -tcfail036.hs:7: No instance for: - `PrelBase.Show NUM' - tcfail036.hs:7: - in an instance declaration - When checking superclass constraints of an instance declaration - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail037.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail037.hs deleted file mode 100644 index 07b308b98cc357bc8befc1f494d4abf435f41c93..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail037.hs +++ /dev/null @@ -1,11 +0,0 @@ ---!!! PreludeCore entities cannot be redefined at the top-level --- -module M where - -data NUM = ONE | TWO - -f a b = a + b -f :: NUM -> NUM -> NUM - -ONE + ONE = TWO - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail037.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail037.stderr deleted file mode 100644 index b18a95d9985b0faac5d400127dee162d3f0e4722..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail037.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail037.hs:3: - Conflicting definitions for: `+' - Defined at tcfail037.hs:10 - Imported from Prelude at tcfail037.hs:3 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail038.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail038.hs deleted file mode 100644 index 7d03529a4e787831c6818b2f566c6b399c762fd9..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail038.hs +++ /dev/null @@ -1,11 +0,0 @@ ---!!! duplicate class-method declarations - -module M where - -data NUM = ONE | TWO -instance Eq NUM where - a == b = True - a /= b = False - a == b = False - a /= b = True - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail038.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail038.stderr deleted file mode 100644 index 84e74e123d47108756b2f5c7f8b47bd58d1d6737..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail038.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail038.hs:8: - Conflicting definitions for `/=' in the bindings in an instance declaration - -tcfail038.hs:7: - Conflicting definitions for `==' in the bindings in an instance declaration - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail039.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail039.hs deleted file mode 100644 index f0df10c28712da89ec5cab0205395e2d552c2ec5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail039.hs +++ /dev/null @@ -1,12 +0,0 @@ ---!!! bogus re-use of prelude class-method name (==) --- -module M where - -data NUM = ONE | TWO -class EQ a where - (==) :: a -> a -> Bool - -instance EQ NUM --- a /= b = False --- a == b = True --- a /= b = False diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail039.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail039.stderr deleted file mode 100644 index 574b8888b3306fa5614a19a4fe0519dd051015f9..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail039.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -tcfail039.hs:3: - Conflicting definitions for: `==' - Defined at tcfail039.hs:7 - Imported from Prelude at tcfail039.hs:3 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail040.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail040.hs deleted file mode 100644 index c611518ee4ab606bea2dec148d1174f4db5ed505..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail040.hs +++ /dev/null @@ -1,29 +0,0 @@ ---!!! instances of functions --- -module M where - -data NUM = ONE | TWO - -class EQ a where - (===) :: a -> a -> Bool - -class ORD a where - (<<) :: a -> a -> Bool - a << b = True - -instance EQ (a -> b) where - f === g = True - -instance ORD (a -> b) - -f = (<<) === (<<) ---f :: (EQ a,Num a) => a -> a -> Bool - - -{- -instance EQ NUM where --- a /= b = False - a === b = True --- a /= b = False - --} diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail040.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail040.stderr deleted file mode 100644 index 51d6bfd51a6b4b9437533c24f0449ebd7fdf41a1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail040.stderr +++ /dev/null @@ -1,7 +0,0 @@ - -tcfail040.hs:3: tcfail040.hs:19: Ambiguous overloading: - at a use of an overloaded identifier: `<<' - `ORD' `a{-aGQ-}' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail041.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail041.hs deleted file mode 100644 index 542c400a865356e696d51f2c74c1e4eabfc5c909..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail041.hs +++ /dev/null @@ -1,61 +0,0 @@ -{- -To: Lennart Augustsson <augustss@cs.chalmers.se> -Cc: partain@dcs.gla.ac.uk, John Peterson (Yale) <peterson-john@cs.yale.edu>, - simonpj@dcs.gla.ac.uk -Subject: Type checking matter -Date: Fri, 23 Oct 92 15:28:38 +0100 -From: Simon L Peyton Jones <simonpj@dcs.gla.ac.uk> - - -I've looked at the enclosed again. It seems to me that -since "s" includes a recursive call to "sort", inside the body -of "sort", then "sort" is monomorphic, and hence so is "s"; -hence the type signature (which claims full polymorphism) is -wrong. - -[Lennart says he can't see any free variables inside "s", but there -is one, namely "sort"!] - -Will: one for the should-fail suite? - -Simon - - -------- Forwarded Message - - -From: Lennart Augustsson <augustss@cs.chalmers.se> -To: partain -Subject: Re: just to show you I'm a nice guy... -Date: Tue, 26 May 92 17:30:12 +0200 - -> Here's a fairly simple module from our compiler, which includes what -> we claim is an illegal type signature (grep ILLEGAL ...). -> Last time I checked, hbc accepted this module. - -Not that I don't believe you, but why is this illegal? -As far as I can see there are no free variables in the function s, -which makes me believe that it can typechecked like a top level -definition. And for a top level defn the signature should be -all right. - - -- Lennart -- ------- End of forwarded message ------- --} -module ShouldFail where - -sort :: Ord a => [a] -> [a] -sort xs = s xs (length xs) - where - s :: Ord b => [b] -> Int -> [b] -- This signature is WRONG - s xs k = if k <= 1 then xs - else merge (sort ys) (sort zs) - where (ys,zs) = init_last xs (k `div` (2::Int)) - --- Defns of merge and init_last are just dummies with the correct types -merge :: Ord a => [a] -> [a] -> [a] -merge xs ys = xs - -init_last :: [a] -> Int -> ([a],[a]) -init_last a b = (a,a) - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail041.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail041.stderr deleted file mode 100644 index c2e2b69fc2e8570e92099ed5852527b278d3539c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail041.stderr +++ /dev/null @@ -1,87 +0,0 @@ - - ---================================================================================ -Typechecked: -`d.Ord' = - `PrelBase.$d6' -`<=' = - `PrelBase.<=' - `PrelBase.Int' - `d.Ord' -`d.Num' = - `PrelBase.$d3' -`fromInt' = - `PrelBase.fromInt' - `PrelBase.Int' - `d.Num' -`lit' = - `fromInt' - `PrelBase.I#' - 1# -`d.Integral' = - `PrelNum.$d36' -`div' = - `PrelNum.div' - `PrelBase.Int' - `d.Integral' -`fromInt' = - `fromInt' -`lit' = - `fromInt' - `PrelBase.I#' - 2# -AbsBinds -[`a{-a121-}'] -[] -[([`a{-a121-}'], `init_last', `init_last')] - `init_last' - `a' `b' = `(a, a)' -AbsBinds -[`a{-a12a-}'] -[`d.Ord'] -[([`a{-a12a-}'], `merge', `merge')] - `merge' - `xs' `ys' - = `xs' -AbsBinds [`a{-a12l-}'] [`d.Ord'] [([`a{-a12l-}'], `sort', `sort')] - `d.Ord' = - `d.Ord' - `sort' - `xs' = `s xs - PrelList.length - a{-a12l-} - xs' - where - AbsBinds [`b{-a12s-}'] [`d.Ord'] [([`b{-a12s-}'], `s', `s')] - `d.Ord' = - `d.Ord' - `merge' = - `merge' - `b{-a12s-}' - `d.Ord' - `d.Ord' = - `d.Ord' - `sort' = - `sort' - `b{-a12s-}' - `d.Ord' - `sort' = - `sort' - `s' `xs' `k' - = `if k <= lit then - xs - else - merge - sort - ys - sort - zs' - where - AbsBinds [] [] [([], `ys', `ys'), ([], `zs', `zs')] - (`ys', `zs') - = `init_last - b{-a12s-} - xs k div lit' - `s' = - `s' `a{-a12l-}' - `d.Ord' diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail042.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail042.hs deleted file mode 100644 index 37c24936a99607b27e61485cfbffe02d840e60e8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail042.hs +++ /dev/null @@ -1,28 +0,0 @@ ---!!! weird class/instance examples off the haskell list --- - -class Foo a where foo :: a -> a -class Foo a => Bar a where bar :: a -> a - - -instance Num a => Foo [a] where - foo [] = [] - foo (x:xs) = map (x+) xs - - -instance (Eq a, Show a) => Bar [a] where - bar [] = [] - bar (x:xs) = foo xs where u = x==x - v = show x - ------------------------------------------- - -{- -class Foo a => Bar2 a where bar2 :: a -> a - -instance (Eq a, Show a) => Foo [a] - -instance Num a => Bar2 [a] - -data X a = X a --} diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail042.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail042.stderr deleted file mode 100644 index 6bc85529f2de68ca31d4ec55169132619b48c637..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail042.stderr +++ /dev/null @@ -1,10 +0,0 @@ - -tcfail042.hs:16: tcfail042.hs:16: Context required by inferred type, but missing on a type signature: - in an instance declaration - `PrelBase.Num' `a{-aN7-}' - When checking superclass constraints of an instance declaration - -tcfail042.hs:4: Module Main must include a definition for `Main.main' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail043.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail043.hs deleted file mode 100644 index cc1983be5bad77fc31e31f45c96a7f98443f0cd0..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail043.hs +++ /dev/null @@ -1,222 +0,0 @@ --- The translation of this program should assign only one dictionary to --- the function search (an Ord dictionary). Instead, it assigns two. --- The output produced currently displays this. - --- 10/12/92: This program is actually erroneous. The pattern-binding for --- search falls under the monomorphism restriction, and there is no --- call to search which might fix its type. So there should be a complaint. --- But the actual error message is horrible: --- --- "bug001.hs", line 26: Ambiguous overloading: --- class "Ord_", type "a" (at a use of an overloaded identifier: gt) --- class "Eq_", type "a" (at a use of an overloaded identifier: eq) - - - -class Eq_ a where - eq :: a -> a -> Bool - -instance Eq_ Int where - eq = eqIntEq - -instance (Eq_ a) => Eq_ [a] where - eq = \ xs ys -> - if (null xs) - then (null ys) - else if (null ys) - then False - else and (eq (hd xs) (hd ys)) (eq (tl xs) (tl ys)) - -class (Eq_ a) => Ord_ a where - gt :: a -> a -> Bool - -instance Ord_ Int where - gt = ordIntGt - -search - = \ a bs -> if gt (hd bs) a - then False - else if eq a (hd bs) then True else search a (tl bs) - -and :: Bool -> Bool -> Bool -and True True = True - -hd :: [a] -> a -hd (a:as) = a - -tl :: [a] -> [a] -tl (a:as) = as - -ordIntGt :: Int -> Int -> Bool -ordIntGt 2 3 = True - -eqIntEq :: Int -> Int -> Bool -eqIntEq 2 3 = True - -null :: [a] -> Bool -null [] = True - - - -{- - -=============================================== -Main.Eq__INST_PreludeBuiltin.Int = - let - AbsBinds [] [] [(eq, eq)] - {- nonrec -} - {-# LINE 2 "test3.hs" -} - - eq :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool - eq = Main.eqIntEq - in ({-dict-} [] [eq]) - -Main.Eq__INST_PreludeBuiltin.List = - /\ t135 -> - \{-dict-} _dict138 -> - let - {- nonrec -} - _dict136 = {-singleDict-} _dict138 - {- nonrec -} - _dict129 = {-singleDict-} _dict136 - AbsBinds [] [] [(eq, eq)] - {- nonrec -} - - _dict133 = - Main.Eq__INST_PreludeBuiltin.List - [t135] [{-singleDict-} _dict136] - {- nonrec -} - {-# LINE 5 "test3.hs" -} - - eq :: [t135] -> [t135] -> PreludeCore.Bool - eq = \ xs ys -> - -if (Main.null t135) xs then - (Main.null t135) ys - else - - if (Main.null t135) ys then - PreludeCore.False - else - - Main.and - - - ((Main.Eq_.eq t135 _dict129) - - - ((Main.hd t135) xs) - ((Main.hd t135) ys)) - - - - - - -(Main.Eq_.eq [t135] _dict133) - - - - ((Main.tl t135) xs) - ((Main.tl t135) ys)) - in ({-dict-} [] [eq]) -Main.Ord__INST_PreludeBuiltin.Int = - let - {- nonrec -} - _dict142 = Main.Eq__INST_PreludeBuiltin.Int [] [] - AbsBinds [] [] [(gt, gt)] - {- nonrec -} - {-# LINE 16 "test3.hs" -} - - gt :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool - gt = Main.ordIntGt - in ({-dict-} [_dict142] [gt]) - -Main.Eq_.eq = /\ a -> \{-classdict-} [] [eq] -> eq - -Main.Ord_.gt = /\ a -> \{-classdict-} [_dict56] [gt] -> gt - -Main.Ord__TO_Main.Eq_ = /\ a -> \{-classdict-} [_dict58] [gt] -> ???_dict58??? - -AbsBinds [t60] [] [(hd, Main.hd)] - {- nonrec -} - - - - hd :: [t60] -> t60 - hd (a PreludeBuiltin.: as) - = a - -AbsBinds [t68] [] [(tl, Main.tl)] - {- nonrec -} - - - - - tl :: [t68] -> [t68] - tl (a PreludeBuiltin.: as) - = as - - -AbsBinds [t91] [_dict85, _dict88] [(search, Main.search)] - {- rec -} - {-# LINE 19 "test3.hs" -} - - - search :: t91 -> [t91] -> PreludeCore.Bool - search - = \ a bs -> - - -if (Main.Ord_.gt t91 _dict85) ((Main.hd t91) bs) a then - PreludeCore.False - else - - if (Main.Eq_.eq t91 _dict88) a ((Main.hd t91) bs) then - PreludeCore.True - else - - search a ((Main.tl t91) bs) -AbsBinds [] [] [(and, Main.and)] - {- nonrec -} - and :: PreludeCore.Bool -> PreludeCore.Bool -> PreludeCore.Bool - and PreludeCore.True PreludeCore.True - = PreludeCore.True -AbsBinds [] [] [(ordIntGt, Main.ordIntGt)] - {- nonrec -} - _dict97 = PreludeCore.Num_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - _dict98 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - _dict100 = PreludeCore.Num_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - _dict101 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - - - - ordIntGt :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool - ordIntGt - 2 3 = PreludeCore.True -AbsBinds [] [] [(eqIntEq, Main.eqIntEq)] - {- nonrec -} - _dict105 = PreludeCore.Num_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - _dict106 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - _dict108 = PreludeCore.Num_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - _dict109 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] [] - {- nonrec -} - - eqIntEq :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool - eqIntEq - 2 3 = PreludeCore.True - - -AbsBinds [t112] [] [(null, Main.null)] - {- nonrec -} - - null :: [t112] -> PreludeCore.Bool - null [] = PreludeCore.True --} diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail043.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail043.stderr deleted file mode 100644 index 5454a6ad39ef9645a136e74b030fad94e43b58a4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail043.stderr +++ /dev/null @@ -1,13 +0,0 @@ - -tcfail043.hs:16: - Conflicting definitions for: `and' - Defined at tcfail043.hs:42 - Imported from Prelude at tcfail043.hs:16 - -tcfail043.hs:16: - Conflicting definitions for: `null' - Defined at tcfail043.hs:57 - Imported from Prelude at tcfail043.hs:16 - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail044.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail044.hs deleted file mode 100644 index 3f899a6f6b883b0c1394ee243cb73a404aa779b2..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail044.hs +++ /dev/null @@ -1,22 +0,0 @@ ---!!! tcfail044: duplicated type variable in instance decls --- -module Main where - -instance (Eq a) => Eq (a->a) - - -instance (Num a) => Num (a->a) where - f + g = \x -> f x + g x - negate f = \x -> - (f x) - f * g = \x -> f x * g x - fromInteger n = \x -> fromInteger n - -ss :: Float -> Float -cc :: Float -> Float -tt :: Float -> Float - -ss = sin * sin -cc = cos * cos -tt = ss + cc - -main = putStr ((show (tt 0.4))++ " "++(show (tt 1.652))) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail044.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail044.stderr deleted file mode 100644 index 6a17c88a6320e969e04b115e2e439b88b7da51d6..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail044.stderr +++ /dev/null @@ -1,14 +0,0 @@ - -tcfail044.hs:12: No instance for: - `PrelBase.Eval (a{-a19I-} -> a{-a19I-})' - tcfail044.hs:12: - in an instance declaration - When checking superclass constraints of an instance declaration - -tcfail044.hs:20: No instance for: - `PrelBase.Eval (PrelBase.Float -> PrelBase.Float)' - tcfail044.hs:20: - at a use of an overloaded identifier: `PrelBase.+' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail045.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail045.hs deleted file mode 100644 index 83a1daf81cce86b2ea48e1dc6bea56596a1e8452..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail045.hs +++ /dev/null @@ -1,10 +0,0 @@ ---!!! a bad _CCallable thing (from a bug from Satnam) --- -module ShouldSucceed where -import PreludeGlaST - -data Socket = Socket# Addr -instance CCallable Socket - -f :: Socket -> PrimIO () -f x = _ccall_ foo x diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail045.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail045.stderr deleted file mode 100644 index 638a617cc4873d9cf656f0209ea744cfde923093..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail045.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail045.hs:4: - Could not find valid interface file `PreludeGlaST' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail046.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail046.hs deleted file mode 100644 index 40fad6ba7d4a99bfeb125f921e0e2aafe0bfa70b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail046.hs +++ /dev/null @@ -1,32 +0,0 @@ ---!! function types in deriving Eq things --- From a bug report by Dave Harrison <D.A.Harrison@newcastle.ac.uk> - -module Simulation(Process, - Status, - Pid, - Time, - Continuation, - Message, - MessList ) where - -type Process a = Pid -> Time -> Message a -> ( MessList a, - Continuation a) - -data Continuation a = Do (Process a) deriving Eq - - -type ProcList a = [ (Pid, Status, Process a) ] -data Status = Active | Passive | Busy Integer | Terminated - deriving Eq - - -data Message a = Create (Process a) | Created Pid | Activate Pid | - Passivate Pid | Terminate Pid | Wait Pid Time | - Query Pid a | Data Pid a | Event | - Output Pid String - deriving Eq - -type MessList a = [ Message a ] - -type Pid = Integer -type Time = Integer diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail046.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail046.stderr deleted file mode 100644 index 858e48e62645a01ed91649ecd7af4129438cca36..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail046.stderr +++ /dev/null @@ -1,35 +0,0 @@ - -tcfail046.hs:4: No instance for class - `PrelBase.Eq' - at type - `Process a{-r7b-}' - -tcfail046.hs:4: No instance for class - `PrelBase.Eq' - at type - `Process a{-r7g-}' - -tcfail046.hs:4: No instance for class - `PrelBase.Eq' - at type - `Process a{-r7b-}' - -tcfail046.hs:4: No instance for class - `PrelBase.Eq' - at type - `Process a{-r7g-}' - -tcfail046.hs:23: No instance for: - `PrelBase.Eq (Process a{-a11o-})' - tcfail046.hs:23: - at a use of an overloaded identifier: `PrelBase.==' - When checking methods of an instance declaration - -tcfail046.hs:15: No instance for: - `PrelBase.Eq (Process a{-a14I-})' - tcfail046.hs:15: - at a use of an overloaded identifier: `PrelBase.==' - When checking methods of an instance declaration - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail047.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail047.hs deleted file mode 100644 index 12770a33eb2fbc8de61354bb27bb672b5e20bb1d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail047.hs +++ /dev/null @@ -1,6 +0,0 @@ - -class A a where - op1 :: a -> a - -instance A (a,(b,c)) where - op1 a = a diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail047.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail047.stderr deleted file mode 100644 index 895309ff49a4c6106b4c59010a50e12cb657c223..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail047.stderr +++ /dev/null @@ -1,7 +0,0 @@ - -tcfail047.hs:6: The type ``(a{-r3e-}, (b{-r3f-}, c{-r3g-}))'' cannot be used as an instance type. - -tcfail047.hs:2: Module Main must include a definition for `Main.main' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail048.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail048.hs deleted file mode 100644 index f4400e2fa01cd72211ee78262ecefd9f9f218186..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail048.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldFail where - -class (B a) => C a where - op1 :: a -> a diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail048.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail048.stderr deleted file mode 100644 index b6fa0673a9d48f11060a7558299dc0c7ee87cc4a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail048.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail048.hs:4: - Type constructor or class not in scope: `B' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail049.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail049.hs deleted file mode 100644 index 64dee54a5c9623bbaa97b3666e1ae46ce04e8d77..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail049.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -f x = g x diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail049.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail049.stderr deleted file mode 100644 index d74b04512e42da6c253186ddec3cf81ba18e55af..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail049.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail049.hs:3: - Value not in scope: `g' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail050.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail050.hs deleted file mode 100644 index c0cee979f7e4ec1f3399d1b9c131c7bf9f84561a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail050.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -f x = B x diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail050.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail050.stderr deleted file mode 100644 index c879f63787fe81d3ae2eb77378badc7836f3af2e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail050.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail050.hs:3: - Data constructor not in scope: `B' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail051.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail051.hs deleted file mode 100644 index 1b8e251c4083de3e28b34c7b7c0eaf6a25b57788..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail051.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldFail where - -instance B Bool where - op1 a = a diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail051.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail051.stderr deleted file mode 100644 index 9136d3a0e09e65835bed5d8968d59cd82f1f358b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail051.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail051.hs:4: - Type constructor or class not in scope: `B' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail052.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail052.hs deleted file mode 100644 index e9be21e6f2b2ad99d5e27c830e9c238b12ca6ed9..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail052.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -data C a = B a c diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail052.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail052.stderr deleted file mode 100644 index e31db7873024ecac6baabbec92ac858d9df13818..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail052.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail052.hs:4: - Type variable not in scope: `c' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail053.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail053.hs deleted file mode 100644 index 99028ab4c8cb49817d1738e7f482a15053eb1121..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail053.hs +++ /dev/null @@ -1,2 +0,0 @@ - -data B = C A diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail053.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail053.stderr deleted file mode 100644 index 96cd3dda059385abcae54094d36c65c59876ad04..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail053.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail053.hs:3: - Type constructor or class not in scope: `A' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail054.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail054.hs deleted file mode 100644 index a4e724cf18a2f7ccc9f913ba1733caa87f854eda..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail054.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -f (B a) = True diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail054.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail054.stderr deleted file mode 100644 index 6b7e65f8158ae773d07379d92c1f25f758cd65bc..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail054.stderr +++ /dev/null @@ -1,6 +0,0 @@ - -tcfail054.hs:3: - Data constructor not in scope: `B' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail055.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail055.hs deleted file mode 100644 index f61c5a81be72f69d0ac0e99fa2fc63ff1d7d1602..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail055.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldFail where - -f x = (x + 1 :: Int) :: Float diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail055.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail055.stderr deleted file mode 100644 index 3e6317cefaab320ea94b5b30f60519b401ea7505..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail055.stderr +++ /dev/null @@ -1,12 +0,0 @@ - -tcfail055.hs:3: Couldn't match the type - `PrelBase.Int' against `PrelBase.Float' - Expected: `PrelBase.Float' - Inferred: `PrelBase.Int' - In an expression with a type signature: - `(x PrelBase.+ 1 :: - PrelBase.Int) :: - PrelBase.Float' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail056.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail056.hs deleted file mode 100644 index a8a1315be781a33d07815c866d7c4cc831415a90..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail056.hs +++ /dev/null @@ -1,11 +0,0 @@ -module ShouldFail where - -data Foo = MkFoo Bool - -instance Eq Foo where - (MkFoo x) == (MkFoo y) = x == y - -instance Eq Foo where - -- forgot to type "Ord" above - (MkFoo x) <= (MkFoo y) = x <= y - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail056.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail056.stderr deleted file mode 100644 index e7afc4dff4cbcaecb01253a3dab290b1e817a14a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail056.stderr +++ /dev/null @@ -1,13 +0,0 @@ - -tcfail056.hs:1: Duplicate or overlapping instance declarations - Class `PrelBase.Eq' type `Foo' - at tcfail056.hs:6 and tcfail056.hs:10 - -tcfail056.hs:1: Duplicate or overlapping instance declarations - Class `PrelBase.Eq' type `Foo' - at tcfail056.hs:6 and tcfail056.hs:10 - -tcfail056.hs:10: Class `PrelBase.Eq' does not have a method `<=' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail057.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail057.hs deleted file mode 100644 index bef0085fe5427bb7569712affb677c1d6002e582..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail057.hs +++ /dev/null @@ -1,6 +0,0 @@ -module ShouldFail where - ---!!! inadvertently using -> instead of => - -f :: (RealFrac a) -> a -> a -f x = x diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail057.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail057.stderr deleted file mode 100644 index 96199e7f135720ba1b7f0588b9f058e89724fec5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail057.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -tcfail057.hs:5: Class used as a type constructor: `PrelNum.RealFrac' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail058.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail058.hs deleted file mode 100644 index c05c85972f9671d6820a652ece52a62dadb84675..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail058.hs +++ /dev/null @@ -1,7 +0,0 @@ -module ShouldFail where -import Array - ---!!! inadvertently using => instead of -> - -f :: (Array a) => a -> b -f x = x diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail058.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail058.stderr deleted file mode 100644 index d771e0e3cf906817af689690643b292642ce3f64..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail058.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -tcfail058.hs:6: Type constructor used as a class: `ArrBase.Array' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail059.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail059.hs deleted file mode 100644 index 8f80a6973880b00ce464c54e3afa023471036bb1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail059.hs +++ /dev/null @@ -1,3 +0,0 @@ ---!! The tycon export shouldn't be allowed to succeed --- -module Foo ( Bar(..) ) where { data Bar = Bar X; data X = Y } diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail059.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail059.stderr deleted file mode 100644 index 89ffb6577047b31999b9f56586fa2bb2f3049c43..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail059.stderr +++ /dev/null @@ -1,15 +0,0 @@ - - ---================================================================================ -Typechecked: -`Bar' = - `\ tpl -> - Bar {tpl}' -`Y' = - `Y {}' -AbsBinds [] [] [([], `$d1', `d.Eval')] - `d.Eval' = - ({-dict-} [] []) -AbsBinds [] [] [([], `$d2', `d.Eval')] - `d.Eval' = - ({-dict-} [] []) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail060.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail060.hs deleted file mode 100644 index 1d859923c421e2ad396ad85048bc2eb1fb0db6e4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail060.hs +++ /dev/null @@ -1,9 +0,0 @@ ---!! The class export shouldn't be allowed to succeed --- -module Foo ( Baz(..) ) where - -class Baz a where - opx :: Int -> Bar -> a -> a - -data Bar = Bar X -data X = Y diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail060.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail060.stderr deleted file mode 100644 index 9694aee5b0a7b4b7f83ce50795084dd43a15f2c7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail060.stderr +++ /dev/null @@ -1,24 +0,0 @@ - - ---================================================================================ -Typechecked: -`Y' = - `Y {}' -`Bar' = - `\ tpl -> - Bar {tpl}' -`opx' = - `_/\_ a{-r6B-} -> \ tpl -> - tpl' -AbsBinds [`a{-aHH-}'] [`d.Baz'] [([`a{-aHH-}'], `$mopx', `opx')] - AbsBinds [] [] [([], `opx', `opx')] - `opx' - = `GHCerr.noDefaultMethodError - (PrelBase.Int -> Bar -> a{-aHH-} -> a{-aHH-}) - "Class Baz Method opx"' -AbsBinds [] [] [([], `$d1', `d.Eval')] - `d.Eval' = - ({-dict-} [] []) -AbsBinds [] [] [([], `$d2', `d.Eval')] - `d.Eval' = - ({-dict-} [] []) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail061.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail061.hs deleted file mode 100644 index 2957e800d5d3aaa776e7f0a16cafafcf43e69082..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail061.hs +++ /dev/null @@ -1,11 +0,0 @@ ---!! signature bugs exposed by Sigbjorne Finne --- -module ShouldFail where - -type Flarp a = (b,b) - ---More fun can be had if we change the signature slightly - -type Bob a = a - -type Flarp2 a = Bob (b,b) diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail061.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail061.stderr deleted file mode 100644 index e9c3c39f1efec6f49015245fd098e3ea41a6cc1c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail061.stderr +++ /dev/null @@ -1,15 +0,0 @@ - -tcfail061.hs:11: - Type variable not in scope: `b' - -tcfail061.hs:11: - Type variable not in scope: `b' - -tcfail061.hs:5: - Type variable not in scope: `b' - -tcfail061.hs:5: - Type variable not in scope: `b' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail062.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail062.hs deleted file mode 100644 index 5c9b0ea2156b7d765f3d90ecd167d42341222829..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail062.hs +++ /dev/null @@ -1,37 +0,0 @@ ---!!! bug report from Satnam --- -module RubyAST -where - -type Module = (String,[Declaration]) - -data Declaration - = Architecture String StructuralExpression | - Behaviour String Parameter Parameter BehaviouralExpression - deriving (Eq, Show) - -data Parameter = ParameterVariable String | ParameterList [Parameter] - deriving (Eq, Show) - -nameOfModule :: Module -> String -nameOfModule (name, _) = name - -data StructuralExpression - = Variable String | - Serial StructuralExpression StructuralExpression | - Par [StructuralExpression] - deriving (Eq, Show) - -data BehaviouralExpression - = BehaviouralVariable String - | AndExpr BehaviouralExpression BehaviouralExpression - | OrExpr BehaviouralExpression BehaviouralExpression - | NotExpr BehaviouralExpression - deriving (Eq, Show) - - -type BehaviouralRelation - = (behaviouralExpression, behaviouralExpression) ------^ typo ----------------^ typo (but so what?) - -type BehaviouralRelationList = [BehaviouralRelation] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail062.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail062.stderr deleted file mode 100644 index 7cffa7b5e3b571dec8d5f538910ac5fe78cb5be6..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail062.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail062.hs:33: - Type variable not in scope: `behaviouralExpression' - -tcfail062.hs:33: - Type variable not in scope: `behaviouralExpression' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail063.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail063.hs deleted file mode 100644 index 562cdf4400cfe991d3318a889054f26bd38ef9dd..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail063.hs +++ /dev/null @@ -1,5 +0,0 @@ ---!!! no type variable on a context ---!!! reported by Sigbjorn Finne - -moby :: Num => Int -> a -> Int -moby x y = x+y diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail063.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail063.stderr deleted file mode 100644 index bdec0c873ca56ade98398a97bc9895a9b1168566..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail063.stderr +++ /dev/null @@ -1 +0,0 @@ -tcfail063.hs:5:1: is_context_format: variable missing after class name on input: "moby" diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail064.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail064.hs deleted file mode 100644 index e69de29bb2d1d6434b8b29ae775ad8c2e48c5391..0000000000000000000000000000000000000000 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail064.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail064.stderr deleted file mode 100644 index 1709a477307b32ff09ab3ec64c2f26c9b9920679..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail064.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -tcfail064.hs:0: Module Main must include a definition for `Main.main' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail065.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail065.hs deleted file mode 100644 index 3029b1978c46b93e524fc37b6192687d34b6ab65..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail065.hs +++ /dev/null @@ -1,37 +0,0 @@ -{- - -------- Forwarded Message - -Date: Wed, 30 Nov 1994 16:34:18 +0100 -From: John Hughes <rjmh@cs.chalmers.se> -To: augustss@cs.chalmers.se, simonpj@dcs.gla.ac.uk -Subject: Nice little program - - -Lennart, Simon, - -You might like to look at the fun little program below. - -THUMBS DOWN to hbc for compiling it (it prints [72, 101, 108, 108, 111]) -THUMBS UP to ghc for rejecting it --- but what an error message! -nhc and gofer both reject it with the right error message. -I haven't tried Yale Haskell. - -Enjoy! -- ---------------------------- --} - -class HasX a where - setX :: x->a->a - -data X x = X x -instance HasX (X x) where - setX x (X _) = X x - -changetype x = case setX x (X (error "change type!")) of X y->y - -main = print (changetype "Hello" :: [Int]) - -{- -------- End of Forwarded Message --} diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail065.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail065.stderr deleted file mode 100644 index c579c2ea84e8fae66ad5b5f0a41c93a8776610d7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail065.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -<NoSrcLoc>: A type signature is more polymorphic than the inferred type - Some type variables in the inferred type can't be forall'd, namely: - `x{-aNe-}' - Possible cause: the RHS mentions something subject to the monomorphism restriction - When checking signature for `setX' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail066.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail066.hs deleted file mode 100644 index 2d2e9bafd8b33365cd4b7efb0660551e72aa21dc..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail066.hs +++ /dev/null @@ -1,42 +0,0 @@ ---!! INLINE on recursive functions. -{- -Date: Thu, 8 Dec 94 11:38:24 GMT -From: Julian Seward (DRL PhD) <sewardj@computer-science.manchester.ac.uk> -Message-Id: <9412081138.AA16652@rdf009.cs.man.ac.uk> -To: partain@dcs.gla.ac.uk --} -module ShouldFail where - -type IMonad a - = IMonadState -> IMonadReturn a - -data IMonadReturn a - = IMonadOk IMonadState a - | IMonadFail IMonadState String - -type IMonadState - = Int - - -returnI r = \s0 -> IMonadOk s0 r - -failI msg = \s0 -> IMonadFail s0 msg - -thenI m k - = \s0 -> case m s0 of - IMonadFail s1 msg -> IMonadFail s1 msg - IMonadOk s1 r1 -> k r1 s1 - -tickI n = \s0 -> IMonadOk (s0+n) () - -mapI f [] = returnI [] -mapI f (x:xs) = f x `thenI` ( \ fx -> - mapI f xs `thenI` ( \ fxs -> - returnI (fx:fxs) - )) - -{-# INLINE returnI #-} -{-# INLINE failI #-} -{-# INLINE thenI #-} -{-# INLINE tickI #-} -{-# INLINE mapI #-} diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail066.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail066.stderr deleted file mode 100644 index 9d8a6a1d8c98cc5041339757de8b0a3ae49bc24f..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail066.stderr +++ /dev/null @@ -1,74 +0,0 @@ - - ---================================================================================ -Typechecked: -`IMonadOk' = - `_/\_ a{-r44-} -> \ tpl tpl -> - IMonadOk - {_@_ a{-r44-} tpl tpl}' -`IMonadFail' = - `_/\_ a{-r44-} -> \ tpl tpl -> - IMonadFail - {_@_ a{-r44-} tpl tpl}' -AbsBinds [`a{-aKg-}'] [] [([`a{-aKg-}'], `$d1', `d.Eval')] - `d.Eval' = - ({-dict-} [] []) -`d.Num' = - `PrelBase.$d3' -`+' = - `PrelBase.+' - `IMonadState' - `d.Num' -AbsBinds [] [] [([], `tickI', `tickI')] - `tickI' - `n' = `\ s0 -> IMonadOk - PrelBase.() - s0 + n PrelBase.()' -AbsBinds -[`t{-aJ6-}', `a{-aIN-}', `a{-aIR-}'] -[] -[([`t{-aJ6-}', `a{-aIN-}', `a{-aIR-}'], `thenI', `thenI')] - `thenI' - `m' `k' = `\ s0 -> case m s0 of - (IMonadFail s1 msg) - -> IMonadFail - a{-aIN-} - s1 msg - (IMonadOk s1 r1) - -> k r1 s1' -AbsBinds [`a{-aJg-}'] [] [([`a{-aJg-}'], `failI', `failI')] - `failI' - `msg' = `\ s0 -> IMonadFail - a{-aJg-} - s0 msg' -AbsBinds [`a{-aJn-}'] [] [([`a{-aJn-}'], `returnI', `returnI')] - `returnI' - `r' = `\ s0 -> IMonadOk - a{-aJn-} - s0 r' -AbsBinds -[`t{-aJz-}', `t{-aJC-}'] -[] -[([`t{-aJz-}', `t{-aJC-}'], `mapI', `mapI')] - `mapI' - `f' `PrelBase.[]' - = `returnI - [t{-aJz-}] - PrelBase.[] - t{-aJz-}' - `mapI' - `f' (`x' `PrelBase.:' `xs') - = `thenI - [IMonadState, [t{-aJz-}], t{-aJz-}] - (f x) - (\ fx -> thenI - [IMonadState, [t{-aJz-}], [t{-aJz-}]] - (mapI - f xs) - (\ fxs -> returnI - [t{-aJz-}] - PrelBase.: - t{-aJz-} - fx fxs))' - -NOTE: Simplifier still going after 4 iterations; bailing out. diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail067.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail067.hs deleted file mode 100644 index 99d4c648c06a8f15ffae96d889d82cafff89ac40..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail067.hs +++ /dev/null @@ -1,98 +0,0 @@ -module SubRange where - -infixr 1 `rangeOf` - - -data Ord a => SubRange a = SubRange (a, a) a - -type IntSubRange = SubRange Int - - -subRangeValue :: SubRange a -> a -subRangeValue (SubRange (lower, upper) value) = value - -subRange :: SubRange a -> (a, a) -subRange (SubRange r value) = r - -newRange :: (Ord a, Show a) => (a, a) -> a -> SubRange a -newRange r value = checkRange (SubRange r value) - - -checkRange :: (Ord a, Show a) => SubRange a -> SubRange a -checkRange (SubRange (lower, upper) value) - = if (value < lower) || (value > upper) then - error ("### sub range error. range = " ++ show lower ++ - ".." ++ show upper ++ " value = " ++ show value ++ "\n") - else - SubRange (lower, upper) value - - -instance Eq a => Eq (SubRange a) where - (==) a b = subRangeValue a == subRangeValue b - -instance (Ord a) => Ord (SubRange a) where - (<) = relOp (<) - (<=) = relOp (<=) - (>=) = relOp (>=) - (>) = relOp (>) - -relOp :: Ord a => (a->a->Bool) -> SubRange a -> SubRange a -> Bool -relOp op a b = (subRangeValue a) `op` (subRangeValue b) - -rangeOf :: (Ord a, Show a) => SubRange a -> SubRange a -> SubRange a -rangeOf a b = checkRange (SubRange (subRange b) (subRangeValue a)) - -showRange :: Show a => SubRange a -> String -showRange (SubRange (lower, upper) value) - = show value ++ " :" ++ show lower ++ ".." ++ show upper - -showRangePair :: (Show a, Show b) => (SubRange a, SubRange b) -> String -showRangePair (a, b) - = "(" ++ showRange a ++ ", " ++ showRange b ++ ")" - -showRangeTriple :: (Show a, Show b, Show c) => - (SubRange a, SubRange b, SubRange c) -> String -showRangeTriple (a, b, c) - = "(" ++ showRange a ++ ", " ++ showRange b ++ ", " ++ showRange c ++ ")" - - - -instance Num a => Num (SubRange a) where - negate = numSubRangeNegate - (+) = numSubRangeAdd - (-) = numSubRangeSubtract - (*) = numSubRangeMultiply - fromInteger a = SubRange (fromInteger a, fromInteger a) (fromInteger a) - -numSubRangeNegate :: (Ord a, Num a) => SubRange a -> SubRange a -numSubRangeNegate (SubRange (lower, upper) value) - = checkRange (SubRange (lower, upper) (-value)) - -numSubRangeBinOp :: Num a => (a -> a -> a) -> - SubRange a -> SubRange a -> SubRange a -numSubRangeBinOp op a b - = SubRange (result, result) result - where - result = (subRangeValue a) `op` (subRangeValue b) - --- partain: -numSubRangeAdd, numSubRangeSubtract, numSubRangeMultiply :: Num a => SubRange a -> SubRange a -> SubRange a - -numSubRangeAdd = numSubRangeBinOp (+) -numSubRangeSubtract = numSubRangeBinOp (-) -numSubRangeMultiply = numSubRangeBinOp (*) - -unsignedBits :: Int -> (Int, Int) -unsignedBits n = (0, 2^n-1) - -signedBits :: Int -> (Int, Int) -signedBits n = (-2^(n-1), 2^(n-1)-1) - - -si_n :: Int -> Int -> IntSubRange -si_n bits value = SubRange (signedBits bits) value - -si8, si10, si16 :: Int -> IntSubRange -si8 = si_n 8 -si10 = si_n 10 -si16 = si_n 16 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail067.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail067.stderr deleted file mode 100644 index 724cb4875fbe280b9106f2fc0287e95ab23079fb..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail067.stderr +++ /dev/null @@ -1,13 +0,0 @@ - -tcfail067.hs:1: tcfail067.hs:76: Context required by inferred type, but missing on a type signature: - at a use of an overloaded identifier: `SubRange' - `PrelBase.Ord' `a{-a1dZ-}' - When checking signature(s) for: `numSubRangeBinOp' - -tcfail067.hs:65: tcfail067.hs:61: Context required by inferred type, but missing on a type signature: - at a use of an overloaded identifier: `numSubRangeNegate' - `PrelBase.Ord' `a{-a1fx-}' - When checking methods of an instance declaration - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail068.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail068.hs deleted file mode 100644 index 0d081b9d261e3feef6005a5df5aeb4bdb5012374..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail068.hs +++ /dev/null @@ -1,92 +0,0 @@ ---!! Make sure that state threads don't escape ---!! (example from Neil Ashton at York) --- -module IndTree(IndTree(..), itgen, itiap, itrap, itrapstate) where - ---partain: import Auxiliary -import GlaExts - -type IndTree s t = MutableArray s (Int,Int) t - -itgen :: Constructed a => (Int,Int) -> a -> IndTree s a -itgen n x = - runST ( - newArray ((1,1),n) x) - -itiap :: Constructed a => (Int,Int) -> (a->a) -> IndTree s a -> IndTree s a -itiap i f arr = - runST ( - readArray arr i `thenStrictlyST` \val -> - writeArray arr i (f val) `seqStrictlyST` - returnStrictlyST arr) - -itrap :: Constructed a => ((Int,Int),(Int,Int)) -> (a->a) -> IndTree s a -> IndTree s a -itrap ((i,k),(j,l)) f arr = runST(itrap' i k) - where - itrap' i k = if k > l then returnStrictlyST arr - else (itrapsnd i k `seqStrictlyST` - itrap' i (k+1)) - itrapsnd i k = if i > j then returnStrictlyST arr - else (readArray arr (i,k) `thenStrictlyST` \val -> - writeArray arr (i,k) (f val) `seqStrictlyST` - itrapsnd (i+1) k) - -itrapstate :: Constructed b => ((Int,Int),(Int,Int)) -> (a->b->(a,b)) -> ((Int,Int)->c->a) -> - (a->c) -> c -> IndTree s b -> (c, IndTree s b) -itrapstate ((i,k),(j,l)) f c d s arr = runST(itrapstate' i k s) - where - itrapstate' i k s = if k > l then returnStrictlyST (s,arr) - else (itrapstatesnd i k s `thenStrictlyST` \(s,arr) -> - itrapstate' i (k+1) s) - itrapstatesnd i k s = if i > j then returnStrictlyST (s,arr) - else (readArray arr (i,k) `thenStrictlyST` \val -> - let (newstate, newval) = f (c (i,k) s) val - in writeArray arr (i,k) newval `seqStrictlyST` - itrapstatesnd (i+1) k (d newstate)) - --- stuff from Auxiliary: copied here (partain) - -sap :: (a->b) -> (c,a) -> (c,b) -sap f (x,y) = (x, f y) - -fap :: (a->b) -> (a,c) -> (b,c) -fap f (x,y) = (f x, y) - -nonempty :: [a] -> Bool -nonempty [] = False -nonempty (_:_) = True - --- const :: a -> b -> a --- const k x = k - --- id :: a -> a --- id x = x - -compose :: [a->a] -> a -> a -compose = foldr (.) id - -data Maybe t = Just t | Nothing - -class Constructed a where - normal :: a -> Bool - -instance Constructed Bool where - normal True = True - normal False = True - -instance Constructed Int where - normal 0 = True - normal n = True - -instance (Constructed a, Constructed b) => Constructed (a,b) where - normal (x,y) = normal x && normal y - --- pair :: (Constructed a, Constructed b) => a -> b -> (a,b) --- pair x y | normal x && normal y = (x,y) - -instance Constructed (Maybe a) where - normal Nothing = True - normal (Just _) = True - -just :: Constructed a => a -> Maybe a -just x | normal x = Just x diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail068.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail068.stderr deleted file mode 100644 index 47bc53f764da3127a81c955261917678c06c6266..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail068.stderr +++ /dev/null @@ -1,69 +0,0 @@ - -tcfail068.hs:4: - Conflicting definitions for: `Just' - Defined at tcfail068.hs:68 - Imported from Prelude at tcfail068.hs:4 - -tcfail068.hs:4: - Conflicting definitions for: `Nothing' - Defined at tcfail068.hs:70 - Imported from Prelude at tcfail068.hs:4 - -tcfail068.hs:4: - Conflicting definitions for: `Maybe' - Defined at tcfail068.hs:68 - Imported from Prelude at tcfail068.hs:4 - -tcfail068.hs:14: - Value not in scope: `runST' - -tcfail068.hs:21: - Value not in scope: `runST' - -tcfail068.hs:19: - Value not in scope: `returnStrictlyST' - -tcfail068.hs:19: - Value not in scope: `seqStrictlyST' - -tcfail068.hs:21: - Value not in scope: `thenStrictlyST' - -tcfail068.hs:26: - Value not in scope: `returnStrictlyST' - -tcfail068.hs:26: - Value not in scope: `seqStrictlyST' - -tcfail068.hs:29: - Value not in scope: `returnStrictlyST' - -tcfail068.hs:30: - Value not in scope: `seqStrictlyST' - -tcfail068.hs:29: - Value not in scope: `thenStrictlyST' - -tcfail068.hs:32: - Value not in scope: `runST' - -tcfail068.hs:38: - Value not in scope: `returnStrictlyST' - -tcfail068.hs:38: - Value not in scope: `thenStrictlyST' - -tcfail068.hs:41: - Value not in scope: `returnStrictlyST' - -tcfail068.hs:42: - Value not in scope: `seqStrictlyST' - -tcfail068.hs:41: - Value not in scope: `thenStrictlyST' - -tcfail068.hs:45: - Value not in scope: `runST' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail069.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail069.hs deleted file mode 100644 index 73dd738549470d2a7e1daf16161a8bae0ae7e9e1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail069.hs +++ /dev/null @@ -1,48 +0,0 @@ -{- -From: Marc van Dongen <dongen@cs.ucc.ie> -Date: Wed, 9 Apr 1997 14:06:39 +0100 (BST) - -I just wanted to report that the erroneous and tiny -program added below can not be compiled within 6MB of -heap (Admitted it can be compiled with a bigger heap). -It was part of a bigger program that could not be -compiled within 20MB of heap. - -[GHC 2.03 and earlier.] Turned out to be a bug in the -error recovery mechanism. - --} - -module Too_Kuch( too_much ) where - -too_much :: [Int] -> [(Int,Int)] -> [(Int,[Int])] -> Bool -too_much ds ((k,m):q1) s0 - = case (list1,list2) of - [] -> error "foo" -- too_much ds q2m s2m - where list1 = ds - list2 = ds - {- - list1 = [k' | k' <- ds, k == k'] - list2 = [k' | k' <- ds, m == k'] - s1 = aas s0 k - raM = [] - raKM = listUnion (\a b -> a) [] [] - s1k = s1 - q1k = raM - s2k = s1 - q2k = raM - s2m = s1 - q2m = raM - s2km = foldr (flip aas) s1 raKM - q2km = raKM - -} - -listUnion :: (v -> v -> Bool) -> [v] -> [v] -> [v] -listUnion _ _ _ - = [] - -aas :: (a,b) -> a -> (a,b) -aas s _ - = s - - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail069.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail069.stderr deleted file mode 100644 index f539eb137fe232d54ace690a71d1528333e91ec8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail069.stderr +++ /dev/null @@ -1,28 +0,0 @@ - -tcfail069.hs:21: Couldn't match the type - `PrelBase.[]' against `PrelTup.(,) [PrelBase.Int]' - Expected: `[t{-aF1-}]' - Inferred: `([PrelBase.Int], [PrelBase.Int])' - In a "case" branch: - `PrelBase.[]' - -> `IOBase.error - "foo"' - In a case expression: - `case (list1, (list2)) of - PrelBase.[] - -> IOBase.error - "foo"' - In an equation for function `too_much': - `too_much ds ((k, m) PrelBase.: q1) s0 - = case (list1, (list2)) of - PrelBase.[] - -> IOBase.error - "foo" - where - list2 - = ds - list1 - = ds' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail070.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail070.hs deleted file mode 100644 index d6cd3d7eab16b976561a237253f569f6e0d5e28d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail070.hs +++ /dev/null @@ -1,14 +0,0 @@ -{- -From: Wolfgang Drotschmann <drotschm@athene.informatik.uni-bonn.de> -Resent-Date: Thu, 15 May 1997 17:23:09 +0100 - -I'm still using the old ghc-2.01. In one program I ran into a problem -I couldn't fix. But I played around with it, I found a small little -script which reproduces it very well: - -panic! (the `impossible' happened): - tlist --} - -type State = ([Int] Bool) - diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail070.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail070.stderr deleted file mode 100644 index f5acaae2dcda6d5449788813256e8baa4ecd70f8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail070.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tcfail070.hs:13: Couldn't match the kind - * against * -> ka2141 - When unifying two kinds - * and * -> ka2141 - In the type declaration for `State' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail071.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail071.hs deleted file mode 100644 index 49587286b998ba457e3adf94f0a8a7623bde9eab..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail071.hs +++ /dev/null @@ -1,10 +0,0 @@ ---!!! Mis-matched contexts in a mutually recursive group - -module Foo7( f ) where - -f :: (Ord c) => c -> c -f c = g c - -g :: c -> c -g c = c - where p = foldr (f c) [] [] diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail071.stderr b/ghc/compiler/tests/typecheck/should_fail/tcfail071.stderr deleted file mode 100644 index e69de29bb2d1d6434b8b29ae775ad8c2e48c5391..0000000000000000000000000000000000000000 diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail072.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail072.hs deleted file mode 100644 index f7f57a76f4ed50ae2dbc81ebf454216833b2802a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_fail/tcfail072.hs +++ /dev/null @@ -1,24 +0,0 @@ -{- This program crashed GHC 2.03 - - From: Marc van Dongen <dongen@cs.ucc.ie> - Date: Sat, 31 May 1997 14:35:40 +0100 (BST) - - zonkIdOcc: g_aoQ - - panic! (the `impossible' happened): - lookupBindC:no info! - for: g_aoQ - (probably: data dependencies broken by an optimisation pass) - static binds for: - Tmp.$d1{-rmM,x-} - local binds for: --} - -module Tmp( g ) where - -data AB p q = A - | B p q - -g :: (Ord p,Ord q) => (AB p q) -> Bool -g (B _ _) = g A - diff --git a/ghc/compiler/tests/typecheck/should_succeed/ClassFoo.hi b/ghc/compiler/tests/typecheck/should_succeed/ClassFoo.hi deleted file mode 100644 index fbda08656dc47007bc089ec40430adfd4f69a3e8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/ClassFoo.hi +++ /dev/null @@ -1,5 +0,0 @@ -_interface_ ClassFoo 1 -_exports_ -ClassFoo Foo(op1 op2); -_declarations_ -1 class Foo a where { op1 :: a -> PrelBase.Int; op2 :: a -> a -> PrelBase.Int} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/M.hi b/ghc/compiler/tests/typecheck/should_succeed/M.hi deleted file mode 100644 index ffb4e0c9dc8ffbe4edce57ecb239e64f82d43486..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/M.hi +++ /dev/null @@ -1,4 +0,0 @@ -interface M where -class (ORD a, Text a) => EQ a where (===) :: a -> a -> Bool -class (Num a) => ORD a -data NUM = ONE | TWO diff --git a/ghc/compiler/tests/typecheck/should_succeed/Makefile b/ghc/compiler/tests/typecheck/should_succeed/Makefile deleted file mode 100644 index faa19119eef98a85f71b12632802c82715d81a6a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/Makefile +++ /dev/null @@ -1,25 +0,0 @@ -TOP = ../../../.. -include $(TOP)/mk/boilerplate.mk - -HS_SRCS = $(wildcard *.hs) - -SRC_RUNTEST_OPTS += -o1 $*.stdout -o2 $*.stderr -x 0 -HC_OPTS += -noC -ddump-tc -dcore-lint -hi - -# Expect failure. Why aren't they in "should-fail"? -tc075_RUNTEST_OPTS += -x 1 -tc080_RUNTEST_OPTS += -x 1 - -%.o : %.hs - -%.o : %.hs - $(RUNTEST) $(HC) $(RUNTEST_OPTS) -- $(HC_OPTS) -c $< -o $@ - -all :: $(HS_OBJS) - -tc019_HC_OPTS = -fglasgow-exts -tc065_HC_OPTS = -syslib ghc - -include $(TOP)/mk/target.mk - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/ShouldSucceed.hi b/ghc/compiler/tests/typecheck/should_succeed/ShouldSucceed.hi deleted file mode 100644 index 3ea8fd3a462a447adadefa36b42b4cec72fd9972..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/ShouldSucceed.hi +++ /dev/null @@ -1,7 +0,0 @@ -interface ShouldSucceed where { -{- TCE -} -{- CE -} -{- LVE -} -a :: Num t64 => t64 -> t64 -{- GIEinst -} -} diff --git a/ghc/compiler/tests/typecheck/should_succeed/TheUtils.hi b/ghc/compiler/tests/typecheck/should_succeed/TheUtils.hi deleted file mode 100644 index dd662cd3691dbff5007b5a05be3edc9030760078..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/TheUtils.hi +++ /dev/null @@ -1,68 +0,0 @@ -_interface_ TheUtils 2 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d14 1 $d15 1 $d16 1 $d17 1 $d18 1 $d19 1 $d2 1 $d21 1 $d22 1 $d23 1 $d24 1 $d25 1 $d26 1 $d27 1 $d3 1 $d32 1 $d33 1 $d34 1 $d36 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d45 1 $d46 1 $d48 1 $d49 1 $d50 1 $d51 1 $d53 1 $d54 1 $d55 1 $d57 1 $d6 1 $d7 1 $d8 1 $m* 1 $m+ 1 $m++ 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m== 1 $m> 1 $m>= 1 $m>> 1 $m>>= 1 $mabs 1 $mcompare 1 $mfromInt 1 $mfromInteger 1 $mmap 1 $mmax 1 $mmin 1 $mnegate 1 $mreturn 1 $mshowList 1 $mshowsPrec 1 $msignum 1 $mzero 1 && 1 . 1 not 1 otherwise 1 show 1 || 1 Eq 1 Eval 1 Functor 1 Maybe 1 Monad 1 MonadPlus 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Ordering 1 Show 1 String 1; -PrelList 1 :: repeat 1 reverse 1 span 1 take 1; -PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1; -PrelTup 1 :: $d10 1 $d13 1 $d14 1 $d3 1 $d4 1 $d49 1 $d50 1 $d9 1; -Pretty 1 :: $d1 1 $d2 1 hsep 1 int 1 sep 1 text 1 Doc 1; -_exports_ -TheUtils appEager assertPanic assertPprPanic assoc assocDefault assocDefaultUsing assocUsing cmpList cmpPString endsWith equivClasses hasNoDups isIn isSingleton isn'tIn lengthExceeds mapAccumB mapAccumL mapAccumR mapAndUnzip mapAndUnzip3 mapEager nOfThem naturalMergeSortLe panic panic# pprError pprPanic pprPanic# pprTrace removeDups returnEager runEager runs sortLt startsWith thenCmp thenEager transitiveClosure unzipWith zipEqual zipLazy zipWith3Equal zipWith4Equal zipWithEqual Eager Ord3(cmp); -_fixities_ -infixr 9 thenCmp; -_instances_ -instance {Ord3 PrelBase.Int} = $d1; -instance _forall_ [a] {Ord3 a} => {Ord3 (PrelBase.Maybe a)} = $d2; -instance _forall_ [a] {Ord3 a} => {Ord3 [a]} = $d3; -_declarations_ -2 $d1 _:_ {Ord3 PrelBase.Int} ;; -1 $d2 _:_ _forall_ [a] {Ord3 a} => {Ord3 (PrelBase.Maybe a)} ;; -1 $d3 _:_ _forall_ [a] {Ord3 a} => {Ord3 [a]} ;; -1 $mcmp _:_ _forall_ [a] {Ord3 a} => a -> a -> GHC.Int# ;; -2 type Eager rvB rvC = (rvC -> rvB) -> rvB ; -2 class Ord3 rvx where {cmp :: rvx -> rvx -> GHC.Int#} ; -1 appEager _:_ _forall_ [a b] => Eager b a -> (a -> b) -> b ;; -1 assertPanic _:_ _forall_ [a] => PrelBase.String -> PrelBase.Int -> a ;; -2 assertPprPanic _:_ _forall_ [a] => PrelBase.String -> PrelBase.Int -> Pretty.Doc -> a ;; -1 assoc _:_ _forall_ [a b] {PrelBase.Eq a} => PrelBase.String -> [(a, b)] -> a -> b ;; -1 assocDefault _:_ _forall_ [a b] {PrelBase.Eq a} => b -> [(a, b)] -> a -> b ;; -1 assocDefaultUsing _:_ _forall_ [a b] => (a -> a -> PrelBase.Bool) -> b -> [(a, b)] -> a -> b ;; -1 assocUsing _:_ _forall_ [a b] => (a -> a -> PrelBase.Bool) -> PrelBase.String -> [(a, b)] -> a -> b ;; -1 cmpList _:_ _forall_ [a] => (a -> a -> GHC.Int#) -> [a] -> [a] -> GHC.Int# ;; -1 endsWith _:_ PrelBase.String -> PrelBase.String -> PrelBase.Maybe PrelBase.String ;; -1 equivClasses _:_ _forall_ [a] => (a -> a -> GHC.Int#) -> [a] -> [[a]] ;; -1 hasNoDups _:_ _forall_ [a] {PrelBase.Eq a} => [a] -> PrelBase.Bool ;; -1 isIn _:_ _forall_ [a] {PrelBase.Eq a} => PrelBase.String -> a -> [a] -> PrelBase.Bool ;; -1 isSingleton _:_ _forall_ [a] => [a] -> PrelBase.Bool ;; -1 isn'tIn _:_ _forall_ [a] {PrelBase.Eq a} => PrelBase.String -> a -> [a] -> PrelBase.Bool ;; -1 lengthExceeds _:_ _forall_ [a] => [a] -> PrelBase.Int -> PrelBase.Bool ;; -1 mapAccumB _:_ _forall_ [a b c d] => (b -> c -> a -> (b, c, d)) -> b -> c -> [a] -> (b, c, [d]) ;; -1 mapAccumL _:_ _forall_ [a b c] => (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) ;; -1 mapAccumR _:_ _forall_ [a b c] => (b -> a -> (b, c)) -> b -> [a] -> (b, [c]) ;; -1 mapAndUnzip _:_ _forall_ [a b c] => (a -> (b, c)) -> [a] -> ([b], [c]) ;; -1 mapAndUnzip3 _:_ _forall_ [a b c d] => (a -> (b, c, d)) -> [a] -> ([b], [c], [d]) ;; -1 mapEager _:_ _forall_ [a b c] => (a -> (c -> b) -> b) -> [a] -> ([c] -> b) -> b ;; -1 nOfThem _:_ _forall_ [a] => PrelBase.Int -> a -> [a] ;; -1 naturalMergeSortLe _:_ _forall_ [a] => (a -> a -> PrelBase.Bool) -> [a] -> [a] ;; -1 panic _:_ _forall_ [a] => [PrelBase.Char] -> a ;; -1 panic# _:_ PrelBase.String -> GHC.Int# ;; -1 pprError _:_ _forall_ [a b] {PrelBase.Show a} => [PrelBase.Char] -> a -> b ;; -1 pprPanic _:_ _forall_ [a b] {PrelBase.Show a} => [PrelBase.Char] -> a -> b ;; -1 pprPanic# _:_ _forall_ [a] {PrelBase.Show a} => [PrelBase.Char] -> a -> GHC.Int# ;; -1 pprTrace _:_ _forall_ [a b] {PrelBase.Show a} => [PrelBase.Char] -> a -> b -> b ;; -1 removeDups _:_ _forall_ [a] => (a -> a -> GHC.Int#) -> [a] -> ([a], [[a]]) ;; -1 returnEager _:_ _forall_ [a b] => b -> (b -> a) -> a ;; -1 runEager _:_ _forall_ [a] => Eager a a -> a ;; -1 runs _:_ _forall_ [a] => (a -> a -> PrelBase.Bool) -> [a] -> [[a]] ;; -1 sortLt _:_ _forall_ [a] => (a -> a -> PrelBase.Bool) -> [a] -> [a] ;; -1 startsWith _:_ PrelBase.String -> PrelBase.String -> PrelBase.Maybe PrelBase.String ;; -1 thenCmp _:_ GHC.Int# -> GHC.Int# -> GHC.Int# ;; -1 thenEager _:_ _forall_ [a b c] => Eager b a -> (a -> (c -> b) -> b) -> (c -> b) -> b ;; -1 transitiveClosure _:_ _forall_ [a] => (a -> [a]) -> (a -> a -> PrelBase.Bool) -> [a] -> [a] ;; -1 unzipWith _:_ _forall_ [a b c] => (a -> b -> c) -> [(a, b)] -> [c] ;; -1 zipEqual _:_ _forall_ [a b] => PrelBase.String -> [a] -> [b] -> [(a, b)] ;; -1 zipLazy _:_ _forall_ [a b] => [a] -> [b] -> [(a, b)] ;; -1 zipWith3Equal _:_ _forall_ [a b c d] => PrelBase.String -> (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] ;; -1 zipWith4Equal _:_ _forall_ [a b c d e] => PrelBase.String -> (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] ;; -1 zipWithEqual _:_ _forall_ [a b c] => PrelBase.String -> (a -> b -> c) -> [a] -> [b] -> [c] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc001.hs b/ghc/compiler/tests/typecheck/should_succeed/tc001.hs deleted file mode 100644 index c3b0a785e26ed22afae9ba8fc8ac7924f6a1d890..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc001.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -a x = y+2 where y = x+3 diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc001.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc001.stderr deleted file mode 100644 index c0887ce97f7bb956c7b5e84f1d10b5a2f9162330..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc001.stderr +++ /dev/null @@ -1,45 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [t{-aGZ-}] [d.Num_aH2] [([t{-aGZ-}], a{-r3h,x-}, a_aGG)] - +_aHc = - PrelBase.+{-r3g,p-} - t{-aGZ-} - d.Num_aH2 - d.Num_aH5 = - d.Num_aH2 - fromInt_aHb = - PrelBase.fromInt{-8R,p-} - t{-aGZ-} - d.Num_aH5 - lit_aHa = - fromInt_aHb PrelBase.I#{-5b,p-}{i} 2# - +_aH9 = - +_aHc - fromInt_aH8 = - fromInt_aHb - lit_aH6 = - fromInt_aH8 PrelBase.I#{-5b,p-}{i} 3# - a_aGG - x_r3d = y_r3f +_aHc lit_aHa - where - {- nonrec -} - AbsBinds [] [] [([], y_r3f, y_aGK)] - y_aGK - = x_r3d +_aH9 lit_aH6 - {- nonrec -} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed a; -_declarations_ -1 a _:_ _forall_ [a] {PrelBase.Num a} => a -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc002.hs b/ghc/compiler/tests/typecheck/should_succeed/tc002.hs deleted file mode 100644 index 85f1a91e1fc5b10eadb03ed3c01cd7bdbfa7929e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc002.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -b = if True then 1 else 2 diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc002.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc002.stderr deleted file mode 100644 index 585daff4c5bce7a9085ba3f1bd8f5fa066023dac..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc002.stderr +++ /dev/null @@ -1,33 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aGV = - PrelBase.$d3{-rb0,p-} -fromInt_aGW = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aGV -lit_aH1 = - fromInt_aGW PrelBase.I#{-5b,p-}{i} 1# -fromInt_aH0 = - fromInt_aGW -lit_aGX = - fromInt_aH0 PrelBase.I#{-5b,p-}{i} 2# -{- nonrec -} -AbsBinds [] [] [([], b{-r1,x-}, b_aGC)] - b_aGC - = if PrelBase.True{-5E,p-}{i} then lit_aH1 else lit_aGX -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed b; -_declarations_ -1 b _:_ PrelBase.Int ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc003.hs b/ghc/compiler/tests/typecheck/should_succeed/tc003.hs deleted file mode 100644 index 70459c34434e8f384be1ea391dbc02cbe7527ed6..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc003.hs +++ /dev/null @@ -1,12 +0,0 @@ -module ShouldSucceed where - --- This is a somewhat surprising program. --- It shows up the monomorphism restriction, *and* ambiguity resolution! --- The binding is a pattern binding without a signature, so it is monomorphic. --- Hence the types of c,d,e are not universally quantified. But then --- their type variables are ambiguous, so the ambiguity resolution leaps --- into action, and resolves them to Integer. - --- That's why we check the interface file in the test suite. - -(c@(d,e)) = if True then (1,2) else (1,3) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc003.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc003.stderr deleted file mode 100644 index 612babd265d804251b3ba69899abf2f1da8d58cc..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc003.stderr +++ /dev/null @@ -1,50 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aWN = - PrelBase.$d3{-rb4,p-} -fromInt_aWO = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aWN -lit_aWW = - fromInt_aWO PrelBase.I#{-5b,p-}{i} 1# -fromInt_aWV = - fromInt_aWO -lit_aWU = - fromInt_aWV PrelBase.I#{-5b,p-}{i} 2# -fromInt_aWT = - fromInt_aWO -lit_aWP = - fromInt_aWT PrelBase.I#{-5b,p-}{i} 3# -{- nonrec -} -AbsBinds -[] -[] -[([], c{-r5,x-}, c_aW8), ([], d{-r4,x-}, d_aW9), ([], - e{-r3,x-}, - e_aWa)] - lit_aWX = - lit_aWW - (c_aW8@(d_aW9, e_aWa)) - = if PrelBase.True{-5E,p-}{i} then - (lit_aWW, lit_aWU) - else - (lit_aWX, lit_aWP) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -PrelTup 1 :: $d13 1 $d4 1 $d9 1; -_exports_ -ShouldSucceed c d e; -_declarations_ -1 c _:_ (PrelBase.Int, PrelBase.Int) ;; -1 d _:_ PrelBase.Int ;; -1 e _:_ PrelBase.Int ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc004.hs b/ghc/compiler/tests/typecheck/should_succeed/tc004.hs deleted file mode 100644 index a0627302d4260c96b6edb7da4aa6666fb46f0f6f..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc004.hs +++ /dev/null @@ -1,5 +0,0 @@ -module ShouldSucceed where - -f x = case x of - True -> True - False -> x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc004.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc004.stderr deleted file mode 100644 index 4ead08528638d0241c29660d72c9521e2df7b759..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc004.stderr +++ /dev/null @@ -1,22 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], f{-r3e,x-}, f_an4)] - f_an4 - x_r3d = case x_r3d of - PrelBase.True{-5E,p-}{i} - -> PrelBase.True{-5E,p-}{i} - PrelBase.False{-58,p-}{i} - -> x_r3d -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f; -_declarations_ -1 f _:_ PrelBase.Bool -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc005.hs b/ghc/compiler/tests/typecheck/should_succeed/tc005.hs deleted file mode 100644 index 9d39da891272b17d3d40f3907648ff590fb72417..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc005.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -g ((x:z),y) = x -g (x,y) = 2 diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc005.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc005.stderr deleted file mode 100644 index 82ba4a800dab9f69e67a1e6dcbfefd1d8dc2ba29..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc005.stderr +++ /dev/null @@ -1,35 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aWw-}, t{-aWz-}] -[d.Num_aWD] -[([t{-aWw-}, t{-aWz-}], g{-r3j,x-}, g_aWb)] - fromInt_aWF = - PrelBase.fromInt{-8R,p-} - t{-aWz-} - d.Num_aWD - lit_aWE = - fromInt_aWF PrelBase.I#{-5b,p-}{i} 2# - g_aWb - ((x_r3d PrelBase.:{-55,p-}{i} z_r3e), y_r3f) - = x_r3d - g_aWb - (x_r3h, y_r3i) - = lit_aWE -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -PrelTup 1 :: $d13 1 $d4 1 $d9 1; -_exports_ -ShouldSucceed g; -_declarations_ -1 g _:_ _forall_ [a b] {PrelBase.Num b} => ([b], a) -> b ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc006.hs b/ghc/compiler/tests/typecheck/should_succeed/tc006.hs deleted file mode 100644 index 2a22688d197dfdec32ece11b16db1ae5e64093a2..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc006.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -h = 1:h diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc006.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc006.stderr deleted file mode 100644 index c04ed356376f839716e53467897ed5378524a7ac..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc006.stderr +++ /dev/null @@ -1,31 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aGS = - PrelBase.$d3{-rb0,p-} -fromInt_aGT = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aGS -lit_aGU = - fromInt_aGT PrelBase.I#{-5b,p-}{i} 1# -{- rec -} -AbsBinds [] [] [([], h{-r1,x-}, h_aGC)] - h_aGC - = PrelBase.:{-55,p-}{i} - PrelBase.Int{-3g,p-} - lit_aGU h_aGC -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed h; -_declarations_ -1 h _:_ [PrelBase.Int] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc007.hs b/ghc/compiler/tests/typecheck/should_succeed/tc007.hs deleted file mode 100644 index c65458514bc8a26ac75b67a0c269d49a8b3b56b0..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc007.hs +++ /dev/null @@ -1,9 +0,0 @@ -module ShouldSucceed where - -j = 2 - -k = 1:j:l - -l = 0:k - -m = j+j diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc007.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc007.stderr deleted file mode 100644 index dc81b95263f39651f9c43eaa69c496f6e793dafa..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc007.stderr +++ /dev/null @@ -1,65 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aHp = - PrelBase.$d3{-rb7,p-} -+_aHu = - PrelBase.+{-rR,p-} - PrelBase.Int{-3g,p-} - d.Num_aHp -d.Num_aHt = - d.Num_aHp -fromInt_aHC = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aHt -lit_aHB = - fromInt_aHC PrelBase.I#{-5b,p-}{i} 1# -fromInt_aHA = - fromInt_aHC -lit_aHz = - fromInt_aHA PrelBase.I#{-5b,p-}{i} 0# -fromInt_aHy = - fromInt_aHC -lit_aHv = - fromInt_aHy PrelBase.I#{-5b,p-}{i} 2# -{- nonrec -} -AbsBinds [] [] [([], j{-rV,x-}, j_aGI)] - j_aGI - = lit_aHv -{- nonrec -} -{- rec -} -AbsBinds [] [] [([], k{-rU,x-}, k_aGS), ([], l{-rT,x-}, l_aGT)] - k_aGS - = PrelBase.:{-55,p-}{i} - PrelBase.Int{-3g,p-} - lit_aHB - (PrelBase.:{-55,p-}{i} - PrelBase.Int{-3g,p-} - j{-rV,x-} l_aGT) - l_aGT - = PrelBase.:{-55,p-}{i} - PrelBase.Int{-3g,p-} - lit_aHz k_aGS -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], m{-rS,x-}, m_aHb)] - m_aHb - = j{-rV,x-} +_aHu j{-rV,x-} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed j k l m; -_declarations_ -1 j _:_ PrelBase.Int ;; -1 k _:_ [PrelBase.Int] ;; -1 l _:_ [PrelBase.Int] ;; -1 m _:_ PrelBase.Int ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc008.hs b/ghc/compiler/tests/typecheck/should_succeed/tc008.hs deleted file mode 100644 index 236b575573e08f2dcefbe0432ba1a5f11731a52a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc008.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -n True = 1 -n False = 0 diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc008.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc008.stderr deleted file mode 100644 index 58036c4c5a8003e107c4ee8ec0e26131e66798cf..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc008.stderr +++ /dev/null @@ -1,35 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [t{-aGL-}] [d.Num_aGP] [([t{-aGL-}], n{-r1,x-}, n_aGE)] - fromInt_aGU = - PrelBase.fromInt{-8R,p-} - t{-aGL-} - d.Num_aGP - lit_aGT = - fromInt_aGU PrelBase.I#{-5b,p-}{i} 1# - fromInt_aGS = - fromInt_aGU - lit_aGQ = - fromInt_aGS PrelBase.I#{-5b,p-}{i} 0# - n_aGE - PrelBase.True{-5E,p-}{i} - = lit_aGT - n_aGE - PrelBase.False{-58,p-}{i} - = lit_aGQ -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed n; -_declarations_ -1 n _:_ _forall_ [a] {PrelBase.Num a} => PrelBase.Bool -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc009.hs b/ghc/compiler/tests/typecheck/should_succeed/tc009.hs deleted file mode 100644 index b682a94c0d224f7950508ae6c4db46be80fb6a61..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc009.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -o (True,x) = x -o (False,y) = y+1 diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc009.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc009.stderr deleted file mode 100644 index 968ef4ad6304bf3b896522186237f4d0534b6b66..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc009.stderr +++ /dev/null @@ -1,38 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [t{-aWp-}] [d.Num_aWs] [([t{-aWp-}], o{-r3h,x-}, o_aW8)] - +_aWy = - PrelBase.+{-r3g,p-} - t{-aWp-} - d.Num_aWs - d.Num_aWv = - d.Num_aWs - fromInt_aWx = - PrelBase.fromInt{-8R,p-} - t{-aWp-} - d.Num_aWv - lit_aWw = - fromInt_aWx PrelBase.I#{-5b,p-}{i} 1# - o_aW8 - (PrelBase.True{-5E,p-}{i}, x_r3d) - = x_r3d - o_aW8 - (PrelBase.False{-58,p-}{i}, y_r3f) - = y_r3f +_aWy lit_aWw -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -PrelTup 1 :: $d13 1 $d4 1 $d9 1; -_exports_ -ShouldSucceed o; -_declarations_ -1 o _:_ _forall_ [a] {PrelBase.Num a} => (PrelBase.Bool, a) -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc010.hs b/ghc/compiler/tests/typecheck/should_succeed/tc010.hs deleted file mode 100644 index 8ec9afd3d0e78e7e1f4338b4e4596ebc917d8511..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc010.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -p = [(y+2,True) | y <- [1,2]] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc010.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc010.stderr deleted file mode 100644 index 09456511c6858bad259c5f26ac7dc3d56e1b5d9a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc010.stderr +++ /dev/null @@ -1,55 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aXA = - PrelBase.$d3{-rb3,p-} -fromInt_aXN = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aXA -lit_aXT = - fromInt_aXN PrelBase.I#{-5b,p-}{i} 1# -fromInt_aXS = - fromInt_aXN -lit_aXR = - fromInt_aXS PrelBase.I#{-5b,p-}{i} 2# -d.Num_aXE = - d.Num_aXA -+_aXQ = - PrelBase.+{-rau,p-} - PrelBase.Int{-3g,p-} - d.Num_aXE -d.Monad_aXG = - PrelBase.$d24{-raX,p-} ->>=_aXP = - PrelBase.>>={-811,p-} - PrelBase.[]{-3j,p-} - d.Monad_aXG -d.Monad_aXJ = - d.Monad_aXG -return_aXO = - PrelBase.return{-816,p-} - PrelBase.[]{-3j,p-} - d.Monad_aXJ -{- nonrec -} -AbsBinds [] [] [([], p{-r3e,x-}, p_aWR)] - lit_aXU = - lit_aXR - p_aWR - = [ (y_r3d +_aXQ lit_aXU, PrelBase.True{-5E,p-}{i}) | - y_r3d <- [lit_aXT, lit_aXR] (PrelBase.Int{-3g,p-}) ] -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d23 1 $d24 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Monad 1 MonadZero 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -PrelTup 1 :: $d13 1 $d4 1 $d9 1; -_exports_ -ShouldSucceed p; -_declarations_ -1 p _:_ [(PrelBase.Int, PrelBase.Bool)] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc011.hs b/ghc/compiler/tests/typecheck/should_succeed/tc011.hs deleted file mode 100644 index 24c5b3b91b344373de24dd6562fe73ea39d9ef77..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc011.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -x@_ = x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc011.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc011.stderr deleted file mode 100644 index 9a2b6286501d8890cc89a5feade7ebd1dfa8fbf6..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc011.stderr +++ /dev/null @@ -1,18 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- rec -} -AbsBinds [t{-an2-}] [] [([t{-an2-}], x{-r1,x-}, x_an0)] - (x_an0@_) - = x_an0 -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed x; -_declarations_ -1 x _:_ _forall_ [a] => a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc012.hs b/ghc/compiler/tests/typecheck/should_succeed/tc012.hs deleted file mode 100644 index 6f5e9542204245244594b568536bc875c39ee511..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc012.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -q = \ y -> y diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc012.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc012.stderr deleted file mode 100644 index cfa99021ca5be60dbf2e7e1357fd88a4ceb52627..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc012.stderr +++ /dev/null @@ -1,18 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [t{-an8-}] [] [([t{-an8-}], q{-r3e,x-}, q_an2)] - q_an2 - = \ y_r3d -> y_r3d -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed q; -_declarations_ -1 q _:_ _forall_ [a] => a -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc013.hs b/ghc/compiler/tests/typecheck/should_succeed/tc013.hs deleted file mode 100644 index f6a08b5e7b68130fb18cad4d9d5ef5dd114b7d28..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc013.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -(r,s) = (1,'a') diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc013.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc013.stderr deleted file mode 100644 index 1c09f6b6df3f1cadb38aa3be28fc32ee1a686c1c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc013.stderr +++ /dev/null @@ -1,31 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aWr = - PrelBase.$d3{-rb2,p-} -fromInt_aWs = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aWr -lit_aWt = - fromInt_aWs PrelBase.I#{-5b,p-}{i} 1# -{- nonrec -} -AbsBinds [] [] [([], r{-r3,x-}, r_aW6), ([], s{-r2,x-}, s_aW7)] - (r_aW6, s_aW7) - = (lit_aWt, 'a') -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -PrelTup 1 :: $d13 1 $d4 1 $d9 1; -_exports_ -ShouldSucceed r s; -_declarations_ -1 r _:_ PrelBase.Int ;; -1 s _:_ PrelBase.Char ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc014.hs b/ghc/compiler/tests/typecheck/should_succeed/tc014.hs deleted file mode 100644 index 97ce37558351b6356d77190dada67e6561a458d7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc014.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -t = 1+t diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc014.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc014.stderr deleted file mode 100644 index 06a5c5c2528f137dba83a6b350ad3d0385ee6fc1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc014.stderr +++ /dev/null @@ -1,35 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aGW = - PrelBase.$d3{-rb1,p-} -+_aH1 = - PrelBase.+{-rO,p-} - PrelBase.Int{-3g,p-} - d.Num_aGW -d.Num_aH0 = - d.Num_aGW -fromInt_aH3 = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aH0 -lit_aH2 = - fromInt_aH3 PrelBase.I#{-5b,p-}{i} 1# -{- rec -} -AbsBinds [] [] [([], t{-rP,x-}, t_aGC)] - t_aGC - = lit_aH2 +_aH1 t_aGC -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed t; -_declarations_ -1 t _:_ PrelBase.Int ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc015.hs b/ghc/compiler/tests/typecheck/should_succeed/tc015.hs deleted file mode 100644 index 41c902bfc6b56a338036d0bc3b4f88a897be2877..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc015.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -u x = \ (y,z) -> x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc015.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc015.stderr deleted file mode 100644 index 55667c8ce63a6195eecada9b2519b5d7b55bee72..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc015.stderr +++ /dev/null @@ -1,22 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aB8-}, t{-aBb-}, t{-aBg-}] -[] -[([t{-aB8-}, t{-aBb-}, t{-aBg-}], u{-r3h,x-}, u_aB2)] - u_aB2 - x_r3d = \ (y_r3f, z_r3g) - -> x_r3d -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed u; -_declarations_ -1 u _:_ _forall_ [a b c] => c -> (a, b) -> c ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc016.hs b/ghc/compiler/tests/typecheck/should_succeed/tc016.hs deleted file mode 100644 index 5f3c7e57215f016151f806f03af383b3ce60e906..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc016.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -f x@_ y@_ = x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc016.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc016.stderr deleted file mode 100644 index fb20a6fa3e6375d9773633f929e3b3919400323f..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc016.stderr +++ /dev/null @@ -1,22 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-ang-}, t{-ani-}] -[] -[([t{-ang-}, t{-ani-}], f{-r3g,x-}, f_an4)] - f_an4 - (x_r3d@_) (y_r3f@_) - = x_r3d -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f; -_declarations_ -1 f _:_ _forall_ [a b] => a -> b -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc017.hs b/ghc/compiler/tests/typecheck/should_succeed/tc017.hs deleted file mode 100644 index ec51aeb8d0b385b00566816584acd970d5dd6b89..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc017.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -v | True = v+1 - | False = v diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc017.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc017.stderr deleted file mode 100644 index 22fc7d4e9628167af0489165e7f3fdbb21919a44..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc017.stderr +++ /dev/null @@ -1,38 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aGW = - PrelBase.$d3{-rb1,p-} -+_aH1 = - PrelBase.+{-ras,p-} - PrelBase.Int{-3g,p-} - d.Num_aGW -d.Num_aH0 = - d.Num_aGW -fromInt_aH3 = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aH0 -lit_aH2 = - fromInt_aH3 PrelBase.I#{-5b,p-}{i} 1# -{- rec -} -AbsBinds [] [] [([], v{-r1,x-}, v_aGC)] - v_aGC - | [PrelBase.True{-5E,p-}{i}] = - v_aGC +_aH1 lit_aH2 - | [PrelBase.False{-58,p-}{i}] = - v_aGC -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed v; -_declarations_ -1 v _:_ PrelBase.Int ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc018.hs b/ghc/compiler/tests/typecheck/should_succeed/tc018.hs deleted file mode 100644 index 7fb398c6e65115832536c0081b0daf2d349de0b8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc018.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -w = a where a = y - y = 2 diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc018.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc018.stderr deleted file mode 100644 index b019ba6de6d06eb5cacb1984df18014b596f7956..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc018.stderr +++ /dev/null @@ -1,40 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aH4 = - PrelBase.$d3{-rb3,p-} -fromInt_aH5 = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aH4 -lit_aH6 = - fromInt_aH5 PrelBase.I#{-5b,p-}{i} 2# -{- nonrec -} -AbsBinds [] [] [([], w{-r3f,x-}, w_aGI)] - w_aGI - = a_r3d - where - {- nonrec -} - AbsBinds [] [] [([], y_r3e, y_aGH)] - y_aGH - = lit_aH6 - {- nonrec -} - {- nonrec -} - AbsBinds [] [] [([], a_r3d, a_aGT)] - a_aGT - = y_r3e - {- nonrec -} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed w; -_declarations_ -1 w _:_ PrelBase.Int ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc019.hs b/ghc/compiler/tests/typecheck/should_succeed/tc019.hs deleted file mode 100644 index 3cfe5ea62699a673848ec7cfd0d4ff2f721c4b0c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc019.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -(al:am) = [y+1 | (y,z) <- [(1,2)]] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc019.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc019.stderr deleted file mode 100644 index 9acf57e10453b3b043adf30f5f9bc56633acd93c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc019.stderr +++ /dev/null @@ -1,61 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aY3 = - PrelBase.$d3{-rb6,p-} -fromInt_aYg = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aY3 -lit_aYm = - fromInt_aYg PrelBase.I#{-5b,p-}{i} 1# -fromInt_aYl = - fromInt_aYg -lit_aYk = - fromInt_aYl PrelBase.I#{-5b,p-}{i} 2# -d.Num_aY7 = - d.Num_aY3 -+_aYj = - PrelBase.+{-r3g,p-} - PrelBase.Int{-3g,p-} - d.Num_aY7 -d.Monad_aY9 = - PrelBase.$d24{-rb0,p-} ->>=_aYi = - PrelBase.>>={-811,p-} - PrelBase.[]{-3j,p-} - d.Monad_aY9 -d.Monad_aYc = - d.Monad_aY9 -return_aYh = - PrelBase.return{-816,p-} - PrelBase.[]{-3j,p-} - d.Monad_aYc -{- nonrec -} -AbsBinds -[] -[] -[([], al{-r3i,x-}, al_aWK), ([], am{-r3h,x-}, am_aWL)] - lit_aYn = - lit_aYm - (al_aWK PrelBase.:{-55,p-}{i} am_aWL) - = [ y_r3e +_aYj lit_aYn | - (y_r3e, z_r3f) <- [(lit_aYm, - lit_aYk)] ((PrelBase.Int{-3g,p-}, PrelBase.Int{-3g,p-})) - ] -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d23 1 $d24 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Monad 1 MonadZero 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -PrelTup 1 :: $d13 1 $d4 1 $d9 1; -_exports_ -ShouldSucceed al am; -_declarations_ -1 al _:_ PrelBase.Int ;; -1 am _:_ [PrelBase.Int] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc020.hs b/ghc/compiler/tests/typecheck/should_succeed/tc020.hs deleted file mode 100644 index a0ef679c8fc93c029737cea1f8ee0194427aa9c0..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc020.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -f x = a where a = x:a diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc020.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc020.stderr deleted file mode 100644 index 10bd436e448d753774ab13b30b2d1938db76b917..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc020.stderr +++ /dev/null @@ -1,26 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [t{-anb-}] [] [([t{-anb-}], f{-r3g,x-}, f_an4)] - f_an4 - x_r3d = a_r3f - where - {- rec -} - AbsBinds [] [] [([], a_r3f, a_an8)] - a_an8 - = PrelBase.:{-55,p-}{i} - t{-anb-} - x_r3d a_an8 - {- nonrec -} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f; -_declarations_ -1 f _:_ _forall_ [a] => a -> [a] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc021.hs b/ghc/compiler/tests/typecheck/should_succeed/tc021.hs deleted file mode 100644 index 418fa38e2918599cf86e4b26eabf4eb34d975257..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc021.hs +++ /dev/null @@ -1,7 +0,0 @@ -module ShouldSucceed where - -f x = a - -a = (x,x) - -x = x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc021.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc021.stderr deleted file mode 100644 index 4e4b624152cdeaefce7ebc05592bdc6b38dd6d98..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc021.stderr +++ /dev/null @@ -1,40 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- rec -} -AbsBinds [t{-aB5-}] [] [([t{-aB5-}], x{-r3g,x-}, x_aB3)] - x_aB3 - = x_aB3 -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aBb-}, t{-aBd-}] -[] -[([t{-aBb-}, t{-aBd-}], a{-r3h,x-}, a_aB7)] - a_aB7 - = (x{-r3g,x-} - t{-aBb-}, - x{-r3g,x-} - t{-aBd-}) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aBp-}, t{-aBl-}, t{-aBn-}] -[] -[([t{-aBp-}, t{-aBl-}, t{-aBn-}], f{-r3i,x-}, f_aBf)] - f_aBf - x_r3f = a{-r3h,x-} - [t{-aBl-}, t{-aBn-}] -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed a f x; -_declarations_ -1 a _:_ _forall_ [a b] => (a, b) ;; -1 f _:_ _forall_ [a b c] => a -> (b, c) ;; -1 x _:_ _forall_ [a] => a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc022.hs b/ghc/compiler/tests/typecheck/should_succeed/tc022.hs deleted file mode 100644 index 1a04d7e7a28be4fb5b831cd28f0d53eb417245d4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc022.hs +++ /dev/null @@ -1,5 +0,0 @@ -module ShouldSucceed where - -main = iD iD - -iD x = x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc022.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc022.stderr deleted file mode 100644 index 4dba0959934a6032515beab68209e7f463f67966..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc022.stderr +++ /dev/null @@ -1,26 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [t{-ana-}] [] [([t{-ana-}], iD{-r3f,x-}, iD_an4)] - iD_an4 - x_r3e = x_r3e -{- nonrec -} -{- nonrec -} -AbsBinds [t{-anh-}] [] [([t{-anh-}], main{-r3g,x-}, main_anc)] - main_anc - = iD{-r3f,x-} - (t{-anh-} -> t{-anh-}) iD{-r3f,x-} - t{-anh-} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed iD main; -_declarations_ -1 iD _:_ _forall_ [a] => a -> a ;; -1 main _:_ _forall_ [a] => a -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc023.hs b/ghc/compiler/tests/typecheck/should_succeed/tc023.hs deleted file mode 100644 index b996719bb9bcc6165aee8eb0f92066a5a0220437..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc023.hs +++ /dev/null @@ -1,7 +0,0 @@ -module ShouldSucceed where - -main = s k k - -s f g x = f x (g x) - -k x y = x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc023.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc023.stderr deleted file mode 100644 index 93888dfe67c74783481e1487016da4ef3dc376fc..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc023.stderr +++ /dev/null @@ -1,43 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-anm-}, t{-ano-}] -[] -[([t{-anm-}, t{-ano-}], k{-r3o,x-}, k_ane)] - k_ane - x_r3l y_r3n - = x_r3l -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-anM-}, t{-anO-}, t{-anQ-}] -[] -[([t{-anM-}, t{-anO-}, t{-anQ-}], s{-r3p,x-}, s_anq)] - s_anq - f_r3f g_r3h x_r3j - = f_r3f x_r3j g_r3h x_r3j -{- nonrec -} -{- nonrec -} -AbsBinds [t{-ao5-}] [] [([t{-ao5-}], main{-r3q,x-}, main_anS)] - main_anS - = s{-r3p,x-} - [t{-ao5-}, GHC.Void{-3T,p-} -> t{-ao5-}, t{-ao5-}] k{-r3o,x-} - [t{-ao5-}, GHC.Void{-3T,p-} - -> t{-ao5-}] - k{-r3o,x-} - [t{-ao5-}, GHC.Void{-3T,p-}] -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed k main s; -_declarations_ -1 k _:_ _forall_ [a b] => a -> b -> a ;; -1 main _:_ _forall_ [a] => a -> a ;; -1 s _:_ _forall_ [a b c] => (a -> b -> c) -> (a -> b) -> a -> c ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc024.hs b/ghc/compiler/tests/typecheck/should_succeed/tc024.hs deleted file mode 100644 index e28d1acf96c827e8577479b5d27ce7eaeb03e0ab..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc024.hs +++ /dev/null @@ -1,7 +0,0 @@ -module ShouldSucceed where - -main x = s k k x - -s f g x = f x (g x) - -k x y = x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc024.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc024.stderr deleted file mode 100644 index 3ccc000e65e17a1f808ea28940a2c32eece42c1d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc024.stderr +++ /dev/null @@ -1,44 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-ano-}, t{-anq-}] -[] -[([t{-ano-}, t{-anq-}], k{-r3q,x-}, k_ang)] - k_ang - x_r3n y_r3p - = x_r3n -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-anO-}, t{-anQ-}, t{-anS-}] -[] -[([t{-anO-}, t{-anQ-}, t{-anS-}], s{-r3r,x-}, s_ans)] - s_ans - f_r3h g_r3j x_r3l - = f_r3h x_r3l g_r3j x_r3l -{- nonrec -} -{- nonrec -} -AbsBinds [t{-ao8-}] [] [([t{-ao8-}], main{-r3s,x-}, main_anU)] - main_anU - x_r3f = s{-r3r,x-} - [t{-ao8-}, GHC.Void{-3T,p-} -> t{-ao8-}, t{-ao8-}] k{-r3q,x-} - [t{-ao8-}, GHC.Void{-3T,p-} - -> t{-ao8-}] - k{-r3q,x-} - [t{-ao8-}, GHC.Void{-3T,p-}] - x_r3f -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed k main s; -_declarations_ -1 k _:_ _forall_ [a b] => a -> b -> a ;; -1 main _:_ _forall_ [a] => a -> a ;; -1 s _:_ _forall_ [a b c] => (a -> b -> c) -> (a -> b) -> a -> c ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc025.hs b/ghc/compiler/tests/typecheck/should_succeed/tc025.hs deleted file mode 100644 index e9adf9acb5713e387877dae7251ec697ff70219c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc025.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -g x = f (f True x) x where f x y = if x then y else (f x y) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc025.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc025.stderr deleted file mode 100644 index 6d8890057fe7c95f86e0d555773249c12835e63d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc025.stderr +++ /dev/null @@ -1,29 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], g{-r3k,x-}, g_an8)] - g_an8 - x_r3d = f_r3f - PrelBase.Bool{-34,p-} f_r3f - PrelBase.Bool{-34,p-} PrelBase.True{-5E,p-}{i} - x_r3d - x_r3d - where - {- rec -} - AbsBinds [t{-ant-}] [] [([t{-ant-}], f_r3f, f_anc)] - f_anc - x_r3h y_r3j - = if x_r3h then y_r3j else f_anc x_r3h y_r3j - {- nonrec -} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed g; -_declarations_ -1 g _:_ PrelBase.Bool -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc026.hs b/ghc/compiler/tests/typecheck/should_succeed/tc026.hs deleted file mode 100644 index 3e718a5053a541c4edcfc0ff2891c8f8e9015e46..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc026.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -g x = f (f True x) x -f x y = if x then y else (f x y) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc026.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc026.stderr deleted file mode 100644 index 19f26efe2581c563d2a5b3b5bd5eb737fd6e18fd..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc026.stderr +++ /dev/null @@ -1,29 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- rec -} -AbsBinds [t{-ann-}] [] [([t{-ann-}], f{-r3j,x-}, f_an8)] - f_an8 - x_r3g y_r3i - = if x_r3g then y_r3i else f_an8 x_r3g y_r3i -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], g{-r3k,x-}, g_anp)] - g_anp - x_r3e = f{-r3j,x-} - PrelBase.Bool{-34,p-} f{-r3j,x-} - PrelBase.Bool{-34,p-} PrelBase.True{-5E,p-}{i} - x_r3e - x_r3e -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f g; -_declarations_ -1 f _:_ _forall_ [a] => PrelBase.Bool -> a -> a ;; -1 g _:_ PrelBase.Bool -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc027.hs b/ghc/compiler/tests/typecheck/should_succeed/tc027.hs deleted file mode 100644 index 6edc01b619fc0154b767f4f787698407d9505ad4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc027.hs +++ /dev/null @@ -1,5 +0,0 @@ -module ShouldSucceed where - -h x = f (f True x) x -f x y = if x then y else (g y x) -g y x = if x then y else (f x y) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc027.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc027.stderr deleted file mode 100644 index eaa43723fcd62e0c0c24a30c1e5d94937ff5ea83..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc027.stderr +++ /dev/null @@ -1,38 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- rec -} -AbsBinds -[t{-anz-}] -[] -[([t{-anz-}], f{-r3p,x-}, f_ane), ([t{-anz-}], g{-r3o,x-}, g_anf)] - f_ane - x_r3h y_r3j - = if x_r3h then y_r3j else g_anf y_r3j x_r3h - g_anf - y_r3l x_r3n - = if x_r3n then y_r3l else f_ane x_r3n y_r3l -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], h{-r3q,x-}, h_anB)] - h_anB - x_r3f = f{-r3p,x-} - PrelBase.Bool{-34,p-} f{-r3p,x-} - PrelBase.Bool{-34,p-} PrelBase.True{-5E,p-}{i} - x_r3f - x_r3f -{- nonrec -} - -NOTE: Simplifier still going after 4 iterations; bailing out. -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f g h; -_declarations_ -1 f _:_ _forall_ [a] => PrelBase.Bool -> a -> a ;; -1 g _:_ _forall_ [a] => a -> PrelBase.Bool -> a ;; -1 h _:_ PrelBase.Bool -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc028.hs b/ghc/compiler/tests/typecheck/should_succeed/tc028.hs deleted file mode 100644 index 49a0835ade2708803ec6bc34aa5af23f46be3b34..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc028.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -type H = (Int,Bool) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc028.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc028.stderr deleted file mode 100644 index 3132154684fb8c44b00a2e25ae6886afd30c2c3a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc028.stderr +++ /dev/null @@ -1,13 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed H; -_declarations_ -1 type H = (PrelBase.Int, PrelBase.Bool) ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc029.hs b/ghc/compiler/tests/typecheck/should_succeed/tc029.hs deleted file mode 100644 index c44b78f79f1fc3ae1b588589aee90e67f395d2d7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc029.hs +++ /dev/null @@ -1,6 +0,0 @@ -module ShouldSucceed where - -type G = [Int] - -data K = H Bool | M G - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc029.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc029.stderr deleted file mode 100644 index 465e4a76a605e805f7e31af9ff2b5e9503e445a8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc029.stderr +++ /dev/null @@ -1,32 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -H{-r4,x-}{i} = - \ tpl_B1 -> - H{-r4,x-}{i} - {tpl_B1} -M{-r3,x-}{i} = - \ tpl_B1 -> - M{-r3,x-}{i} - {tpl_B1} -{- rec -} -AbsBinds [] [] [([], $d1{-rG9,x-}, d.Eval_aG6)] - d.Eval_aG6 = - ({-dict-} [] []) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d44 1 $d46 1 Eval 1; -_exports_ -ShouldSucceed G K(H M); -_instances_ -instance {PrelBase.Eval K} = $d1; -_declarations_ -1 $d1 _:_ {PrelBase.Eval K} ;; -1 type G = [PrelBase.Int] ; -1 data K = H PrelBase.Bool | M G ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc030.hs b/ghc/compiler/tests/typecheck/should_succeed/tc030.hs deleted file mode 100644 index 004bc226d1ff29c3da0d869601ae9a5e508b37de..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc030.hs +++ /dev/null @@ -1,5 +0,0 @@ -module ShouldSucceed where - -type H = [Bool] - -type G = (H,Char) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc030.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc030.stderr deleted file mode 100644 index b46901ecb77b04958779b48f720ae202ffda5624..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc030.stderr +++ /dev/null @@ -1,14 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed G H; -_declarations_ -1 type G = (H, PrelBase.Char) ; -1 type H = [PrelBase.Bool] ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc031.hs b/ghc/compiler/tests/typecheck/should_succeed/tc031.hs deleted file mode 100644 index c55bf11f54096f1622492f623067bb5531238607..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc031.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -data Rec = Node Int Rec diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc031.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc031.stderr deleted file mode 100644 index 530d74b6086fa2d783918864095e60c0e3a6d418..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc031.stderr +++ /dev/null @@ -1,27 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -Node{-r2,x-}{i} = - \ tpl_B1 tpl_B2 -> - Node{-r2,x-}{i} - {tpl_B1 tpl_B2} -{- rec -} -AbsBinds [] [] [([], $d1{-rFX,x-}, d.Eval_aFU)] - d.Eval_aFU = - ({-dict-} [] []) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1; -_exports_ -ShouldSucceed Rec(Node); -_instances_ -instance {PrelBase.Eval Rec} = $d1; -_declarations_ -1 $d1 _:_ {PrelBase.Eval Rec} ;; -1 data Rec = Node PrelBase.Int Rec ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc032.hs b/ghc/compiler/tests/typecheck/should_succeed/tc032.hs deleted file mode 100644 index 9c43bbb0100d890c5203dcaf3789763bd5476392..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc032.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -data AList b = Node b [b] | Other (b,Char) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc032.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc032.stderr deleted file mode 100644 index a0bbfe6932c41165ceb36f1313ed76cd0852b5b6..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc032.stderr +++ /dev/null @@ -1,32 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -Node{-r4,x-}{i} = - _/\_ b{-r3h-} -> \ tpl_B1 tpl_B2 -> - Node{-r4,x-}{i} - {_@_ b{-r3h-} tpl_B1 tpl_B2} -Other{-r3,x-}{i} = - _/\_ b{-r3h-} -> \ tpl_B1 -> - Other{-r3,x-}{i} - {_@_ b{-r3h-} tpl_B1} -{- rec -} -AbsBinds [b{-aVe-}] [] [([b{-aVe-}], $d1{-rVh,x-}, d.Eval_aVd)] - d.Eval_aVd = - ({-dict-} [] []) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d38 1 $d39 1 $d41 1 $d44 1 $d46 1 Eval 1; -PrelTup 1 :: $d13 1; -_exports_ -ShouldSucceed AList(Node Other); -_instances_ -instance _forall_ [a] => {PrelBase.Eval (AList a)} = $d1; -_declarations_ -1 $d1 _:_ _forall_ [a] => {PrelBase.Eval (AList a)} ;; -1 data AList r3h = Node r3h [r3h] | Other (r3h, PrelBase.Char) ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc033.hs b/ghc/compiler/tests/typecheck/should_succeed/tc033.hs deleted file mode 100644 index 7111d75a4eea04d3271cab22ee2dccd3a02594c1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc033.hs +++ /dev/null @@ -1,7 +0,0 @@ -module ShouldSucceed where - -data Twine = Twine2 Twist - -data Twist = Twist2 Twine - -type F = Twine diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc033.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc033.stderr deleted file mode 100644 index 26bba1397e7df9b400850db997244616652627a5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc033.stderr +++ /dev/null @@ -1,40 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -Twist2{-r4,x-}{i} = - \ tpl_B1 -> - Twist2{-r4,x-}{i} - {tpl_B1} -{- nonrec -} -Twine2{-r8,x-}{i} = - \ tpl_B1 -> - Twine2{-r8,x-}{i} - {tpl_B1} -{- rec -} -AbsBinds [] [] [([], $d1{-rGe,x-}, d.Eval_aG6)] - d.Eval_aG6 = - ({-dict-} [] []) -{- rec -} -AbsBinds [] [] [([], $d2{-rGg,x-}, d.Eval_aGb)] - d.Eval_aGb = - ({-dict-} [] []) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1; -_exports_ -ShouldSucceed F Twine(Twine2) Twist(Twist2); -_instances_ -instance {PrelBase.Eval Twist} = $d1; -instance {PrelBase.Eval Twine} = $d2; -_declarations_ -1 $d1 _:_ {PrelBase.Eval Twist} ;; -1 $d2 _:_ {PrelBase.Eval Twine} ;; -1 type F = Twine ; -1 data Twine = Twine2 Twist ; -1 data Twist = Twist2 Twine ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc034.hs b/ghc/compiler/tests/typecheck/should_succeed/tc034.hs deleted file mode 100644 index 0e7c4a66ed995d2c5b9101dd37b565181920b197..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc034.hs +++ /dev/null @@ -1,11 +0,0 @@ -module ShouldSucceed where - -data AList a = ANull | ANode a (AList a) - -type IntList = AList Int - -g (ANull) = 2 -g (ANode b (ANode c d)) | b = 3 - | True = 4 - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc034.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc034.stderr deleted file mode 100644 index 6c18bd9880ca255fd9110d869ee2f6baf24c01ce..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc034.stderr +++ /dev/null @@ -1,63 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -ANull{-r6,x-}{i} = - _/\_ a{-r3p-} -> - ANull{-r6,x-}{i} - {_@_ a{-r3p-}} -ANode{-r5,x-}{i} = - _/\_ a{-r3p-} -> \ tpl_B1 tpl_B2 -> - ANode{-r5,x-}{i} - {_@_ a{-r3p-} tpl_B1 tpl_B2} -{- rec -} -AbsBinds [a{-aHA-}] [] [([a{-aHA-}], $d1{-rHD,x-}, d.Eval_aHz)] - d.Eval_aHz = - ({-dict-} [] []) -{- nonrec -} -{- nonrec -} -AbsBinds [t{-aHn-}] [d.Num_aHr] [([t{-aHn-}], g{-r3q,x-}, g_aH1)] - fromInt_aHJ = - PrelBase.fromInt{-8R,p-} - t{-aHn-} - d.Num_aHr - lit_aHI = - fromInt_aHJ PrelBase.I#{-5b,p-}{i} 2# - fromInt_aHH = - fromInt_aHJ - lit_aHG = - fromInt_aHH PrelBase.I#{-5b,p-}{i} 3# - fromInt_aHF = - fromInt_aHJ - lit_aHE = - fromInt_aHF PrelBase.I#{-5b,p-}{i} 4# - g_aH1 - ANull{-r6,x-}{i} - = lit_aHI - g_aH1 - (ANode{-r5,x-}{i} b_r3k (ANode{-r5,x-}{i} c_r3l d_r3m)) - | [b_r3k] = - lit_aHG - | [PrelBase.True{-5E,p-}{i}] = - lit_aHE -{- nonrec -} -tc034.hs:7: - Warning: Possibly incomplete patterns - in the definition of function `g' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed g AList(ANull ANode) IntList; -_instances_ -instance _forall_ [a] => {PrelBase.Eval (AList a)} = $d1; -_declarations_ -1 $d1 _:_ _forall_ [a] => {PrelBase.Eval (AList a)} ;; -1 data AList r3p = ANull | ANode r3p (AList r3p) ; -1 type IntList = AList PrelBase.Int ; -1 g _:_ _forall_ [a] {PrelBase.Num a} => AList PrelBase.Bool -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc035.hs b/ghc/compiler/tests/typecheck/should_succeed/tc035.hs deleted file mode 100644 index b8dd5543736d46b4f588985d6174bbc0f4ebfa0d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc035.hs +++ /dev/null @@ -1,9 +0,0 @@ -module ShouldSucceed where - -type AnnExpr a = (a,Expr a) - -data Expr a = Var [Char] - | App (AnnExpr a) (AnnExpr a) - -g (a,(Var name)) = [name] -g (a,(App e1 e2)) = (g e1) ++ (g e2) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc035.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc035.stderr deleted file mode 100644 index 00d21101c54818e49bd2a8176e9b90eb48f1ad5f..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc035.stderr +++ /dev/null @@ -1,51 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -Var{-r5,x-}{i} = - _/\_ a{-r3q-} -> \ tpl_B1 -> - Var{-r5,x-}{i} - {_@_ a{-r3q-} tpl_B1} -App{-r4,x-}{i} = - _/\_ a{-r3q-} -> \ tpl_B1 tpl_B2 -> - App{-r4,x-}{i} - {_@_ a{-r3q-} tpl_B1 tpl_B2} -{- rec -} -AbsBinds [a{-aWY-}] [] [([a{-aWY-}], $d1{-rX1,x-}, d.Eval_aWV)] - d.Eval_aWV = - ({-dict-} [] []) -{- nonrec -} -d.MonadPlus_aWX = - PrelBase.$d22{-rq5,p-} -++_aX2 = - PrelBase.++{-rur,p-} - PrelBase.[]{-3j,p-} - d.MonadPlus_aWX -{- rec -} -AbsBinds [t{-aWD-}] [] [([t{-aWD-}], g{-r3t,x-}, g_aWg)] - g_aWg - (a_r3j, (Var{-r5,x-}{i} name_r3k)) - = [name_r3k] ([PrelBase.Char{-38,p-}]) - g_aWg - (a_r3m, (App{-r4,x-}{i} e1_r3n e2_r3o)) - = ++_aX2 - [PrelBase.Char{-38,p-}] - (g_aWg e1_r3n) (g_aWg e2_r3o) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d22 1 $d23 1 $d24 1 $d37 1 $d38 1 $d39 1 $d41 1 $d44 1 $d46 1 Eval 1 Monad 1 MonadPlus 1 MonadZero 1; -PrelTup 1 :: $d13 1; -_exports_ -ShouldSucceed g AnnExpr Expr(Var App); -_instances_ -instance _forall_ [a] => {PrelBase.Eval (Expr a)} = $d1; -_declarations_ -1 $d1 _:_ _forall_ [a] => {PrelBase.Eval (Expr a)} ;; -1 type AnnExpr r3s = (r3s, Expr r3s) ; -1 data Expr r3q = Var [PrelBase.Char] | App (AnnExpr r3q) (AnnExpr r3q) ; -1 g _:_ _forall_ [a] => (a, Expr a) -> [[PrelBase.Char]] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc036.hs b/ghc/compiler/tests/typecheck/should_succeed/tc036.hs deleted file mode 100644 index 05b87846aca15ed96e1d567bccc314420c57fe56..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc036.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -class (Eq a) => A a where - op1 :: a -> a diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc036.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc036.stderr deleted file mode 100644 index 5e4ec7a69f39e9e0124ee80f1a9f20e21f1b963c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc036.stderr +++ /dev/null @@ -1,33 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_APrelBaseEq{-aG7,x-} = - _/\_ a{-r3e-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -op1{-r3f,x-} = - _/\_ a{-r3e-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aG6-}] -[d.A_aFZ] -[([a{-aG6-}], $mop1{-rG8,x-}, op1_aG1)] - AbsBinds [] [] [([], op1_aG1, op1_aG3)] - op1_aG3 - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aG6-} -> a{-aG6-}) "Class A Method op1" -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d15 1 $d32 1 $d7 1 Eq 1; -PrelNum 1 :: $d18 1; -_exports_ -ShouldSucceed A(op1); -_declarations_ -1 $mop1 _:_ _forall_ [a] {A a} => a -> a ;; -1 class {PrelBase.Eq r3e} => A r3e where {op1 :: r3e -> r3e} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc037.hi b/ghc/compiler/tests/typecheck/should_succeed/tc037.hi deleted file mode 100644 index 026e6c2b5cd8e9c104ba616a3541a21628ffcba2..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc037.hi +++ /dev/null @@ -1,6 +0,0 @@ -interface ShouldSucceed where { -class Eq' a where { - deq :: a -> a -> Bool - }; -instance (Eq' a) => Eq' [a] {-# FROMMODULE ShouldSucceed #-} -} diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc037.hs b/ghc/compiler/tests/typecheck/should_succeed/tc037.hs deleted file mode 100644 index 8621b278d32e4da8bf04514aea367b0cc44f009e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc037.hs +++ /dev/null @@ -1,9 +0,0 @@ -module ShouldSucceed where - -class Eq' a where - deq :: a -> a -> Bool - -instance (Eq' a) => Eq' [a] where - deq [] [] = True - deq (x:xs) (y:ys) = if (x `deq` y) then (deq xs ys) else False - deq other1 other2 = False diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc037.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc037.stderr deleted file mode 100644 index d506e3cf75d850df3c2b0f7aa5edd8320a9f0e45..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc037.stderr +++ /dev/null @@ -1,67 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -deq{-r3x,x-} = - _/\_ a{-r3w-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aog-}] -[d.Eq'_ao9] -[([a{-aog-}], $mdeq{-rnR,x-}, deq_aob)] - AbsBinds [] [] [([], deq_aob, deq_aod)] - deq_aod - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aog-} - -> a{-aog-} - -> PrelBase.Bool{-34,p-}) "Class Eq' Method deq" -{- rec -} -AbsBinds -[a{-anC-}] -[d.Eq'_ao2] -[([a{-anC-}], $d1{-roh,x-}, d.Eq'_anw)] - d.Eq'_ao5 = - d.Eq'_ao2 - deq_aok = - deq{-r3x,x-} - a{-anC-} - d.Eq'_ao5 - deq_aoj = - deq_aoi - AbsBinds [] [] [([], deq_aoi, deq_anz)] - deq_anz - PrelBase.[]{-5i,p-}{i} PrelBase.[]{-5i,p-}{i} - = PrelBase.True{-5E,p-}{i} - deq_anz - (x_r3l PrelBase.:{-55,p-}{i} xs_r3m) - (y_r3o PrelBase.:{-55,p-}{i} ys_r3p) - = if x_r3l deq_aok y_r3o then - deq_aoj xs_r3m ys_r3p - else - PrelBase.False{-58,p-}{i} - deq_anz - other1_r3r other2_r3t - = PrelBase.False{-58,p-}{i} - d.Eq'_anw = - ({-dict-} [] [deq_aoi]) -{- nonrec -} -ghc:junk old iface line?:section::interface ShouldSucceed where { -ghc:junk old iface line?:section::class Eq' a where { -ghc:junk old iface line?:section:: deq :: a -> a -> Bool -ghc:junk old iface line?:section:: }; -ghc:junk old iface line?:section::instance (Eq' a) => Eq' [a] {-# FROMMODULE ShouldSucceed #-} -ghc:junk old iface line?:section::} -ghc: module version changed to 1; reason: exports changed -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed Eq'(deq); -_instances_ -instance _forall_ [a] {Eq' a} => {Eq' [a]} = $d1; -_declarations_ -1 $d1 _:_ _forall_ [a] {Eq' a} => {Eq' [a]} ;; -1 $mdeq _:_ _forall_ [a] {Eq' a} => a -> a -> PrelBase.Bool ;; -1 class Eq' r3w where {deq :: r3w -> r3w -> PrelBase.Bool} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc038.hs b/ghc/compiler/tests/typecheck/should_succeed/tc038.hs deleted file mode 100644 index d404ee69132bb3ced15488a80b33b9630ac21c7e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc038.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -f (x:xs) = if (x == (fromInteger 2)) then xs else [] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc038.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc038.stderr deleted file mode 100644 index 235fa69648150f85c1dee401bb5026d60012d0a9..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc038.stderr +++ /dev/null @@ -1,49 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aH6 = - PrelNum.$d33{-rxe,p-} -fromInt_aH7 = - PrelBase.fromInt{-8R,p-} - PrelBase.Integer{-3h,p-} - d.Num_aH6 -lit_aH8 = - fromInt_aH7 PrelBase.I#{-5b,p-}{i} 2# -{- nonrec -} -AbsBinds [t{-aGW-}] [d.Num_aH1] [([t{-aGW-}], f{-r3f,x-}, f_aGF)] - d.Eq_aGZ = - PrelBase.scsel_NumPrelBaseEq{-aHb,p-} - t{-aGW-} - d.Num_aH1 - ==_aHa = - PrelBase.=={-8Y,p-} - t{-aGW-} - d.Eq_aGZ - fromInteger_aH9 = - PrelBase.fromInteger{-8S,p-} - t{-aGW-} - d.Num_aH1 - f_aGF - (x_r3d PrelBase.:{-55,p-}{i} xs_r3e) - = if x_r3d ==_aHa (fromInteger_aH9 lit_aH8) then - xs_r3e - else - PrelBase.[]{-5i,p-}{i} - t{-aGW-} -{- nonrec -} -tc038.hs:3: - Warning: Possibly incomplete patterns - in the definition of function `f' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f; -_declarations_ -1 f _:_ _forall_ [a] {PrelBase.Num a} => [a] -> [a] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc039.hs b/ghc/compiler/tests/typecheck/should_succeed/tc039.hs deleted file mode 100644 index 0e5bd9518cebd20ccc9f8f7fbfd3256527f6adc0..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc039.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucc where - -class (Eq a) => A a where - op1 :: a -> a diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc039.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc039.stderr deleted file mode 100644 index a6a93c2f20f76b2a8605235869e938070f42bd33..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc039.stderr +++ /dev/null @@ -1,33 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_APrelBaseEq{-aG7,x-} = - _/\_ a{-r3e-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -op1{-r3f,x-} = - _/\_ a{-r3e-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aG6-}] -[d.A_aFZ] -[([a{-aG6-}], $mop1{-rG8,x-}, op1_aG1)] - AbsBinds [] [] [([], op1_aG1, op1_aG3)] - op1_aG3 - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aG6-} -> a{-aG6-}) "Class A Method op1" -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucc 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d15 1 $d32 1 $d7 1 Eq 1; -PrelNum 1 :: $d18 1; -_exports_ -ShouldSucc A(op1); -_declarations_ -1 $mop1 _:_ _forall_ [a] {A a} => a -> a ;; -1 class {PrelBase.Eq r3e} => A r3e where {op1 :: r3e -> r3e} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc040.hi b/ghc/compiler/tests/typecheck/should_succeed/tc040.hi deleted file mode 100644 index 41d1ee57b36dedae5cc64bb61e3547bbf543bf19..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc040.hi +++ /dev/null @@ -1,4 +0,0 @@ -interface ShouldSucceed where { -import PreludeCore(Eq) -f :: Eq a => a -> [a] -} diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc040.hs b/ghc/compiler/tests/typecheck/should_succeed/tc040.hs deleted file mode 100644 index 33113cc07d79899897db6cbd4d920ded7f0b1fdc..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc040.hs +++ /dev/null @@ -1,9 +0,0 @@ -module ShouldSucceed where - ---!!! tests the deduction of contexts. - -f :: (Eq a) => a -> [a] - -f x = g x - where - g y = if (y == x) then [] else [y] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc040.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc040.stderr deleted file mode 100644 index ef50348be87b5d369182d3938406108e5148ed90..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc040.stderr +++ /dev/null @@ -1,41 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [a{-aG6-}] [d.Eq_aGl] [([a{-aG6-}], f{-r3e,x-}, f_aG3)] - d.Eq_aGn = - d.Eq_aGl - ==_aGo = - PrelBase.=={-8Y,p-} - a{-aG6-} - d.Eq_aGn - f_aG3 - x_r3g = g_r3i x_r3g - where - {- nonrec -} - AbsBinds [] [] [([], g_r3i, g_aG8)] - g_aG8 - y_r3k = if y_r3k ==_aGo x_r3g then - PrelBase.[]{-5i,p-}{i} - a{-aG6-} - else - [y_r3k] (a{-aG6-}) - {- nonrec -} -{- nonrec -} -ghc:junk old iface line?:section::interface ShouldSucceed where { -ghc:junk old iface line?:section::import PreludeCore(Eq) -ghc:junk old iface line?:section::f :: Eq a => a -> [a] -ghc:junk old iface line?:section::} -ghc: module version changed to 1; reason: usages changed -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d15 1 $d27 1 $d32 1 $d7 1 Eq 1; -PrelNum 1 :: $d18 1; -_exports_ -ShouldSucceed f; -_declarations_ -1 f _:_ _forall_ [a] {PrelBase.Eq a} => a -> [a] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc041.hs b/ghc/compiler/tests/typecheck/should_succeed/tc041.hs deleted file mode 100644 index 730af9c1aec0705b24245424b8da964407f81bb8..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc041.hs +++ /dev/null @@ -1,12 +0,0 @@ ---!!! a very simple test of class and instance declarations - -module ShouldSucceed where - -class H a where - op1 :: a -> a -> a - -instance H Bool where - op1 x y = y - -f :: Bool -> Int -> Bool -f x y = op1 x x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc041.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc041.stderr deleted file mode 100644 index d5f7819948ccb6f87e4cf4ef286ee1e22fbc159d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc041.stderr +++ /dev/null @@ -1,51 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -op1{-r3u,x-} = - _/\_ a{-r3t-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-anU-}] -[d.H_anN] -[([a{-anU-}], $mop1{-rnq,x-}, op1_anP)] - AbsBinds [] [] [([], op1_anP, op1_anR)] - op1_anR - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-anU-} -> a{-anU-} -> a{-anU-}) "Class H Method op1" -{- rec -} -AbsBinds [] [] [([], $d1{-rnZ,x-}, d.H_anE)] - AbsBinds [] [] [([], op1_ao0, op1_anH)] - op1_anH - x_r3o y_r3q - = y_r3q - d.H_anE = - ({-dict-} [] [op1_ao0]) -{- nonrec -} -d.H_anX = - $d1{-rnZ,x-} -op1_anY = - op1{-r3u,x-} - PrelBase.Bool{-34,p-} - d.H_anX -{- nonrec -} -AbsBinds [] [] [([], f{-r1,x-}, f_anp)] - f_anp - x_r3h y_r3j - = op1_anY x_r3h x_r3h -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f H(op1); -_instances_ -instance {H PrelBase.Bool} = $d1; -_declarations_ -1 $d1 _:_ {H PrelBase.Bool} ;; -1 $mop1 _:_ _forall_ [a] {H a} => a -> a -> a ;; -1 class H r3t where {op1 :: r3t -> r3t -> r3t} ; -1 f _:_ PrelBase.Bool -> PrelBase.Int -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc042.hs b/ghc/compiler/tests/typecheck/should_succeed/tc042.hs deleted file mode 100644 index 708ea26d67fedc287bedba6a435df5730a3f3a20..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc042.hs +++ /dev/null @@ -1,73 +0,0 @@ ---!!! a file mailed us by Ryzard Kubiak. This provides a good test of the code ---!!! handling type signatures and recursive data types. - -module ShouldSucceed where - -data Boolean = FF | TT -data Pair a b = Mkpair a b -data List alpha = Nil | Cons alpha (List alpha) -data Nat = Zero | Succ Nat -data Tree t = Leaf t | Node (Tree t) (Tree t) - -idb :: Boolean -> Boolean -idb x = x - - -swap :: Pair a b -> Pair b a -swap t = case t of - Mkpair x y -> Mkpair y x - -neg :: Boolean -> Boolean -neg b = case b of - FF -> TT - TT -> FF - -nUll :: List alpha -> Boolean -nUll l = case l of - Nil -> TT - Cons y ys -> FF - -idl :: List a -> List a -idl xs = case xs of - Nil -> Nil - Cons y ys -> Cons y (idl ys) - -add :: Nat -> Nat -> Nat -add a b = case a of - Zero -> b - Succ c -> Succ (add c b) - -app :: List alpha -> List alpha -> List alpha -app xs zs = case xs of - Nil -> zs - Cons y ys -> Cons y (app ys zs) - -lEngth :: List a -> Nat -lEngth xs = case xs of - Nil -> Zero - Cons y ys -> Succ(lEngth ys) - -before :: List Nat -> List Nat -before xs = case xs of - Nil -> Nil - Cons y ys -> case y of - Zero -> Nil - Succ n -> Cons y (before ys) - -rEverse :: List alpha -> List alpha -rEverse rs = case rs of - Nil -> Nil - Cons y ys -> app (rEverse ys) (Cons y Nil) - - -flatten :: Tree alpha -> List alpha -flatten t = case t of - Leaf x -> Cons x Nil - Node l r -> app (flatten l) (flatten r) - -sUm :: Tree Nat -> Nat -sUm t = case t of - Leaf t -> t - Node l r -> add (sUm l) (sUm r) - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc042.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc042.stderr deleted file mode 100644 index 4c434e34b6934b1303af8f141dfad011f09ed521..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc042.stderr +++ /dev/null @@ -1,255 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -Leaf{-rg,x-}{i} = - _/\_ t{-r5r-} -> \ tpl_B1 -> - Leaf{-rg,x-}{i} - {_@_ t{-r5r-} tpl_B1} -Node{-rf,x-}{i} = - _/\_ t{-r5r-} -> \ tpl_B1 tpl_B2 -> - Node{-rf,x-}{i} - {_@_ t{-r5r-} tpl_B1 tpl_B2} -{- nonrec -} -Zero{-rl,x-}{i} = - Zero{-rl,x-}{i} - {} -Succ{-rk,x-}{i} = - \ tpl_B1 -> - Succ{-rk,x-}{i} - {tpl_B1} -{- nonrec -} -Nil{-rq,x-}{i} = - _/\_ alpha{-r5u-} -> - Nil{-rq,x-}{i} - {_@_ alpha{-r5u-}} -Cons{-rp,x-}{i} = - _/\_ alpha{-r5u-} -> \ tpl_B1 tpl_B2 -> - Cons{-rp,x-}{i} - {_@_ alpha{-r5u-} tpl_B1 tpl_B2} -{- nonrec -} -Mkpair{-r5B,x-}{i} = - _/\_ a{-r5w-} b{-r5x-} -> \ tpl_B1 tpl_B2 -> - Mkpair{-r5B,x-}{i} - {_@_ a{-r5w-} _@_ b{-r5x-} tpl_B1 tpl_B2} -{- nonrec -} -FF{-rx,x-}{i} = - FF{-rx,x-}{i} - {} -TT{-rw,x-}{i} = - TT{-rw,x-}{i} - {} -{- rec -} -AbsBinds [t{-aMR-}] [] [([t{-aMR-}], $d1{-rMX,x-}, d.Eval_aMt)] - d.Eval_aMt = - ({-dict-} [] []) -{- rec -} -AbsBinds [] [] [([], $d2{-rMZ,x-}, d.Eval_aMy)] - d.Eval_aMy = - ({-dict-} [] []) -{- rec -} -AbsBinds -[alpha{-aMS-}] -[] -[([alpha{-aMS-}], $d3{-rN1,x-}, d.Eval_aME)] - d.Eval_aME = - ({-dict-} [] []) -{- rec -} -AbsBinds -[a{-aMT-}, b{-aMU-}] -[] -[([a{-aMT-}, b{-aMU-}], $d4{-rN3,x-}, d.Eval_aML)] - d.Eval_aML = - ({-dict-} [] []) -{- rec -} -AbsBinds [] [] [([], $d5{-rN5,x-}, d.Eval_aMQ)] - d.Eval_aMQ = - ({-dict-} [] []) -{- nonrec -} -{- rec -} -AbsBinds [] [] [([], before{-r4a,x-}, before_aIA)] - before_aIA - xs_r4Y = case xs_r4Y of - Nil{-rq,x-}{i} - -> Nil{-rq,x-}{i} - Nat{-r5z,x-} - (Cons{-rp,x-}{i} y_r51 ys_r52) - -> case y_r51 of - Zero{-rl,x-}{i} - -> Nil{-rq,x-}{i} - Nat{-r5z,x-} - (Succ{-rk,x-}{i} n_r55) - -> Cons{-rp,x-}{i} - Nat{-r5z,x-} y_r51 before{-r4a,x-} ys_r52 -{- nonrec -} -{- rec -} -AbsBinds [a{-aJ2-}] [] [([a{-aJ2-}], lEngth{-r49,x-}, lEngth_aIZ)] - lEngth_aIZ - xs_r4S = case xs_r4S of - Nil{-rq,x-}{i} - -> Zero{-rl,x-}{i} - (Cons{-rp,x-}{i} y_r4V ys_r4W) - -> Succ{-rk,x-}{i} lEngth{-r49,x-} - a{-aJ2-} ys_r4W -{- nonrec -} -{- rec -} -AbsBinds -[alpha{-aJo-}] -[] -[([alpha{-aJo-}], app{-r48,x-}, app_aJl)] - app_aJl - xs_r4K zs_r4M - = case xs_r4K of - Nil{-rq,x-}{i} - -> zs_r4M - (Cons{-rp,x-}{i} y_r4P ys_r4Q) - -> Cons{-rp,x-}{i} - alpha{-aJo-} y_r4P - app{-r48,x-} - alpha{-aJo-} ys_r4Q zs_r4M -{- nonrec -} -{- rec -} -AbsBinds -[alpha{-aJO-}] -[] -[([alpha{-aJO-}], rEverse{-r4b,x-}, rEverse_aJL)] - rEverse_aJL - rs_r57 = case rs_r57 of - Nil{-rq,x-}{i} - -> Nil{-rq,x-}{i} - alpha{-aJO-} - (Cons{-rp,x-}{i} y_r5a ys_r5b) - -> app{-r48,x-} - alpha{-aJO-} rEverse{-r4b,x-} - alpha{-aJO-} ys_r5b - Cons{-rp,x-}{i} - alpha{-aJO-} y_r5a - Nil{-rq,x-}{i} - alpha{-aJO-} -{- nonrec -} -{- rec -} -AbsBinds -[alpha{-aKi-}] -[] -[([alpha{-aKi-}], flatten{-r4c,x-}, flatten_aKf)] - flatten_aKf - t_r5d = case t_r5d of - (Leaf{-rg,x-}{i} x_r5f) - -> Cons{-rp,x-}{i} - alpha{-aKi-} x_r5f - Nil{-rq,x-}{i} - alpha{-aKi-} - (Node{-rf,x-}{i} l_r5h r_r5i) - -> app{-r48,x-} - alpha{-aKi-} flatten{-r4c,x-} - alpha{-aKi-} l_r5h - flatten{-r4c,x-} - alpha{-aKi-} r_r5i -{- nonrec -} -{- rec -} -AbsBinds [] [] [([], add{-r47,x-}, add_aKH)] - add_aKH - a_r4D b_r4F - = case a_r4D of - Zero{-rl,x-}{i} - -> b_r4F - (Succ{-rk,x-}{i} c_r4I) - -> Succ{-rk,x-}{i} add{-r47,x-} c_r4I b_r4F -{- nonrec -} -{- rec -} -AbsBinds [] [] [([], sUm{-r4d,x-}, sUm_aKR)] - sUm_aKR - t_r5k = case t_r5k of - (Leaf{-rg,x-}{i} t_r5m) - -> t_r5m - (Node{-rf,x-}{i} l_r5o r_r5p) - -> add{-r47,x-} sUm{-r4d,x-} l_r5o sUm{-r4d,x-} r_r5p -{- nonrec -} -{- rec -} -AbsBinds [a{-aLe-}] [] [([a{-aLe-}], idl{-r46,x-}, idl_aLb)] - idl_aLb - xs_r4x = case xs_r4x of - Nil{-rq,x-}{i} - -> Nil{-rq,x-}{i} - a{-aLe-} - (Cons{-rp,x-}{i} y_r4A ys_r4B) - -> Cons{-rp,x-}{i} - a{-aLe-} y_r4A - idl{-r46,x-} - a{-aLe-} ys_r4B -{- nonrec -} -{- nonrec -} -AbsBinds -[alpha{-aLD-}] -[] -[([alpha{-aLD-}], nUll{-r45,x-}, nUll_aLA)] - nUll_aLA - l_r4r = case l_r4r of - Nil{-rq,x-}{i} - -> TT{-rw,x-}{i} - (Cons{-rp,x-}{i} y_r4u ys_r4v) - -> FF{-rx,x-}{i} -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], neg{-r44,x-}, neg_aLP)] - neg_aLP - b_r4n = case b_r4n of - FF{-rx,x-}{i} - -> TT{-rw,x-}{i} - TT{-rw,x-}{i} - -> FF{-rx,x-}{i} -{- nonrec -} -{- nonrec -} -AbsBinds -[a{-aM3-}, b{-aM4-}] -[] -[([b{-aM4-}, a{-aM3-}], swap{-r43,x-}, swap_aM0)] - swap_aM0 - t_r4i = case t_r4i of - (Mkpair{-r5B,x-}{i} x_r4k y_r4l) - -> Mkpair{-r5B,x-}{i} - [b{-aM4-}, a{-aM3-}] y_r4l x_r4k -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], idb{-r42,x-}, idb_aMl)] - idb_aMl - x_r4g = x_r4g -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1; -_exports_ -ShouldSucceed add app before flatten idb idl lEngth nUll neg rEverse sUm swap Boolean(FF TT) List(Nil Cons) Nat(Zero Succ) Pair(Mkpair) Tree(Leaf Node); -_instances_ -instance _forall_ [a] => {PrelBase.Eval (Tree a)} = $d1; -instance {PrelBase.Eval Nat} = $d2; -instance _forall_ [a] => {PrelBase.Eval (List a)} = $d3; -instance _forall_ [a b] => {PrelBase.Eval (Pair a b)} = $d4; -instance {PrelBase.Eval Boolean} = $d5; -_declarations_ -1 $d1 _:_ _forall_ [a] => {PrelBase.Eval (Tree a)} ;; -1 $d2 _:_ {PrelBase.Eval Nat} ;; -1 $d3 _:_ _forall_ [a] => {PrelBase.Eval (List a)} ;; -1 $d4 _:_ _forall_ [a b] => {PrelBase.Eval (Pair a b)} ;; -1 $d5 _:_ {PrelBase.Eval Boolean} ;; -1 data Boolean = FF | TT ; -1 data List r5u = Nil | Cons r5u (List r5u) ; -1 data Nat = Zero | Succ Nat ; -1 data Pair r5w r5x = Mkpair r5w r5x ; -1 data Tree r5r = Leaf r5r | Node (Tree r5r) (Tree r5r) ; -1 add _:_ Nat -> Nat -> Nat ;; -1 app _:_ _forall_ [a] => List a -> List a -> List a ;; -1 before _:_ List Nat -> List Nat ;; -1 flatten _:_ _forall_ [a] => Tree a -> List a ;; -1 idb _:_ Boolean -> Boolean ;; -1 idl _:_ _forall_ [a] => List a -> List a ;; -1 lEngth _:_ _forall_ [a] => List a -> Nat ;; -1 nUll _:_ _forall_ [a] => List a -> Boolean ;; -1 neg _:_ Boolean -> Boolean ;; -1 rEverse _:_ _forall_ [a] => List a -> List a ;; -1 sUm _:_ Tree Nat -> Nat ;; -1 swap _:_ _forall_ [a b] => Pair b a -> Pair a b ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc043.hs b/ghc/compiler/tests/typecheck/should_succeed/tc043.hs deleted file mode 100644 index 727f2886aeec0134433b038c1b3765863b99f990..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc043.hs +++ /dev/null @@ -1,18 +0,0 @@ -module ShouldSucceed where - ---!!! another simple test of class and instance code. - -class A a where - op1 :: a - -instance A Int where - op1 = 2 - -f x = op1 - -class B b where - op2 :: b -> Int - -instance (B a) => B [a] where - op2 [] = 0 - op2 (x:xs) = 1 + op2 xs diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc043.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc043.stderr deleted file mode 100644 index 7b0da4fcb1bb6558966d74dd2f50583ced8f23e1..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc043.stderr +++ /dev/null @@ -1,105 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -op2{-r3D,x-} = - _/\_ b{-r3t-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[b{-aIu-}] -[d.B_aIn] -[([b{-aIu-}], $mop2{-rHi,x-}, op2_aIp)] - AbsBinds [] [] [([], op2_aIp, op2_aIr)] - op2_aIr - = GHCerr.noDefaultMethodError{-8k,p-} - (b{-aIu-} -> PrelBase.Int{-3g,p-}) "Class B Method op2" -{- nonrec -} -op1{-r3E,x-} = - _/\_ a{-r3B-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aID-}] -[d.A_aIy] -[([a{-aID-}], $mop1{-rHh,x-}, op1_aIA)] - AbsBinds [] [] [([], op1_aIA, op1_aIC)] - op1_aIC - = GHCerr.noDefaultMethodError{-8k,p-} - a{-aID-} "Class A Method op1" -{- rec -} -AbsBinds [a{-aHF-}] [d.B_aI1] [([a{-aHF-}], $d1{-rIW,x-}, d.B_aHz)] - op2_aIY = - op2_aIX - AbsBinds [] [] [([], op2_aIX, op2_aHC)] - op2_aHC - PrelBase.[]{-5i,p-}{i} - = lit_aIU - op2_aHC - (x_r3p PrelBase.:{-55,p-}{i} xs_r3q) - = lit_aIR +_aIT (op2_aIY xs_r3q) - d.B_aHz = - ({-dict-} [] [op2_aIX]) -{- rec -} -AbsBinds [] [] [([], $d2{-rIZ,x-}, d.A_aIc)] - AbsBinds [] [] [([], op1_aJ0, op1_aIf)] - op1_aIf - = lit_aIN - d.A_aIc = - ({-dict-} [] [op1_aJ0]) -{- nonrec -} -d.Num_aIJ = - PrelBase.$d3{-rbv,p-} -fromInt_aIV = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aIJ -lit_aIU = - fromInt_aIV PrelBase.I#{-5b,p-}{i} 0# -d.Num_aIM = - d.Num_aIJ -+_aIT = - PrelBase.+{-rd3,p-} - PrelBase.Int{-3g,p-} - d.Num_aIM -fromInt_aIS = - fromInt_aIV -lit_aIR = - fromInt_aIS PrelBase.I#{-5b,p-}{i} 1# -fromInt_aIQ = - fromInt_aIV -lit_aIN = - fromInt_aIQ PrelBase.I#{-5b,p-}{i} 2# -{- nonrec -} -AbsBinds -[t{-aHr-}, a{-aHo-}] -[d.A_aHt] -[([t{-aHr-}, a{-aHo-}], f{-r3C,x-}, f_aHg)] - op1_aJ1 = - op1{-r3E,x-} - a{-aHo-} - d.A_aHt - f_aHg - x_r3h = op1_aJ1 -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f A(op1) B(op2); -_instances_ -instance _forall_ [a] {B a} => {B [a]} = $d1; -instance {A PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {B a} => {B [a]} ;; -1 $d2 _:_ {A PrelBase.Int} ;; -1 $mop1 _:_ _forall_ [a] {A a} => a ;; -1 $mop2 _:_ _forall_ [a] {B a} => a -> PrelBase.Int ;; -1 class A r3B where {op1 :: r3B} ; -1 class B r3t where {op2 :: r3t -> PrelBase.Int} ; -1 f _:_ _forall_ [a b] {A b} => a -> b ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc044.hs b/ghc/compiler/tests/typecheck/should_succeed/tc044.hs deleted file mode 100644 index 9f98989bb11695d584aff99474db5652e4f3db34..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc044.hs +++ /dev/null @@ -1,6 +0,0 @@ --- once produced a bug, here as regression test - -module P where - -f _ | otherwise = () - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc044.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc044.stderr deleted file mode 100644 index cc55d72d2e3620abd77e121f3a023213cfec9800..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc044.stderr +++ /dev/null @@ -1,21 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [t{-auu-}] [] [([t{-auu-}], f{-r1,x-}, f_auo)] - f_auo - _ | [PrelBase.otherwise{-818,p-}] = - PrelBase.(){-60,p-}{i} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ P 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: otherwise 1; -_exports_ -P f; -_declarations_ -1 f _:_ _forall_ [a] => a -> PrelBase.() ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc045.hs b/ghc/compiler/tests/typecheck/should_succeed/tc045.hs deleted file mode 100644 index fc6a72ea979aa66daf7efbb137feccb0f01cf6f3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc045.hs +++ /dev/null @@ -1,19 +0,0 @@ -module H where - -class C a where - op1 :: a -> a - -class (C a) => B a where - op2 :: a -> a -> a - -instance (B a) => B [a] where - op2 xs ys = xs - -instance C [a] where - op1 xs = xs - -{- This was passed by the prototype, but failed hard in the new -typechecker with the message - -Fail:No match in theta_class --} diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc045.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc045.stderr deleted file mode 100644 index 846d0184d176dfcd7c5a61d8d79447b71a31d07c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc045.stderr +++ /dev/null @@ -1,70 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_BHC{-aow,x-} = - _/\_ a{-r3x-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -op2{-r3D,x-} = - _/\_ a{-r3x-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aok-}] -[d.B_aod] -[([a{-aok-}], $mop2{-rox,x-}, op2_aof)] - AbsBinds [] [] [([], op2_aof, op2_aoh)] - op2_aoh - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aok-} -> a{-aok-} -> a{-aok-}) "Class B Method op2" -{- nonrec -} -op1{-r3E,x-} = - _/\_ a{-r3C-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aov-}] -[d.C_aoo] -[([a{-aov-}], $mop1{-roy,x-}, op1_aoq)] - AbsBinds [] [] [([], op1_aoq, op1_aos)] - op1_aos - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aov-} -> a{-aov-}) "Class C Method op1" -{- rec -} -AbsBinds [a{-anP-}] [] [([a{-anP-}], $d1{-roz,x-}, d.C_anJ)] - AbsBinds [] [] [([], op1_aoA, op1_anM)] - op1_anM - xs_r3k = xs_r3k - d.C_anJ = - ({-dict-} [] [op1_aoA]) -{- rec -} -AbsBinds -[a{-ao2-}] -[d.B_ao5, d.C_ao6] -[([a{-ao2-}], $d2{-roB,x-}, d.B_anW)] - d.C_ao7 = - d.C_ao6 - AbsBinds [] [] [([], op2_aoC, op2_anZ)] - op2_anZ - xs_r3s ys_r3u - = xs_r3s - d.B_anW = - ({-dict-} [d.C_ao7] [op2_aoC]) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ H 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -H B(op2) C(op1); -_instances_ -instance _forall_ [a] => {C [a]} = $d1; -instance _forall_ [a] {B a} => {B [a]} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] => {C [a]} ;; -1 $d2 _:_ _forall_ [a] {B a, C [a]} => {B [a]} ;; -1 $mop1 _:_ _forall_ [a] {C a} => a -> a ;; -1 $mop2 _:_ _forall_ [a] {B a} => a -> a -> a ;; -1 class {C r3x} => B r3x where {op2 :: r3x -> r3x -> r3x} ; -1 class C r3C where {op1 :: r3C -> r3C} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc046.hs b/ghc/compiler/tests/typecheck/should_succeed/tc046.hs deleted file mode 100644 index dbbf3a176a5ac1eba86875daaebdbf2b1880dfa3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc046.hs +++ /dev/null @@ -1,9 +0,0 @@ -module H where - -class C a where - op1 :: a -> a - -class (C a) => B a where - op2 :: a -> a -> a - -{- Failed hard in new tc with "No match in theta_class" -} diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc046.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc046.stderr deleted file mode 100644 index 54a3e3040fea5851ef8c13bbf1710dbf88789920..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc046.stderr +++ /dev/null @@ -1,45 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_BHC{-anH,x-} = - _/\_ a{-r3g-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -op2{-r3m,x-} = - _/\_ a{-r3g-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-anv-}] -[d.B_ano] -[([a{-anv-}], $mop2{-rnI,x-}, op2_anq)] - AbsBinds [] [] [([], op2_anq, op2_ans)] - op2_ans - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-anv-} -> a{-anv-} -> a{-anv-}) "Class B Method op2" -{- nonrec -} -op1{-r3o,x-} = - _/\_ a{-r3l-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-anG-}] -[d.C_anz] -[([a{-anG-}], $mop1{-rnJ,x-}, op1_anB)] - AbsBinds [] [] [([], op1_anB, op1_anD)] - op1_anD - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-anG-} -> a{-anG-}) "Class C Method op1" -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ H 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -H B(op2) C(op1); -_declarations_ -1 $mop1 _:_ _forall_ [a] {C a} => a -> a ;; -1 $mop2 _:_ _forall_ [a] {B a} => a -> a -> a ;; -1 class {C r3g} => B r3g where {op2 :: r3g -> r3g -> r3g} ; -1 class C r3l where {op1 :: r3l -> r3l} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc047.hs b/ghc/compiler/tests/typecheck/should_succeed/tc047.hs deleted file mode 100644 index b8c197d185f09f42eb3d48e1d32247a5a30499d3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc047.hs +++ /dev/null @@ -1,23 +0,0 @@ -module ShouldSucceed where - -type OL a = [a] - --- produces the interface: --- data OL a = MkOL [a] deriving () --- ranOAL :: (OL (a, a)) -> [a] --- this interface was produced by BOTH hbc and nhc - --- the following bogus type sig. was accepted by BOTH hbc and nhc -f x = ranOAL where -- ranOAL :: OL (a,v) -> [a] ---ranOAL :: OL (a,v) -> [v], the right sig. - ranOAL ( xs) = mp sd xs - - -mp f [] = [] -mp f (x:xs) = (f x) : mp f xs - -sd (f,s) = s - - - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc047.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc047.stderr deleted file mode 100644 index 696eec869870505c89fec37d246762b0ebb72a68..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc047.stderr +++ /dev/null @@ -1,61 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aBv-}, t{-aBy-}] -[] -[([t{-aBv-}, t{-aBy-}], sd{-r3y,x-}, sd_aBq)] - sd_aBq - (f_r3u, s_r3v) - = s_r3v -{- nonrec -} -{- rec -} -AbsBinds -[t{-aBI-}, t{-aBK-}] -[] -[([t{-aBI-}, t{-aBK-}], mp{-r3z,x-}, mp_aBC)] - mp_aBC - f_r3m PrelBase.[]{-5i,p-}{i} - = PrelBase.[]{-5i,p-}{i} - t{-aBK-} - mp_aBC - f_r3p (x_r3r PrelBase.:{-55,p-}{i} xs_r3s) - = PrelBase.:{-55,p-}{i} - t{-aBK-} - (f_r3p x_r3r) (mp_aBC f_r3p xs_r3s) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aCo-}, t{-aCk-}, t{-aCm-}] -[] -[([t{-aCo-}, t{-aCk-}, t{-aCm-}], f{-r3A,x-}, f_aC0)] - f_aC0 - x_r3g = ranOAL_r3i - [t{-aCk-}, t{-aCm-}] - where - {- nonrec -} - AbsBinds - [t{-aCb-}, t{-aCd-}] - [] - [([t{-aCb-}, t{-aCd-}], ranOAL_r3i, ranOAL_aC4)] - ranOAL_aC4 - xs_r3k = mp{-r3z,x-} - [(t{-aCb-}, t{-aCd-}), t{-aCd-}] sd{-r3y,x-} - [t{-aCb-}, t{-aCd-}] - xs_r3k - {- nonrec -} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f mp sd OL; -_declarations_ -1 type OL r3x = [r3x] ; -1 f _:_ _forall_ [a b c] => a -> [(b, c)] -> [c] ;; -1 mp _:_ _forall_ [a b] => (a -> b) -> [a] -> [b] ;; -1 sd _:_ _forall_ [a b] => (a, b) -> b ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc048.hs b/ghc/compiler/tests/typecheck/should_succeed/tc048.hs deleted file mode 100644 index eea6f10e791a776760b9b83b5245e1da7715abae..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc048.hs +++ /dev/null @@ -1,21 +0,0 @@ -module ShouldSucceed where - -data OL a = MkOL [a] -data FG a b = MkFG (OL (a,b)) -data AFE n a b = MkAFE (OL (n,(FG a b))) - ---ranOAL :: OL (a,v) -> [a] -ranOAL :: OL (a,v) -> [v] -ranOAL (MkOL xs) = mAp sNd xs - -mAp f [] = [] -mAp f (x:xs) = (f x) : mAp f xs - -sNd (f,s) = s - -ranAFE :: AFE n a b -> [FG a b] -- ? -ranAFE (MkAFE nfs) = ranOAL nfs - - - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc048.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc048.stderr deleted file mode 100644 index 52223ea2879704d798f21e6797e6153d68cb0020..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc048.stderr +++ /dev/null @@ -1,108 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -MkAFE{-r3U,x-}{i} = - _/\_ n{-r3M-} a{-r3N-} b{-r3O-} -> \ tpl_B1 -> - MkAFE{-r3U,x-}{i} - {_@_ n{-r3M-} _@_ a{-r3N-} _@_ b{-r3O-} tpl_B1} -{- nonrec -} -MkFG{-r3W,x-}{i} = - _/\_ a{-r3Q-} b{-r3R-} -> \ tpl_B1 -> - MkFG{-r3W,x-}{i} - {_@_ a{-r3Q-} _@_ b{-r3R-} tpl_B1} -{- nonrec -} -MkOL{-r3Y,x-}{i} = - _/\_ a{-r3T-} -> \ tpl_B1 -> - MkOL{-r3Y,x-}{i} - {_@_ a{-r3T-} tpl_B1} -{- rec -} -AbsBinds -[n{-aXN-}, a{-aXP-}, b{-aXO-}] -[] -[([n{-aXN-}, a{-aXP-}, b{-aXO-}], $d1{-rXV,x-}, d.Eval_aXz)] - d.Eval_aXz = - ({-dict-} [] []) -{- rec -} -AbsBinds -[a{-aXQ-}, b{-aXR-}] -[] -[([a{-aXQ-}, b{-aXR-}], $d2{-rXX,x-}, d.Eval_aXG)] - d.Eval_aXG = - ({-dict-} [] []) -{- rec -} -AbsBinds [a{-aXS-}] [] [([a{-aXS-}], $d3{-rXZ,x-}, d.Eval_aXM)] - d.Eval_aXM = - ({-dict-} [] []) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aWc-}, t{-aWf-}] -[] -[([t{-aWc-}, t{-aWf-}], sNd{-r3u,x-}, sNd_aW7)] - sNd_aW7 - (f_r3H, s_r3I) - = s_r3I -{- nonrec -} -{- rec -} -AbsBinds -[t{-aWp-}, t{-aWr-}] -[] -[([t{-aWp-}, t{-aWr-}], mAp{-r3v,x-}, mAp_aWj)] - mAp_aWj - f_r3z PrelBase.[]{-5i,p-}{i} - = PrelBase.[]{-5i,p-}{i} - t{-aWr-} - mAp_aWj - f_r3C (x_r3E PrelBase.:{-55,p-}{i} xs_r3F) - = PrelBase.:{-55,p-}{i} - t{-aWr-} - (f_r3C x_r3E) (mAp_aWj f_r3C xs_r3F) -{- nonrec -} -{- nonrec -} -AbsBinds -[a{-aWR-}, v{-aWS-}] -[] -[([a{-aWR-}, v{-aWS-}], ranOAL{-r3s,x-}, ranOAL_aWM)] - ranOAL_aWM - (MkOL{-r3Y,x-}{i} xs_r3x) - = mAp{-r3v,x-} - [(a{-aWR-}, v{-aWS-}), v{-aWS-}] sNd{-r3u,x-} - [a{-aWR-}, v{-aWS-}] - xs_r3x -{- nonrec -} -{- nonrec -} -AbsBinds -[n{-aXk-}, a{-aXl-}, b{-aXm-}] -[] -[([n{-aXk-}, a{-aXl-}, b{-aXm-}], ranAFE{-r3t,x-}, ranAFE_aXb)] - ranAFE_aXb - (MkAFE{-r3U,x-}{i} nfs_r3K) - = ranOAL{-r3s,x-} - [n{-aXk-}, FG{-r3X,x-} a{-aXl-} b{-aXm-}] nfs_r3K -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d44 1 $d46 1 Eval 1; -PrelTup 1 :: $d13 1; -_exports_ -ShouldSucceed mAp ranAFE ranOAL sNd AFE(MkAFE) FG(MkFG) OL(MkOL); -_instances_ -instance _forall_ [a b c] => {PrelBase.Eval (AFE a b c)} = $d1; -instance _forall_ [a b] => {PrelBase.Eval (FG a b)} = $d2; -instance _forall_ [a] => {PrelBase.Eval (OL a)} = $d3; -_declarations_ -1 $d1 _:_ _forall_ [a b c] => {PrelBase.Eval (AFE a b c)} ;; -1 $d2 _:_ _forall_ [a b] => {PrelBase.Eval (FG a b)} ;; -1 $d3 _:_ _forall_ [a] => {PrelBase.Eval (OL a)} ;; -1 data AFE r3M r3N r3O = MkAFE (OL (r3M, FG r3N r3O)) ; -1 data FG r3Q r3R = MkFG (OL (r3Q, r3R)) ; -1 data OL r3T = MkOL [r3T] ; -1 mAp _:_ _forall_ [a b] => (a -> b) -> [a] -> [b] ;; -1 ranAFE _:_ _forall_ [a b c] => AFE a b c -> [FG b c] ;; -1 ranOAL _:_ _forall_ [a b] => OL (a, b) -> [b] ;; -1 sNd _:_ _forall_ [a b] => (a, b) -> b ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc049.hs b/ghc/compiler/tests/typecheck/should_succeed/tc049.hs deleted file mode 100644 index 20be6b768b3cc11db8d7c34c6f42e8be17b1400f..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc049.hs +++ /dev/null @@ -1,39 +0,0 @@ -module ShouldSucceed where - -fib n = if n <= 2 then n else fib (n-1) + fib (n-2) - ----------------------------------------- - -mem x [] = False -mem x (y:ys) = (x == y) `oR` mem x ys - -a `oR` b = if a then True else b - ----------------------------------------- - -mem1 x [] = False -mem1 x (y:ys) = (x == y) `oR1` mem2 x ys - -a `oR1` b = if a then True else b - -mem2 x [] = False -mem2 x (y:ys) = (x == y) `oR` mem1 x ys - ---------------------------------------- - -mem3 x [] = False -mem3 x (y:ys) = if [x] == [y] then mem4 x ys else False - -mem4 y (x:xs) = mem3 y xs - ---------------------------------------- - -main1 = [[(1,True)]] == [[(2,False)]] - ---------------------------------------- - -main2 = "Hello" == "Goodbye" - ---------------------------------------- - -main3 = [[1],[2]] == [[3]] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc049.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc049.stderr deleted file mode 100644 index 4350d750b41b24b1ebc69b1104ee2e2042a95c98..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc049.stderr +++ /dev/null @@ -1,239 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -d.Eq_a11Z = - PrelBase.$d7{-rcB,p-} -d.Eq_a120 = - PrelBase.$d32{-rc8,p-} -d.Eq_a11X = - PrelTup.$d9{-ry4,p-} - [PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-}] - [d.Eq_a11Z, d.Eq_a120] -d.Eq_a11V = - PrelBase.$d27{-rc2,p-} - (PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-}) - d.Eq_a11X -d.Eq_a11T = - PrelBase.$d27{-rc2,p-} - [(PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-})] - d.Eq_a11V -==_a12u = - PrelBase.=={-8Y,p-} - [[(PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-})]] - d.Eq_a11T -d.Num_a125 = - PrelBase.$d3{-rc5,p-} -fromInt_a12t = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_a125 -lit_a12s = - fromInt_a12t PrelBase.I#{-5b,p-}{i} 1# -fromInt_a12r = - fromInt_a12t -lit_a12q = - fromInt_a12r PrelBase.I#{-5b,p-}{i} 2# -d.Eq_a12b = - PrelBase.$d33{-rc9,p-} -d.Eq_a129 = - PrelBase.$d27{-rc2,p-} - PrelBase.Char{-38,p-} - d.Eq_a12b -==_a12p = - PrelBase.=={-8Y,p-} - [PrelBase.Char{-38,p-}] - d.Eq_a129 -d.Eq_a12i = - d.Eq_a11Z -d.Eq_a12g = - PrelBase.$d27{-rc2,p-} - PrelBase.Int{-3g,p-} - d.Eq_a12i -d.Eq_a12e = - PrelBase.$d27{-rc2,p-} - [PrelBase.Int{-3g,p-}] - d.Eq_a12g -==_a12o = - PrelBase.=={-8Y,p-} - [[PrelBase.Int{-3g,p-}]] - d.Eq_a12e -lit_a12n = - lit_a12s -lit_a12m = - lit_a12q -fromInt_a12l = - fromInt_a12t -lit_a12j = - fromInt_a12l PrelBase.I#{-5b,p-}{i} 3# -{- nonrec -} -AbsBinds [] [] [([], main3{-r47,x-}, main3_aXA)] - main3_aXA - = [[lit_a12n] (PrelBase.Int{-3g,p-}), - [lit_a12m] (PrelBase.Int{-3g,p-})] ([PrelBase.Int{-3g,p-}]) - ==_a12o [[lit_a12j] (PrelBase.Int{-3g,p-})] ([PrelBase.Int{-3g,p-}]) -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], main2{-r48,x-}, main2_aYl)] - main2_aYl - = "Hello" ==_a12p "Goodbye" -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], main1{-r49,x-}, main1_aYv)] - main1_aYv - = [[(lit_a12s, - PrelBase.True{-5E,p-}{i})] ((PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-}))] ([(PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-})]) - ==_a12u [[(lit_a12q, - PrelBase.False{-58,p-}{i})] ((PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-}))] ([(PrelBase.Int{-3g,p-}, PrelBase.Bool{-34,p-})]) -{- nonrec -} -{- rec -} -AbsBinds -[t{-aZp-}] -[d.Eq_aZS] -[([t{-aZp-}], mem3{-r4b,x-}, mem3_aZc), ([t{-aZp-}], - mem4{-r4a,x-}, - mem4_aZd)] - d.Eq_aZQ = - PrelBase.$d27{-rc2,p-} - t{-aZp-} - d.Eq_aZS - ==_a12v = - PrelBase.=={-8Y,p-} - [t{-aZp-}] - d.Eq_aZQ - mem3_aZc - x_r3V PrelBase.[]{-5i,p-}{i} - = PrelBase.False{-58,p-}{i} - mem3_aZc - x_r3Y (y_r40 PrelBase.:{-55,p-}{i} ys_r41) - = if [x_r3Y] (t{-aZp-}) ==_a12v [y_r40] (t{-aZp-}) then - mem4_aZd x_r3Y ys_r41 - else - PrelBase.False{-58,p-}{i} - mem4_aZd - y_r43 (x_r45 PrelBase.:{-55,p-}{i} xs_r46) - = mem3_aZc y_r43 xs_r46 -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], oR1{-r4d,x-}, oR1_aZU)] - oR1_aZU - a_r3J b_r3L - = if a_r3J then PrelBase.True{-5E,p-}{i} else b_r3L -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], oR{-r4f,x-}, oR_a102)] - oR_a102 - a_r3x b_r3z - = if a_r3x then PrelBase.True{-5E,p-}{i} else b_r3z -{- nonrec -} -{- rec -} -AbsBinds -[t{-a10n-}] -[d.Eq_a10R] -[([t{-a10n-}], mem2{-r4c,x-}, mem2_a10a), ([t{-a10n-}], - mem1{-r4e,x-}, - mem1_a10b)] - ==_a12x = - PrelBase.=={-8Y,p-} - t{-a10n-} - d.Eq_a10R - ==_a12w = - ==_a12x - mem2_a10a - x_r3N PrelBase.[]{-5i,p-}{i} - = PrelBase.False{-58,p-}{i} - mem2_a10a - x_r3Q (y_r3S PrelBase.:{-55,p-}{i} ys_r3T) - = (x_r3Q ==_a12x y_r3S) oR{-r4f,x-} (mem1_a10b x_r3Q ys_r3T) - mem1_a10b - x_r3B PrelBase.[]{-5i,p-}{i} - = PrelBase.False{-58,p-}{i} - mem1_a10b - x_r3E (y_r3G PrelBase.:{-55,p-}{i} ys_r3H) - = (x_r3E ==_a12w y_r3G) oR1{-r4d,x-} (mem2_a10a x_r3E ys_r3H) -{- nonrec -} -{- rec -} -AbsBinds -[t{-a10Z-}] -[d.Eq_a11c] -[([t{-a10Z-}], mem{-r4g,x-}, mem_a10T)] - ==_a12y = - PrelBase.=={-8Y,p-} - t{-a10Z-} - d.Eq_a11c - mem_a10T - x_r3p PrelBase.[]{-5i,p-}{i} - = PrelBase.False{-58,p-}{i} - mem_a10T - x_r3s (y_r3u PrelBase.:{-55,p-}{i} ys_r3v) - = (x_r3s ==_a12y y_r3u) oR{-r4f,x-} (mem_a10T x_r3s ys_r3v) -{- nonrec -} -{- rec -} -AbsBinds -[riC{-a11y-}] -[d.Ord_a11J, d.Num_a11M] -[([riC{-a11y-}], fib{-r4h,x-}, fib_a11e)] - <=_a12H = - PrelBase.<={-rdK,p-} - riC{-a11y-} - d.Ord_a11J - fromInt_a12G = - PrelBase.fromInt{-8R,p-} - riC{-a11y-} - d.Num_a11M - lit_a12F = - fromInt_a12G PrelBase.I#{-5b,p-}{i} 2# - d.Num_a11O = - d.Num_a11M - +_a12E = - PrelBase.+{-rdD,p-} - riC{-a11y-} - d.Num_a11O - d.Num_a11Q = - d.Num_a11M - -_a12D = - PrelBase.-{-817,p-} - riC{-a11y-} - d.Num_a11Q - fromInt_a12C = - fromInt_a12G - lit_a12B = - fromInt_a12C PrelBase.I#{-5b,p-}{i} 1# - -_a12A = - -_a12D - lit_a12z = - lit_a12F - fib_a11e - n_r3n = if n_r3n <=_a12H lit_a12F then - n_r3n - else - (fib_a11e n_r3n -_a12D lit_a12B) - +_a12E (fib_a11e n_r3n -_a12A lit_a12z) -{- nonrec -} -tc049.hs:27: - Warning: Possibly incomplete patterns - in the definition of function `mem4' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d14 1 $d15 1 $d2 1 $d21 1 $d26 1 $d27 1 $d3 1 $d32 1 $d33 1 $d34 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d45 1 $d46 1 $d49 1 $d50 1 $d51 1 $d54 1 $d55 1 $d6 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Ord 1 Ordering 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1; -PrelTup 1 :: $d13 1 $d4 1 $d49 1 $d9 1; -_exports_ -ShouldSucceed fib main1 main2 main3 mem mem1 mem2 mem3 mem4 oR oR1; -_declarations_ -1 fib _:_ _forall_ [a] {PrelBase.Ord a, PrelBase.Num a} => a -> a ;; -1 main1 _:_ PrelBase.Bool ;; -1 main2 _:_ PrelBase.Bool ;; -1 main3 _:_ PrelBase.Bool ;; -1 mem _:_ _forall_ [a] {PrelBase.Eq a} => a -> [a] -> PrelBase.Bool ;; -1 mem1 _:_ _forall_ [a] {PrelBase.Eq a} => a -> [a] -> PrelBase.Bool ;; -1 mem2 _:_ _forall_ [a] {PrelBase.Eq a} => a -> [a] -> PrelBase.Bool ;; -1 mem3 _:_ _forall_ [a] {PrelBase.Eq a} => a -> [a] -> PrelBase.Bool ;; -1 mem4 _:_ _forall_ [a] {PrelBase.Eq a} => a -> [a] -> PrelBase.Bool ;; -1 oR _:_ PrelBase.Bool -> PrelBase.Bool -> PrelBase.Bool ;; -1 oR1 _:_ PrelBase.Bool -> PrelBase.Bool -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc050.hs b/ghc/compiler/tests/typecheck/should_succeed/tc050.hs deleted file mode 100644 index ef03b282d908116441dd2911d3f2a41b9892171e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc050.hs +++ /dev/null @@ -1,23 +0,0 @@ -module ShouldSucceed where - -class Foo a where - o_and :: a -> a -> a - - -instance Foo Bool where - o_and False x = False - o_and x False = False - o_and True True = True - - -instance Foo Int where - o_and x 0 = 0 - o_and 0 x = 0 - o_and 1 1 = 1 - - -f x y = o_and x False - -g x y = o_and x 1 - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc050.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc050.stderr deleted file mode 100644 index 21e76c07633c1c9b9c65efc169d47ec4edf2b956..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc050.stderr +++ /dev/null @@ -1,133 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -o_and{-r3P,x-} = - _/\_ a{-r3M-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aIR-}] -[d.Foo_aIK] -[([a{-aIR-}], $mo_and{-rHn,x-}, o_and_aIM)] - AbsBinds [] [] [([], o_and_aIM, o_and_aIO)] - o_and_aIO - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIR-} -> a{-aIR-} -> a{-aIR-}) "Class Foo Method o_and" -{- rec -} -AbsBinds [] [] [([], $d1{-rJ9,x-}, d.Foo_aI0)] - AbsBinds [] [] [([], o_and_aJa, o_and_aI3)] - lit_aJi = - lit_aJ7 - lit_aJh = - lit_aJ7 - ==_aJg = - ==_aJ6 - lit_aJf = - lit_aJ7 - ==_aJe = - ==_aJ6 - lit_aJd = - lit_aJ4 - ==_aJc = - ==_aJ6 - lit_aJb = - lit_aJ4 - o_and_aI3 - x_r3r 0 = lit_aJi - o_and_aI3 - 0 x_r3v = lit_aJf - o_and_aI3 - 1 1 = lit_aJb - d.Foo_aI0 = - ({-dict-} [] [o_and_aJa]) -{- rec -} -AbsBinds [] [] [([], $d2{-rJj,x-}, d.Foo_aIB)] - AbsBinds [] [] [([], o_and_aJk, o_and_aIE)] - o_and_aIE - PrelBase.False{-58,p-}{i} x_r3E - = PrelBase.False{-58,p-}{i} - o_and_aIE - x_r3G PrelBase.False{-58,p-}{i} - = PrelBase.False{-58,p-}{i} - o_and_aIE - PrelBase.True{-5E,p-}{i} PrelBase.True{-5E,p-}{i} - = PrelBase.True{-5E,p-}{i} - d.Foo_aIB = - ({-dict-} [] [o_and_aJk]) -{- nonrec -} -d.Num_aIV = - PrelBase.$d3{-rbG,p-} -fromInt_aJ8 = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aIV -lit_aJ7 = - fromInt_aJ8 PrelBase.I#{-5b,p-}{i} 0# -d.Eq_aIY = - PrelBase.$d7{-rcc,p-} -==_aJ6 = - PrelBase.=={-8Y,p-} - PrelBase.Int{-3g,p-} - d.Eq_aIY -fromInt_aJ5 = - fromInt_aJ8 -lit_aJ4 = - fromInt_aJ5 PrelBase.I#{-5b,p-}{i} 1# -d.Foo_aJ2 = - $d2{-rJj,x-} -o_and_aJ3 = - o_and{-r3P,x-} - PrelBase.Bool{-34,p-} - d.Foo_aJ2 -{- nonrec -} -AbsBinds -[t{-aHw-}, t{-aHB-}] -[d.Foo_aHD, d.Num_aHG] -[([t{-aHw-}, t{-aHB-}], g{-r3N,x-}, g_aHm)] - o_and_aJn = - o_and{-r3P,x-} - t{-aHw-} - d.Foo_aHD - fromInt_aJm = - PrelBase.fromInt{-8R,p-} - t{-aHw-} - d.Num_aHG - lit_aJl = - fromInt_aJm PrelBase.I#{-5b,p-}{i} 1# - g_aHm - x_r3k y_r3m - = o_and_aJn x_r3k lit_aJl -{- nonrec -} -{- nonrec -} -AbsBinds [t{-aHT-}] [] [([t{-aHT-}], f{-r3O,x-}, f_aHI)] - f_aHI - x_r3g y_r3i - = o_and_aJ3 x_r3g PrelBase.False{-58,p-}{i} -{- nonrec -} -tc050.hs:14: - Warning: Possibly incomplete patterns - in the definition of function `o_and' -tc050.hs:8: - Warning: Possibly incomplete patterns - in the definition of function `o_and' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f g Foo(o_and); -_instances_ -instance {Foo PrelBase.Int} = $d1; -instance {Foo PrelBase.Bool} = $d2; -_declarations_ -1 $d1 _:_ {Foo PrelBase.Int} ;; -1 $d2 _:_ {Foo PrelBase.Bool} ;; -1 $mo_and _:_ _forall_ [a] {Foo a} => a -> a -> a ;; -1 class Foo r3M where {o_and :: r3M -> r3M -> r3M} ; -1 f _:_ _forall_ [a] => PrelBase.Bool -> a -> PrelBase.Bool ;; -1 g _:_ _forall_ [a b] {Foo a, PrelBase.Num a} => a -> b -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc051.hs b/ghc/compiler/tests/typecheck/should_succeed/tc051.hs deleted file mode 100644 index 7f14282fb8d53c9dfcff5e18f7b8a5407435027d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc051.hs +++ /dev/null @@ -1,30 +0,0 @@ -module ShouldSucceed where - -class Eq' a where - doubleeq :: a -> a -> Bool - -class (Eq' a) => Ord' a where - lt :: a -> a -> Bool - -instance Eq' Int where - doubleeq x y = True - -instance (Eq' a) => Eq' [a] where - doubleeq x y = True - -instance Ord' Int where - lt x y = True - -{- -class (Ord a) => Ix a where - range :: (a,a) -> [a] - -instance Ix Int where - range (x,y) = [x,y] --} - - - - - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc051.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc051.stderr deleted file mode 100644 index a578587bd1bb7e0a3082c9bf20840244e075aa10..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc051.stderr +++ /dev/null @@ -1,85 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_Ord'ShouldSucceedEq'{-aoN,x-} = - _/\_ a{-r3G-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -lt{-r3L,x-} = - _/\_ a{-r3G-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aoB-}] -[d.Ord'_aou] -[([a{-aoB-}], $mlt{-roO,x-}, lt_aow)] - AbsBinds [] [] [([], lt_aow, lt_aoy)] - lt_aoy - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aoB-} - -> a{-aoB-} - -> PrelBase.Bool{-34,p-}) "Class Ord' Method lt" -{- nonrec -} -doubleeq{-r3N,x-} = - _/\_ a{-r3K-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aoM-}] -[d.Eq'_aoF] -[([a{-aoM-}], $mdoubleeq{-roP,x-}, doubleeq_aoH)] - AbsBinds [] [] [([], doubleeq_aoH, doubleeq_aoJ)] - doubleeq_aoJ - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aoM-} - -> a{-aoM-} - -> PrelBase.Bool{-34,p-}) "Class Eq' Method doubleeq" -{- rec -} -AbsBinds [] [] [([], $d1{-roQ,x-}, d.Ord'_anQ)] - d.Eq'_anU = - $d3{-roS,x-} - AbsBinds [] [] [([], lt_aoR, lt_anT)] - lt_anT - x_r3j y_r3l - = PrelBase.True{-5E,p-}{i} - d.Ord'_anQ = - ({-dict-} [d.Eq'_anU] [lt_aoR]) -{- rec -} -AbsBinds -[a{-aob-}] -[d.Eq'_aoe] -[([a{-aob-}], $d2{-roT,x-}, d.Eq'_ao5)] - AbsBinds [] [] [([], doubleeq_aoU, doubleeq_ao8)] - doubleeq_ao8 - x_r3t y_r3v - = PrelBase.True{-5E,p-}{i} - d.Eq'_ao5 = - ({-dict-} [] [doubleeq_aoU]) -{- rec -} -AbsBinds [] [] [([], $d3{-roS,x-}, d.Eq'_aol)] - AbsBinds [] [] [([], doubleeq_aoV, doubleeq_aoo)] - doubleeq_aoo - x_r3B y_r3D - = PrelBase.True{-5E,p-}{i} - d.Eq'_aol = - ({-dict-} [] [doubleeq_aoV]) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed Eq'(doubleeq) Ord'(lt); -_instances_ -instance {Ord' PrelBase.Int} = $d1; -instance _forall_ [a] {Eq' a} => {Eq' [a]} = $d2; -instance {Eq' PrelBase.Int} = $d3; -_declarations_ -1 $d1 _:_ {Ord' PrelBase.Int} ;; -1 $d2 _:_ _forall_ [a] {Eq' a} => {Eq' [a]} ;; -1 $d3 _:_ {Eq' PrelBase.Int} ;; -1 $mdoubleeq _:_ _forall_ [a] {Eq' a} => a -> a -> PrelBase.Bool ;; -1 $mlt _:_ _forall_ [a] {Ord' a} => a -> a -> PrelBase.Bool ;; -1 class Eq' r3K where {doubleeq :: r3K -> r3K -> PrelBase.Bool} ; -1 class {Eq' r3G} => Ord' r3G where {lt :: r3G -> r3G -> PrelBase.Bool} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc052.hs b/ghc/compiler/tests/typecheck/should_succeed/tc052.hs deleted file mode 100644 index 108ef12046ad6db96477e422bdbf91d694216032..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc052.hs +++ /dev/null @@ -1,8 +0,0 @@ -module ShouldSucceed where - -type A a = B a - -type B c = C - -type C = Int - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc052.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc052.stderr deleted file mode 100644 index fe73b103e992447be5e215ae97058777079569da..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc052.stderr +++ /dev/null @@ -1,15 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed A B C; -_declarations_ -1 type A r3i = B r3i ; -1 type B r3g = C ; -1 type C = PrelBase.Int ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc053.hs b/ghc/compiler/tests/typecheck/should_succeed/tc053.hs deleted file mode 100644 index 865211d9175e86e933dce118ba004ccf4c9d13d9..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc053.hs +++ /dev/null @@ -1,12 +0,0 @@ -module ShouldSucceed where - -class Eq' a where - deq :: a -> a -> Bool - -instance Eq' Int where - deq x y = True - -instance (Eq' a) => Eq' [a] where - deq (a:as) (b:bs) = if (deq a b) then (deq as bs) else False - -f x = deq x [1] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc053.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc053.stderr deleted file mode 100644 index ada7849daf0e9ed1fb9be0e9498b19d767b97da5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc053.stderr +++ /dev/null @@ -1,94 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -deq{-r3D,x-} = - _/\_ a{-r3B-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aIm-}] -[d.Eq'_aIf] -[([a{-aIm-}], $mdeq{-rHb,x-}, deq_aIh)] - AbsBinds [] [] [([], deq_aIh, deq_aIj)] - deq_aIj - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIm-} - -> a{-aIm-} - -> PrelBase.Bool{-34,p-}) "Class Eq' Method deq" -{- rec -} -AbsBinds -[a{-aHK-}] -[d.Eq'_aHW] -[([a{-aHK-}], $d1{-rIn,x-}, d.Eq'_aHA)] - d.Eq'_aI0 = - d.Eq'_aHW - deq_aIq = - deq{-r3D,x-} - a{-aHK-} - d.Eq'_aI0 - deq_aIp = - deq_aIo - AbsBinds [] [] [([], deq_aIo, deq_aHD)] - deq_aHD - (a_r3m PrelBase.:{-55,p-}{i} as_r3n) - (b_r3p PrelBase.:{-55,p-}{i} bs_r3q) - = if deq_aIq a_r3m b_r3p then - deq_aIp as_r3n bs_r3q - else - PrelBase.False{-58,p-}{i} - d.Eq'_aHA = - ({-dict-} [] [deq_aIo]) -{- rec -} -AbsBinds [] [] [([], $d2{-rIr,x-}, d.Eq'_aI6)] - AbsBinds [] [] [([], deq_aIs, deq_aI9)] - deq_aI9 - x_r3w y_r3y - = PrelBase.True{-5E,p-}{i} - d.Eq'_aI6 = - ({-dict-} [] [deq_aIs]) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aHl-}] -[d.Eq'_aHr, d.Num_aHu] -[([t{-aHl-}], f{-r3C,x-}, f_aHa)] - d.Eq'_aHp = - $d1{-rIn,x-} - t{-aHl-} - d.Eq'_aHr - deq_aIv = - deq{-r3D,x-} - [t{-aHl-}] - d.Eq'_aHp - fromInt_aIu = - PrelBase.fromInt{-8R,p-} - t{-aHl-} - d.Num_aHu - lit_aIt = - fromInt_aIu PrelBase.I#{-5b,p-}{i} 1# - f_aHa - x_r3f = deq_aIv x_r3f [lit_aIt] (t{-aHl-}) -{- nonrec -} -tc053.hs:10: - Warning: Possibly incomplete patterns - in the definition of function `deq' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f Eq'(deq); -_instances_ -instance _forall_ [a] {Eq' a} => {Eq' [a]} = $d1; -instance {Eq' PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {Eq' a} => {Eq' [a]} ;; -1 $d2 _:_ {Eq' PrelBase.Int} ;; -1 $mdeq _:_ _forall_ [a] {Eq' a} => a -> a -> PrelBase.Bool ;; -1 class Eq' r3B where {deq :: r3B -> r3B -> PrelBase.Bool} ; -1 f _:_ _forall_ [a] {Eq' a, PrelBase.Num a} => [a] -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc054.hs b/ghc/compiler/tests/typecheck/should_succeed/tc054.hs deleted file mode 100644 index df9deb08aaeafdb96be7b9582e5beb1d8fcac365..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc054.hs +++ /dev/null @@ -1,16 +0,0 @@ -module ShouldSucceed where - -class Eq' a where - doubleeq :: a -> a -> Bool - -class (Eq' a) => Ord' a where - lt :: a -> a -> Bool - -instance Eq' Int where - doubleeq x y = True - -instance Ord' Int where - lt x y = True - -f x y | lt x 1 = True - | otherwise = False diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc054.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc054.stderr deleted file mode 100644 index e9c470b440661a4999ae4e95d2c82f1301a02226..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc054.stderr +++ /dev/null @@ -1,98 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_Ord'ShouldSucceedEq'{-aIr,x-} = - _/\_ a{-r3B-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -lt{-r3I,x-} = - _/\_ a{-r3B-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aIf-}] -[d.Ord'_aI8] -[([a{-aIf-}], $mlt{-rHm,x-}, lt_aIa)] - AbsBinds [] [] [([], lt_aIa, lt_aIc)] - lt_aIc - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIf-} - -> a{-aIf-} - -> PrelBase.Bool{-34,p-}) "Class Ord' Method lt" -{- nonrec -} -doubleeq{-r3K,x-} = - _/\_ a{-r3G-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aIq-}] -[d.Eq'_aIj] -[([a{-aIq-}], $mdoubleeq{-rHn,x-}, doubleeq_aIl)] - AbsBinds [] [] [([], doubleeq_aIl, doubleeq_aIn)] - doubleeq_aIn - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIq-} - -> a{-aIq-} - -> PrelBase.Bool{-34,p-}) "Class Eq' Method doubleeq" -{- rec -} -AbsBinds [] [] [([], $d1{-rIs,x-}, d.Ord'_aHL)] - d.Eq'_aHP = - $d2{-rIu,x-} - AbsBinds [] [] [([], lt_aIt, lt_aHO)] - lt_aHO - x_r3o y_r3q - = PrelBase.True{-5E,p-}{i} - d.Ord'_aHL = - ({-dict-} [d.Eq'_aHP] [lt_aIt]) -{- rec -} -AbsBinds [] [] [([], $d2{-rIu,x-}, d.Eq'_aHZ)] - AbsBinds [] [] [([], doubleeq_aIv, doubleeq_aI2)] - doubleeq_aI2 - x_r3w y_r3y - = PrelBase.True{-5E,p-}{i} - d.Eq'_aHZ = - ({-dict-} [] [doubleeq_aIv]) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aHw-}, t{-aHB-}] -[d.Ord'_aHD, d.Num_aHG] -[([t{-aHw-}, t{-aHB-}], f{-r3H,x-}, f_aHl)] - lt_aIy = - lt{-r3I,x-} - t{-aHw-} - d.Ord'_aHD - fromInt_aIx = - PrelBase.fromInt{-8R,p-} - t{-aHw-} - d.Num_aHG - lit_aIw = - fromInt_aIx PrelBase.I#{-5b,p-}{i} 1# - f_aHl - x_r3h y_r3j - | [lt_aIy x_r3h lit_aIw] = - PrelBase.True{-5E,p-}{i} - | [PrelBase.otherwise{-818,p-}] = - PrelBase.False{-58,p-}{i} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 otherwise 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f Eq'(doubleeq) Ord'(lt); -_instances_ -instance {Ord' PrelBase.Int} = $d1; -instance {Eq' PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ {Ord' PrelBase.Int} ;; -1 $d2 _:_ {Eq' PrelBase.Int} ;; -1 $mdoubleeq _:_ _forall_ [a] {Eq' a} => a -> a -> PrelBase.Bool ;; -1 $mlt _:_ _forall_ [a] {Ord' a} => a -> a -> PrelBase.Bool ;; -1 class Eq' r3G where {doubleeq :: r3G -> r3G -> PrelBase.Bool} ; -1 class {Eq' r3B} => Ord' r3B where {lt :: r3B -> r3B -> PrelBase.Bool} ; -1 f _:_ _forall_ [a b] {Ord' a, PrelBase.Num a} => a -> b -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc055.hs b/ghc/compiler/tests/typecheck/should_succeed/tc055.hs deleted file mode 100644 index cdbb8f4b4d81f0a1c9b4431826bba1541a565ffb..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc055.hs +++ /dev/null @@ -1,3 +0,0 @@ -module ShouldSucceed where - -(x,y) = (\p -> p,\q -> q) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc055.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc055.stderr deleted file mode 100644 index 5980a7536a86cb5eb619f347b1ff669b22fe14f5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc055.stderr +++ /dev/null @@ -1,26 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aBi-}, t{-aBk-}] -[] -[([t{-aBi-}, t{-aBk-}], x{-r3i,x-}, x_aB3), ([t{-aBi-}, t{-aBk-}], - y{-r3h,x-}, - y_aB4)] - (x_aB3, y_aB4) - = (\ p_r3e -> p_r3e, \ q_r3g -> q_r3g) -{- nonrec -} - -NOTE: Simplifier still going after 4 iterations; bailing out. -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed x y; -_declarations_ -1 x _:_ _forall_ [a b] => a -> a ;; -1 y _:_ _forall_ [a b] => b -> b ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc056.hs b/ghc/compiler/tests/typecheck/should_succeed/tc056.hs deleted file mode 100644 index f5198f245ddd1f3adeba7cdf6bc2e4f95f283e6e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc056.hs +++ /dev/null @@ -1,15 +0,0 @@ -module ShouldSucceed where - -class Eq' a where - doubleeq :: a -> a -> Bool - -class (Eq' a) => Ord' a where - lt :: a -> a -> Bool - -instance Eq' Int where - doubleeq x y = True - -instance (Eq' a,Eq' a) => Eq' [a] where - doubleeq x y = True - -f x y = doubleeq x [1] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc056.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc056.stderr deleted file mode 100644 index 7d29402556978f6a479b4a3fab6ccdd91743e56b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc056.stderr +++ /dev/null @@ -1,112 +0,0 @@ - -tc056.hs:13:warning: - Duplicate class assertion `[(`Eq'', - `a'), - (`Eq'', - `a')]' in context: - [(`Eq'', - `a'), - (`Eq'', - `a')] - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_Ord'ShouldSucceedEq'{-aID,x-} = - _/\_ a{-r3D-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -lt{-r3J,x-} = - _/\_ a{-r3D-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aIr-}] -[d.Ord'_aIk] -[([a{-aIr-}], $mlt{-rHo,x-}, lt_aIm)] - AbsBinds [] [] [([], lt_aIm, lt_aIo)] - lt_aIo - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIr-} - -> a{-aIr-} - -> PrelBase.Bool{-34,p-}) "Class Ord' Method lt" -{- nonrec -} -doubleeq{-r3L,x-} = - _/\_ a{-r3H-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aIC-}] -[d.Eq'_aIv] -[([a{-aIC-}], $mdoubleeq{-rHp,x-}, doubleeq_aIx)] - AbsBinds [] [] [([], doubleeq_aIx, doubleeq_aIz)] - doubleeq_aIz - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIC-} - -> a{-aIC-} - -> PrelBase.Bool{-34,p-}) "Class Eq' Method doubleeq" -{- rec -} -AbsBinds -[a{-aHZ-}] -[d.Eq'_aI2, d.Eq'_aI3] -[([a{-aHZ-}], $d1{-rIE,x-}, d.Eq'_aHT)] - AbsBinds [] [] [([], doubleeq_aIF, doubleeq_aHW)] - doubleeq_aHW - x_r3q y_r3s - = PrelBase.True{-5E,p-}{i} - d.Eq'_aHT = - ({-dict-} [] [doubleeq_aIF]) -{- rec -} -AbsBinds [] [] [([], $d2{-rIG,x-}, d.Eq'_aIb)] - AbsBinds [] [] [([], doubleeq_aIH, doubleeq_aIe)] - doubleeq_aIe - x_r3y y_r3A - = PrelBase.True{-5E,p-}{i} - d.Eq'_aIb = - ({-dict-} [] [doubleeq_aIH]) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aHA-}, t{-aHF-}] -[d.Eq'_aHJ, d.Num_aHN] -[([t{-aHA-}, t{-aHF-}], f{-r3I,x-}, f_aHn)] - d.Eq'_aHK = - d.Eq'_aHJ - d.Eq'_aHH = - $d1{-rIE,x-} - t{-aHA-} - [d.Eq'_aHJ, d.Eq'_aHK] - doubleeq_aIK = - doubleeq{-r3L,x-} - [t{-aHA-}] - d.Eq'_aHH - fromInt_aIJ = - PrelBase.fromInt{-8R,p-} - t{-aHA-} - d.Num_aHN - lit_aII = - fromInt_aIJ PrelBase.I#{-5b,p-}{i} 1# - f_aHn - x_r3h y_r3j - = doubleeq_aIK x_r3h [lit_aII] (t{-aHA-}) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f Eq'(doubleeq) Ord'(lt); -_instances_ -instance _forall_ [a] {Eq' a, Eq' a} => {Eq' [a]} = $d1; -instance {Eq' PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {Eq' a, Eq' a} => {Eq' [a]} ;; -1 $d2 _:_ {Eq' PrelBase.Int} ;; -1 $mdoubleeq _:_ _forall_ [a] {Eq' a} => a -> a -> PrelBase.Bool ;; -1 $mlt _:_ _forall_ [a] {Ord' a} => a -> a -> PrelBase.Bool ;; -1 class Eq' r3H where {doubleeq :: r3H -> r3H -> PrelBase.Bool} ; -1 class {Eq' r3D} => Ord' r3D where {lt :: r3D -> r3D -> PrelBase.Bool} ; -1 f _:_ _forall_ [a b] {Eq' a, PrelBase.Num a} => [a] -> b -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc057.hi b/ghc/compiler/tests/typecheck/should_succeed/tc057.hi deleted file mode 100644 index 3613dfacb6086edf6c6fbbc3b573cecd04026cec..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc057.hi +++ /dev/null @@ -1,7 +0,0 @@ -interface ShouldSucceed where { -class Eq' a where { deq } -instance <Eq' Int> -instance Eq' a => <Eq' [a]> -dand :: Bool -> Bool -> Bool -f :: Eq' t93 => t93 -> t93 -> Bool -} diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc057.hs b/ghc/compiler/tests/typecheck/should_succeed/tc057.hs deleted file mode 100644 index cc561b95b88e5734dc2821ce3f9185dd64e9f0eb..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc057.hs +++ /dev/null @@ -1,18 +0,0 @@ -module ShouldSucceed where - --- See also tcfail060.hs - -class Eq' a where - deq :: a -> a -> Bool - -instance Eq' Int where - deq x y = True - -instance (Eq' a) => Eq' [a] where - deq (a:as) (b:bs) = dand (f a b) (f as bs) - -dand True True = True -dand x y = False - -f :: Eq' a => a -> a -> Bool -f p q = dand (deq p q) (deq [1::Int] [2::Int]) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc057.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc057.stderr deleted file mode 100644 index d0c198309bf40d4de712192b5d965517204ff372..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc057.stderr +++ /dev/null @@ -1,126 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -deq{-r3R,x-} = - _/\_ a{-r3Q-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aIY-}] -[d.Eq'_aIR] -[([a{-aIY-}], $mdeq{-rHC,x-}, deq_aIT)] - AbsBinds [] [] [([], deq_aIT, deq_aIV)] - deq_aIV - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIY-} - -> a{-aIY-} - -> PrelBase.Bool{-34,p-}) "Class Eq' Method deq" -{- rec -} -AbsBinds -[a{-aIk-}] -[d.Eq'_aIw] -[([a{-aIk-}], $d1{-rJf,x-}, d.Eq'_aIa)] - d.Eq'_aIA = - d.Eq'_aIw - f_aJi = - f{-r3i,x-} - a{-aIk-} - d.Eq'_aIA - d.Eq'_aIC = - d.Eq'_aIa - f_aJh = - f{-r3i,x-} - [a{-aIk-}] - d.Eq'_aIC - AbsBinds [] [] [([], deq_aJg, deq_aId)] - deq_aId - (a_r3B PrelBase.:{-55,p-}{i} as_r3C) - (b_r3E PrelBase.:{-55,p-}{i} bs_r3F) - = dand{-r3j,x-} f_aJi a_r3B b_r3E f_aJh as_r3C bs_r3F - d.Eq'_aIa = - ({-dict-} [] [deq_aJg]) -{- rec -} -AbsBinds [] [] [([], $d2{-rJj,x-}, d.Eq'_aII)] - AbsBinds [] [] [([], deq_aJk, deq_aIL)] - deq_aIL - x_r3L y_r3N - = PrelBase.True{-5E,p-}{i} - d.Eq'_aII = - ({-dict-} [] [deq_aJk]) -{- nonrec -} -d.Eq'_aJ3 = - $d2{-rJj,x-} -d.Eq'_aJ1 = - $d1{-rJf,x-} - PrelBase.Int{-3g,p-} - d.Eq'_aJ3 -deq_aJe = - deq{-r3R,x-} - [PrelBase.Int{-3g,p-}] - d.Eq'_aJ1 -d.Num_aJ7 = - PrelBase.$d3{-rbH,p-} -fromInt_aJd = - PrelBase.fromInt{-8R,p-} - PrelBase.Int{-3g,p-} - d.Num_aJ7 -lit_aJc = - fromInt_aJd PrelBase.I#{-5b,p-}{i} 1# -fromInt_aJb = - fromInt_aJd -lit_aJ8 = - fromInt_aJb PrelBase.I#{-5b,p-}{i} 2# -{- nonrec -} -AbsBinds [] [] [([], dand{-r3j,x-}, dand_aHo)] - dand_aHo - PrelBase.True{-5E,p-}{i} PrelBase.True{-5E,p-}{i} - = PrelBase.True{-5E,p-}{i} - dand_aHo - x_r3n y_r3p - = PrelBase.False{-58,p-}{i} -{- nonrec -} -{- nonrec -} -AbsBinds [a{-aHz-}] [d.Eq'_aHY] [([a{-aHz-}], f{-r3i,x-}, f_aHw)] - d.Eq'_aI0 = - d.Eq'_aHY - deq_aJl = - deq{-r3R,x-} - a{-aHz-} - d.Eq'_aI0 - f_aHw - p_r3r q_r3t - = dand{-r3j,x-} deq_aJl p_r3r q_r3t - deq_aJe [lit_aJc] (PrelBase.Int{-3g,p-}) - [lit_aJ8] (PrelBase.Int{-3g,p-}) -{- nonrec -} -tc057.hs:12: - Warning: Possibly incomplete patterns - in the definition of function `deq' -ghc:junk old iface line?:section::interface ShouldSucceed where { -ghc:junk old iface line?:section::class Eq' a where { deq } -ghc:junk old iface line?:section::instance <Eq' Int> -ghc:junk old iface line?:section::instance Eq' a => <Eq' [a]> -ghc:junk old iface line?:section::dand :: Bool -> Bool -> Bool -ghc:junk old iface line?:section::f :: Eq' t93 => t93 -> t93 -> Bool -ghc:junk old iface line?:section::} -ghc: module version changed to 1; reason: usages changed -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed dand f Eq'(deq); -_instances_ -instance _forall_ [a] {Eq' a} => {Eq' [a]} = $d1; -instance {Eq' PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {Eq' a} => {Eq' [a]} ;; -1 $d2 _:_ {Eq' PrelBase.Int} ;; -1 $mdeq _:_ _forall_ [a] {Eq' a} => a -> a -> PrelBase.Bool ;; -1 class Eq' r3Q where {deq :: r3Q -> r3Q -> PrelBase.Bool} ; -1 dand _:_ PrelBase.Bool -> PrelBase.Bool -> PrelBase.Bool ;; -1 f _:_ _forall_ [a] {Eq' a} => a -> a -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc058.hs b/ghc/compiler/tests/typecheck/should_succeed/tc058.hs deleted file mode 100644 index 7df1f3bc6d7f3bb7ad2d82e6446123cf9dedfb76..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc058.hs +++ /dev/null @@ -1,18 +0,0 @@ -module ShouldSucceed where - -class Eq2 a where - doubleeq :: a -> a -> Bool - -class (Eq2 a) => Ord2 a where - lt :: a -> a -> Bool - -instance Eq2 Int where - doubleeq x y = True - -instance Ord2 Int where - lt x y = True - -instance (Eq2 a,Ord2 a) => Eq2 [a] where - doubleeq xs ys = True - -f x y = doubleeq x [1] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc058.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc058.stderr deleted file mode 100644 index e933039ea2d0d609dcb1ebde5a21f97aafdfdbd7..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc058.stderr +++ /dev/null @@ -1,116 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -scsel_Ord2ShouldSucceedEq2{-aJ0,x-} = - _/\_ a{-r3M-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -lt{-r3S,x-} = - _/\_ a{-r3M-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aIO-}] -[d.Ord2_aIH] -[([a{-aIO-}], $mlt{-rHw,x-}, lt_aIJ)] - AbsBinds [] [] [([], lt_aIJ, lt_aIL)] - lt_aIL - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIO-} - -> a{-aIO-} - -> PrelBase.Bool{-34,p-}) "Class Ord2 Method lt" -{- nonrec -} -doubleeq{-r3T,x-} = - _/\_ a{-r3Q-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aIZ-}] -[d.Eq2_aIS] -[([a{-aIZ-}], $mdoubleeq{-rHx,x-}, doubleeq_aIU)] - AbsBinds [] [] [([], doubleeq_aIU, doubleeq_aIW)] - doubleeq_aIW - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIZ-} - -> a{-aIZ-} - -> PrelBase.Bool{-34,p-}) "Class Eq2 Method doubleeq" -{- rec -} -AbsBinds -[a{-aI8-}] -[d.Eq2_aIb, d.Ord2_aIc] -[([a{-aI8-}], $d1{-rJ1,x-}, d.Eq2_aI2)] - AbsBinds [] [] [([], doubleeq_aJ2, doubleeq_aI5)] - doubleeq_aI5 - xs_r3r ys_r3t - = PrelBase.True{-5E,p-}{i} - d.Eq2_aI2 = - ({-dict-} [] [doubleeq_aJ2]) -{- rec -} -AbsBinds [] [] [([], $d2{-rJ3,x-}, d.Ord2_aIk)] - d.Eq2_aIo = - $d3{-rJ5,x-} - AbsBinds [] [] [([], lt_aJ4, lt_aIn)] - lt_aIn - x_r3z y_r3B - = PrelBase.True{-5E,p-}{i} - d.Ord2_aIk = - ({-dict-} [d.Eq2_aIo] [lt_aJ4]) -{- rec -} -AbsBinds [] [] [([], $d3{-rJ5,x-}, d.Eq2_aIy)] - AbsBinds [] [] [([], doubleeq_aJ6, doubleeq_aIB)] - doubleeq_aIB - x_r3H y_r3J - = PrelBase.True{-5E,p-}{i} - d.Eq2_aIy = - ({-dict-} [] [doubleeq_aJ6]) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aHI-}, t{-aHN-}] -[d.Ord2_aHS, d.Num_aHV] -[([t{-aHI-}, t{-aHN-}], f{-r3R,x-}, f_aHv)] - d.Eq2_aHR = - scsel_Ord2ShouldSucceedEq2{-aJ0,x-} - t{-aHI-} - d.Ord2_aHS - d.Eq2_aHP = - $d1{-rJ1,x-} - t{-aHI-} - [d.Eq2_aHR, d.Ord2_aHS] - doubleeq_aJ9 = - doubleeq{-r3T,x-} - [t{-aHI-}] - d.Eq2_aHP - fromInt_aJ8 = - PrelBase.fromInt{-8R,p-} - t{-aHI-} - d.Num_aHV - lit_aJ7 = - fromInt_aJ8 PrelBase.I#{-5b,p-}{i} 1# - f_aHv - x_r3h y_r3j - = doubleeq_aJ9 x_r3h [lit_aJ7] (t{-aHI-}) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f Eq2(doubleeq) Ord2(lt); -_instances_ -instance _forall_ [a] {Eq2 a, Ord2 a} => {Eq2 [a]} = $d1; -instance {Ord2 PrelBase.Int} = $d2; -instance {Eq2 PrelBase.Int} = $d3; -_declarations_ -1 $d1 _:_ _forall_ [a] {Eq2 a, Ord2 a} => {Eq2 [a]} ;; -1 $d2 _:_ {Ord2 PrelBase.Int} ;; -1 $d3 _:_ {Eq2 PrelBase.Int} ;; -1 $mdoubleeq _:_ _forall_ [a] {Eq2 a} => a -> a -> PrelBase.Bool ;; -1 $mlt _:_ _forall_ [a] {Ord2 a} => a -> a -> PrelBase.Bool ;; -1 class Eq2 r3Q where {doubleeq :: r3Q -> r3Q -> PrelBase.Bool} ; -1 class {Eq2 r3M} => Ord2 r3M where {lt :: r3M -> r3M -> PrelBase.Bool} ; -1 f _:_ _forall_ [a b] {Ord2 a, PrelBase.Num a} => [a] -> b -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc059.hs b/ghc/compiler/tests/typecheck/should_succeed/tc059.hs deleted file mode 100644 index f0faac8155968230cf6de449e1fc581906d87336..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc059.hs +++ /dev/null @@ -1,15 +0,0 @@ -module ShouldSucceed where - -class Eq2 a where - deq :: a -> a -> Bool - foo :: a -> a - -instance Eq2 Int where - deq x y = True - foo x = x - -instance (Eq2 a) => Eq2 [a] where - deq (a:as) (b:bs) = if (deq a (foo b)) then (deq as (foo bs)) else False - foo x = x - -f x = deq x [1] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc059.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc059.stderr deleted file mode 100644 index 39105c91145f8cf500daf98c17fdcdeca142056b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc059.stderr +++ /dev/null @@ -1,120 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -deq{-r3N,x-} = - _/\_ a{-r3K-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -foo{-r3M,x-} = - _/\_ a{-r3K-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aIS-}] -[d.Eq2_aIL] -[([a{-aIS-}], $mdeq{-rHo,x-}, deq_aIN)] - AbsBinds [] [] [([], deq_aIN, deq_aIP)] - deq_aIP - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIS-} - -> a{-aIS-} - -> PrelBase.Bool{-34,p-}) "Class Eq2 Method deq" -AbsBinds -[a{-aIS-}] -[d.Eq2_aIV] -[([a{-aIS-}], $mfoo{-rHn,x-}, foo_aIX)] - AbsBinds [] [] [([], foo_aIX, foo_aIZ)] - foo_aIZ - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aIS-} -> a{-aIS-}) "Class Eq2 Method foo" -{- rec -} -AbsBinds -[a{-aHX-}] -[d.Eq2_aIm] -[([a{-aHX-}], $d1{-rJ2,x-}, d.Eq2_aHN)] - d.Eq2_aIp = - d.Eq2_aIm - deq_aJ8 = - deq{-r3N,x-} - a{-aHX-} - d.Eq2_aIp - d.Eq2_aIr = - d.Eq2_aIm - foo_aJ7 = - foo{-r3M,x-} - a{-aHX-} - d.Eq2_aIr - deq_aJ6 = - deq_aJ4 - foo_aJ5 = - foo_aJ3 - AbsBinds [] [] [([], deq_aJ4, deq_aHQ)] - deq_aHQ - (a_r3n PrelBase.:{-55,p-}{i} as_r3o) - (b_r3q PrelBase.:{-55,p-}{i} bs_r3r) - = if deq_aJ8 a_r3n foo_aJ7 b_r3q then - deq_aJ6 as_r3o foo_aJ5 bs_r3r - else - PrelBase.False{-58,p-}{i} - AbsBinds [] [] [([], foo_aJ3, foo_aIj)] - foo_aIj - x_r3v = x_r3v - d.Eq2_aHN = - ({-dict-} [] [deq_aJ4, foo_aJ3]) -{- rec -} -AbsBinds [] [] [([], $d2{-rJ9,x-}, d.Eq2_aIx)] - AbsBinds [] [] [([], deq_aJb, deq_aIA)] - deq_aIA - x_r3B y_r3D - = PrelBase.True{-5E,p-}{i} - AbsBinds [] [] [([], foo_aJa, foo_aIG)] - foo_aIG - x_r3H = x_r3H - d.Eq2_aIx = - ({-dict-} [] [deq_aJb, foo_aJa]) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aHy-}] -[d.Eq2_aHE, d.Num_aHH] -[([t{-aHy-}], f{-r3L,x-}, f_aHm)] - d.Eq2_aHC = - $d1{-rJ2,x-} - t{-aHy-} - d.Eq2_aHE - deq_aJe = - deq{-r3N,x-} - [t{-aHy-}] - d.Eq2_aHC - fromInt_aJd = - PrelBase.fromInt{-8R,p-} - t{-aHy-} - d.Num_aHH - lit_aJc = - fromInt_aJd PrelBase.I#{-5b,p-}{i} 1# - f_aHm - x_r3g = deq_aJe x_r3g [lit_aJc] (t{-aHy-}) -{- nonrec -} -tc059.hs:12: - Warning: Possibly incomplete patterns - in the definition of function `deq' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -ShouldSucceed f Eq2(deq foo); -_instances_ -instance _forall_ [a] {Eq2 a} => {Eq2 [a]} = $d1; -instance {Eq2 PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {Eq2 a} => {Eq2 [a]} ;; -1 $d2 _:_ {Eq2 PrelBase.Int} ;; -1 $mdeq _:_ _forall_ [a] {Eq2 a} => a -> a -> PrelBase.Bool ;; -1 $mfoo _:_ _forall_ [a] {Eq2 a} => a -> a ;; -1 class Eq2 r3K where {deq :: r3K -> r3K -> PrelBase.Bool; foo :: r3K -> r3K} ; -1 f _:_ _forall_ [a] {Eq2 a, PrelBase.Num a} => [a] -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc060.hs b/ghc/compiler/tests/typecheck/should_succeed/tc060.hs deleted file mode 100644 index 6ae0ca92283677687bd0a45253f8eec04648eff4..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc060.hs +++ /dev/null @@ -1,12 +0,0 @@ -module ShouldSucceed where - -class Eq2 a where - deq :: a -> a -> Bool - -instance (Eq2 a) => Eq2 [a] where - deq (a:as) (b:bs) = if (deq a b) then (deq as bs) else False - - -instance Eq2 Int where - deq x y = True - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc060.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc060.stderr deleted file mode 100644 index 42a7567a0b6a951d7351003226d2b62be21cfb68..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc060.stderr +++ /dev/null @@ -1,68 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -deq{-r3z,x-} = - _/\_ a{-r3y-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aol-}] -[d.Eq2_aoe] -[([a{-aol-}], $mdeq{-ro0,x-}, deq_aog)] - AbsBinds [] [] [([], deq_aog, deq_aoi)] - deq_aoi - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aol-} - -> a{-aol-} - -> PrelBase.Bool{-34,p-}) "Class Eq2 Method deq" -{- rec -} -AbsBinds [] [] [([], $d1{-rom,x-}, d.Eq2_anx)] - AbsBinds [] [] [([], deq_aon, deq_anA)] - deq_anA - x_r3h y_r3j - = PrelBase.True{-5E,p-}{i} - d.Eq2_anx = - ({-dict-} [] [deq_aon]) -{- rec -} -AbsBinds -[a{-anT-}] -[d.Eq2_ao6] -[([a{-anT-}], $d2{-roo,x-}, d.Eq2_anJ)] - d.Eq2_aoa = - d.Eq2_ao6 - deq_aor = - deq{-r3z,x-} - a{-anT-} - d.Eq2_aoa - deq_aoq = - deq_aop - AbsBinds [] [] [([], deq_aop, deq_anM)] - deq_anM - (a_r3r PrelBase.:{-55,p-}{i} as_r3s) - (b_r3u PrelBase.:{-55,p-}{i} bs_r3v) - = if deq_aor a_r3r b_r3u then - deq_aoq as_r3s bs_r3v - else - PrelBase.False{-58,p-}{i} - d.Eq2_anJ = - ({-dict-} [] [deq_aop]) -{- nonrec -} -tc060.hs:7: - Warning: Possibly incomplete patterns - in the definition of function `deq' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed Eq2(deq); -_instances_ -instance {Eq2 PrelBase.Int} = $d1; -instance _forall_ [a] {Eq2 a} => {Eq2 [a]} = $d2; -_declarations_ -1 $d1 _:_ {Eq2 PrelBase.Int} ;; -1 $d2 _:_ _forall_ [a] {Eq2 a} => {Eq2 [a]} ;; -1 $mdeq _:_ _forall_ [a] {Eq2 a} => a -> a -> PrelBase.Bool ;; -1 class Eq2 r3y where {deq :: r3y -> r3y -> PrelBase.Bool} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc061.hs b/ghc/compiler/tests/typecheck/should_succeed/tc061.hs deleted file mode 100644 index 25a8b65f35573bd1a82cdb1a691bbe408a9fae66..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc061.hs +++ /dev/null @@ -1,11 +0,0 @@ -module ShouldSucceed where - -class Eq1 a where - deq :: a -> a -> Bool - -instance (Eq1 a) => Eq1 [a] where - deq (a:as) (b:bs) = deq a b - -instance Eq1 Int where - deq x y = True - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc061.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc061.stderr deleted file mode 100644 index a3fcb3bab2df21d32df7307e75de50c0b4b39d12..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc061.stderr +++ /dev/null @@ -1,63 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -deq{-r3z,x-} = - _/\_ a{-r3y-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aoi-}] -[d.Eq1_aob] -[([a{-aoi-}], $mdeq{-ro0,x-}, deq_aod)] - AbsBinds [] [] [([], deq_aod, deq_aof)] - deq_aof - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aoi-} - -> a{-aoi-} - -> PrelBase.Bool{-34,p-}) "Class Eq1 Method deq" -{- rec -} -AbsBinds [] [] [([], $d1{-roj,x-}, d.Eq1_anx)] - AbsBinds [] [] [([], deq_aok, deq_anA)] - deq_anA - x_r3h y_r3j - = PrelBase.True{-5E,p-}{i} - d.Eq1_anx = - ({-dict-} [] [deq_aok]) -{- rec -} -AbsBinds -[a{-anT-}] -[d.Eq1_ao3] -[([a{-anT-}], $d2{-rol,x-}, d.Eq1_anJ)] - d.Eq1_ao7 = - d.Eq1_ao3 - deq_aon = - deq{-r3z,x-} - a{-anT-} - d.Eq1_ao7 - AbsBinds [] [] [([], deq_aom, deq_anM)] - deq_anM - (a_r3r PrelBase.:{-55,p-}{i} as_r3s) - (b_r3u PrelBase.:{-55,p-}{i} bs_r3v) - = deq_aon a_r3r b_r3u - d.Eq1_anJ = - ({-dict-} [] [deq_aom]) -{- nonrec -} -tc061.hs:7: - Warning: Possibly incomplete patterns - in the definition of function `deq' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed Eq1(deq); -_instances_ -instance {Eq1 PrelBase.Int} = $d1; -instance _forall_ [a] {Eq1 a} => {Eq1 [a]} = $d2; -_declarations_ -1 $d1 _:_ {Eq1 PrelBase.Int} ;; -1 $d2 _:_ _forall_ [a] {Eq1 a} => {Eq1 [a]} ;; -1 $mdeq _:_ _forall_ [a] {Eq1 a} => a -> a -> PrelBase.Bool ;; -1 class Eq1 r3y where {deq :: r3y -> r3y -> PrelBase.Bool} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc062.hs b/ghc/compiler/tests/typecheck/should_succeed/tc062.hs deleted file mode 100644 index fde6c4b1dae5af7e595e0513ebf09515e2622619..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc062.hs +++ /dev/null @@ -1,12 +0,0 @@ -module ShouldSucceed where - -class Eq1 a where - deq :: a -> a -> Bool - -instance Eq1 Int where - deq x y = True - -instance (Eq1 a) => Eq1 [a] where - deq (a:as) (b:bs) = if (deq a b) then (deq as bs) else False - -f x (y:ys) = deq x ys diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc062.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc062.stderr deleted file mode 100644 index 33e6ca34512fd44a3a621ecbe3a738652f2085e3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc062.stderr +++ /dev/null @@ -1,86 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -deq{-r3G,x-} = - _/\_ a{-r3E-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-aoL-}] -[d.Eq1_aoE] -[([a{-aoL-}], $mdeq{-rnK,x-}, deq_aoG)] - AbsBinds [] [] [([], deq_aoG, deq_aoI)] - deq_aoI - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aoL-} - -> a{-aoL-} - -> PrelBase.Bool{-34,p-}) "Class Eq1 Method deq" -{- rec -} -AbsBinds -[a{-ao9-}] -[d.Eq1_aol] -[([a{-ao9-}], $d1{-roM,x-}, d.Eq1_anZ)] - d.Eq1_aop = - d.Eq1_aol - deq_aoP = - deq{-r3G,x-} - a{-ao9-} - d.Eq1_aop - deq_aoO = - deq_aoN - AbsBinds [] [] [([], deq_aoN, deq_ao2)] - deq_ao2 - (a_r3p PrelBase.:{-55,p-}{i} as_r3q) - (b_r3s PrelBase.:{-55,p-}{i} bs_r3t) - = if deq_aoP a_r3p b_r3s then - deq_aoO as_r3q bs_r3t - else - PrelBase.False{-58,p-}{i} - d.Eq1_anZ = - ({-dict-} [] [deq_aoN]) -{- rec -} -AbsBinds [] [] [([], $d2{-roQ,x-}, d.Eq1_aov)] - AbsBinds [] [] [([], deq_aoR, deq_aoy)] - deq_aoy - x_r3z y_r3B - = PrelBase.True{-5E,p-}{i} - d.Eq1_aov = - ({-dict-} [] [deq_aoR]) -{- nonrec -} -{- nonrec -} -AbsBinds [t{-anH-}] [d.Eq1_anT] [([t{-anH-}], f{-r3F,x-}, f_anB)] - d.Eq1_anR = - $d1{-roM,x-} - t{-anH-} - d.Eq1_anT - deq_aoS = - deq{-r3G,x-} - [t{-anH-}] - d.Eq1_anR - f_anB - x_r3f (y_r3h PrelBase.:{-55,p-}{i} ys_r3i) - = deq_aoS x_r3f ys_r3i -{- nonrec -} -tc062.hs:10: - Warning: Possibly incomplete patterns - in the definition of function `deq' -tc062.hs:12: - Warning: Possibly incomplete patterns - in the definition of function `f' -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed f Eq1(deq); -_instances_ -instance _forall_ [a] {Eq1 a} => {Eq1 [a]} = $d1; -instance {Eq1 PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {Eq1 a} => {Eq1 [a]} ;; -1 $d2 _:_ {Eq1 PrelBase.Int} ;; -1 $mdeq _:_ _forall_ [a] {Eq1 a} => a -> a -> PrelBase.Bool ;; -1 class Eq1 r3E where {deq :: r3E -> r3E -> PrelBase.Bool} ; -1 f _:_ _forall_ [a] {Eq1 a} => [a] -> [a] -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc063.hs b/ghc/compiler/tests/typecheck/should_succeed/tc063.hs deleted file mode 100644 index 36affbfdcedbc2a306b67a64c3d3749d12169768..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc063.hs +++ /dev/null @@ -1,18 +0,0 @@ -module ShouldSucceed where - -data X a = Tag a - -class Reps r where - f :: r -> r -> r - -instance Reps (X q) where --- f (Tag x) (Tag y) = Tag y - f x y = y - -instance Reps Bool where - f True True = True - f x y = False - -g x = f x x - - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc063.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc063.stderr deleted file mode 100644 index b2e89fd92b361c67775561f7c230000f9b05721b..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc063.stderr +++ /dev/null @@ -1,75 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -Tag{-r3K,x-}{i} = - _/\_ a{-r3G-} -> \ tpl_B1 -> - Tag{-r3K,x-}{i} - {_@_ a{-r3G-} tpl_B1} -{- nonrec -} -f{-r3I,x-} = - _/\_ r{-r3C-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[r{-aHm-}] -[d.Reps_aHf] -[([r{-aHm-}], $mf{-rGx,x-}, f_aHh)] - AbsBinds [] [] [([], f_aHh, f_aHj)] - f_aHj - = GHCerr.noDefaultMethodError{-8k,p-} - (r{-aHm-} -> r{-aHm-} -> r{-aHm-}) "Class Reps Method f" -{- rec -} -AbsBinds [a{-aHn-}] [] [([a{-aHn-}], $d3{-rHq,x-}, d.Eval_aGM)] - d.Eval_aGM = - ({-dict-} [] []) -{- rec -} -AbsBinds [] [] [([], $d1{-rHr,x-}, d.Reps_aGR)] - AbsBinds [] [] [([], f_aHs, f_aGU)] - f_aGU - PrelBase.True{-5E,p-}{i} PrelBase.True{-5E,p-}{i} - = PrelBase.True{-5E,p-}{i} - f_aGU - x_r3o y_r3q - = PrelBase.False{-58,p-}{i} - d.Reps_aGR = - ({-dict-} [] [f_aHs]) -{- rec -} -AbsBinds [q{-aH9-}] [] [([q{-aH9-}], $d2{-rHt,x-}, d.Reps_aH3)] - AbsBinds [] [] [([], f_aHu, f_aH6)] - f_aH6 - x_r3x y_r3z - = y_r3z - d.Reps_aH3 = - ({-dict-} [] [f_aHu]) -{- nonrec -} -{- nonrec -} -AbsBinds [r{-aGB-}] [d.Reps_aGG] [([r{-aGB-}], g{-r3H,x-}, g_aGw)] - f_aHv = - f{-r3I,x-} - r{-aGB-} - d.Reps_aGG - g_aGw - x_r3h = f_aHv x_r3h x_r3h -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1; -_exports_ -ShouldSucceed g Reps(f) X(Tag); -_instances_ -instance {Reps PrelBase.Bool} = $d1; -instance _forall_ [a] => {Reps (X a)} = $d2; -instance _forall_ [a] => {PrelBase.Eval (X a)} = $d3; -_declarations_ -1 $d1 _:_ {Reps PrelBase.Bool} ;; -1 $d2 _:_ _forall_ [a] => {Reps (X a)} ;; -1 $d3 _:_ _forall_ [a] => {PrelBase.Eval (X a)} ;; -1 $mf _:_ _forall_ [a] {Reps a} => a -> a -> a ;; -1 class Reps r3C where {f :: r3C -> r3C -> r3C} ; -1 data X r3G = Tag r3G ; -1 g _:_ _forall_ [a] {Reps a} => a -> a ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc064.hs b/ghc/compiler/tests/typecheck/should_succeed/tc064.hs deleted file mode 100644 index 18aecb091d34d70bb005fbce97da9975e34a0a18..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc064.hs +++ /dev/null @@ -1,7 +0,0 @@ -module ShouldSucceed where - -data Boolean = FF | TT - -idb :: Boolean -> Boolean -idb x = x - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc064.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc064.stderr deleted file mode 100644 index 5b346e862491a75aa1144cf4dcaf629b746d21d3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc064.stderr +++ /dev/null @@ -1,35 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -FF{-r5,x-}{i} = - FF{-r5,x-}{i} - {} -TT{-r4,x-}{i} = - TT{-r4,x-}{i} - {} -{- rec -} -AbsBinds [] [] [([], $d1{-rG8,x-}, d.Eval_aG5)] - d.Eval_aG5 = - ({-dict-} [] []) -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], idb{-r6,x-}, idb_aFY)] - idb_aFY - x_r3k = x_r3k -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1; -_exports_ -ShouldSucceed idb Boolean(FF TT); -_instances_ -instance {PrelBase.Eval Boolean} = $d1; -_declarations_ -1 $d1 _:_ {PrelBase.Eval Boolean} ;; -1 data Boolean = FF | TT ; -1 idb _:_ Boolean -> Boolean ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc065.hs b/ghc/compiler/tests/typecheck/should_succeed/tc065.hs deleted file mode 100644 index 14de5930512f7da097750b40acc0e5f39951dc77..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc065.hs +++ /dev/null @@ -1,107 +0,0 @@ -module Digraphs where - -import TheUtils -import Set -import List (partition ) - -data Digraph vertex = MkDigraph [vertex] - -type Edge vertex = (vertex, vertex) -type Cycle vertex = [vertex] - -mkDigraph = MkDigraph - -stronglyConnComp :: Eq vertex => [Edge vertex] -> [vertex] -> [[vertex]] -stronglyConnComp es vs - = snd (span_tree (new_range reversed_edges) - ([],[]) - ( snd (dfs (new_range es) ([],[]) vs) ) - ) - where - reversed_edges = map swap es - - swap :: Edge v -> Edge v - swap (x,y) = (y, x) - - new_range [] w = [] - new_range ((x,y):xys) w - = if x==w - then (y : (new_range xys w)) - else (new_range xys w) - - span_tree r (vs,ns) [] = (vs,ns) - span_tree r (vs,ns) (x:xs) - | x `elem` vs = span_tree r (vs,ns) xs - | otherwise = span_tree r (vs',(x:ns'):ns) xs - where - (vs',ns') = dfs r (x:vs,[]) (r x) - -dfs r (vs,ns) [] = (vs,ns) -dfs r (vs,ns) (x:xs) | x `elem` vs = dfs r (vs,ns) xs - | otherwise = dfs r (vs',(x:ns')++ns) xs - where - (vs',ns') = dfs r (x:vs,[]) (r x) - - -isCyclic :: Eq vertex => [Edge vertex] -> [vertex] -> Bool -isCyclic edges [v] = (v,v) `elem` edges -isCyclic edges vs = True - - -topSort :: (Eq vertex) => [Edge vertex] -> [vertex] - -> MaybeErr [vertex] [[vertex]] - - -topSort edges vertices - = case cycles of - [] -> Succeeded [v | [v] <- singletons] - _ -> Failed cycles - where - sccs = stronglyConnComp edges vertices - (cycles, singletons) = partition (isCyclic edges) sccs - - -type FlattenedDependencyInfo vertex name code - = [(vertex, Set name, Set name, code)] - -mkVertices :: FlattenedDependencyInfo vertex name code -> [vertex] -mkVertices info = [ vertex | (vertex,_,_,_) <- info] - -mkEdges :: (Eq vertex, Ord name) => - [vertex] - -> FlattenedDependencyInfo vertex name code - -> [Edge vertex] - -mkEdges vertices flat_info - = [ (source_vertex, target_vertex) - | (source_vertex, _, used_names, _) <- flat_info, - target_name <- setToList used_names, - target_vertex <- vertices_defining target_name flat_info - ] - where - vertices_defining name flat_info - = [ vertex | (vertex, names_defined, _, _) <- flat_info, - name `elementOf` names_defined - ] - -lookupVertex :: (Eq vertex, Ord name) => - FlattenedDependencyInfo vertex name code - -> vertex - -> code - -lookupVertex flat_info vertex - = head code_list - where - code_list = [ code | (vertex',_,_,code) <- flat_info, vertex == vertex'] - - -isRecursiveCycle :: (Eq vertex) => Cycle vertex -> [Edge vertex] -> Bool -isRecursiveCycle [vertex] edges = (vertex, vertex) `elem` edges -isRecursiveCycle cycle edges = True - - - --- may go to TheUtils - -data MaybeErr a b = Succeeded a | Failed b - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc065.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc065.stderr deleted file mode 100644 index dbaac2dcc86b5bc394bf378c4d2f5c0f24c7e3d6..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc065.stderr +++ /dev/null @@ -1,486 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -Succeeded{-r4G,x-}{i} = - _/\_ a{-r8v-} b{-r8w-} -> \ tpl_B1 -> - Succeeded{-r4G,x-}{i} - {_@_ a{-r8v-} _@_ b{-r8w-} tpl_B1} -Failed{-r4F,x-}{i} = - _/\_ a{-r8v-} b{-r8w-} -> \ tpl_B1 -> - Failed{-r4F,x-}{i} - {_@_ a{-r8v-} _@_ b{-r8w-} tpl_B1} -{- nonrec -} -MkDigraph{-r8L,x-}{i} = - _/\_ vertex{-r8G-} -> \ tpl_B1 -> - MkDigraph{-r8L,x-}{i} - {_@_ vertex{-r8G-} tpl_B1} -{- nonrec -} -{- rec -} -AbsBinds -[a{-a1lz-}, b{-a1lA-}] -[] -[([a{-a1lz-}, b{-a1lA-}], $d1{-r1lE,x-}, d.Eval_a1kX)] - d.Eval_a1kX = - ({-dict-} [] []) -{- rec -} -AbsBinds -[vertex{-a1lB-}] -[] -[([vertex{-a1lB-}], $d2{-r1lS,x-}, d.Eval_a1l3)] - d.Eval_a1l3 = - ({-dict-} [] []) -{- nonrec -} -d.Monad_a1l5 = - PrelBase.$d24{-rj0,p-} ->>=_a1lQ = - PrelBase.>>={-811,p-} - PrelBase.[]{-3j,p-} - d.Monad_a1l5 -d.Monad_a1l8 = - d.Monad_a1l5 -return_a1lP = - PrelBase.return{-816,p-} - PrelBase.[]{-3j,p-} - d.Monad_a1l8 -d.MonadZero_a1la = - PrelBase.$d23{-riZ,p-} -zero_a1lO = - PrelBase.zero{-810,p-} - PrelBase.[]{-3j,p-} - d.MonadZero_a1la -d.Functor_a1ld = - PrelBase.$d25{-rj1,p-} -map_a1lN = - PrelBase.map{-rkx,p-} - PrelBase.[]{-3j,p-} - d.Functor_a1ld -d.MonadPlus_a1lg = - PrelBase.$d22{-riY,p-} -++_a1lM = - PrelBase.++{-rnk,p-} - PrelBase.[]{-3j,p-} - d.MonadPlus_a1lg ->>=_a1lL = - >>=_a1lQ -return_a1lK = - return_a1lP ->>=_a1lJ = - >>=_a1lQ -return_a1lI = - return_a1lP ->>=_a1lH = - >>=_a1lQ -return_a1lG = - return_a1lP -zero_a1lF = - zero_a1lO -{- nonrec -} -AbsBinds -[vertex{-a1ba-}] -[d.Eq_a1bl] -[([vertex{-a1ba-}], - isRecursiveCycle{-r6x,x-}, - isRecursiveCycle_a1b5)] - d.Eq_a1bp = - d.Eq_a1bl - d.Eq_a1bq = - d.Eq_a1bl - d.Eq_a1bn = - PrelTup.$d9{-rEY,p-} - [vertex{-a1ba-}, vertex{-a1ba-}] - [d.Eq_a1bp, d.Eq_a1bq] - elem_a1lT = - PrelList.elem{-rF6,p-} - (vertex{-a1ba-}, vertex{-a1ba-}) - d.Eq_a1bn - isRecursiveCycle_a1b5 - [vertex_r8n] edges_r8p - = (vertex_r8n, vertex_r8n) elem_a1lT edges_r8p - isRecursiveCycle_a1b5 - cycle_r8r edges_r8t - = PrelBase.True{-5E,p-}{i} -{- nonrec -} -{- nonrec -} -AbsBinds -[vertex{-a1bC-}, name{-a1bD-}, code{-a1bE-}] -[d.Eq_a1cs, d.Ord_a1ct] -[([name{-a1bD-}, vertex{-a1bC-}, code{-a1bE-}], - lookupVertex{-r6w,x-}, - lookupVertex_a1bz)] - d.Eq_a1cv = - d.Eq_a1cs - ==_a1lU = - PrelBase.=={-8Y,p-} - vertex{-a1bC-} - d.Eq_a1cv - lookupVertex_a1bz - flat_info_r8e vertex_r8g - = PrelList.head{-rFm,p-} - code{-a1bE-} code_list_r8i - where - {- nonrec -} - AbsBinds [] [] [([], code_list_r8i, code_list_a1bI)] - code_list_a1bI - = [ code_r8l | - (vertex'_r8k, _, _, code_r8l) <- flat_info_r8e, vertex_r8g - ==_a1lU vertex'_r8k - ] - {- nonrec -} -{- nonrec -} -{- nonrec -} -AbsBinds -[vertex{-a1cO-}, name{-a1cR-}, code{-a1cS-}] -[d.Eq_a1ei, d.Ord_a1ej] -[([name{-a1cR-}, code{-a1cS-}, vertex{-a1cO-}], - mkEdges{-r6v,x-}, - mkEdges_a1cL)] - d.Ord_a1ek = - d.Ord_a1ej - d.MonadZero_a1el = - PrelBase.$d23{-riZ,p-} - mkEdges_a1cL - vertices_r7U flat_info_r7W - = [ (source_vertex_r87, target_vertex_r8c) | - (source_vertex_r87, _, used_names_r88, _) <- flat_info_r7W, target_name_r8a <- Set.setToList{-rhd,p-} - name{-a1cR-} used_names_r88, target_vertex_r8c <- vertices_defining_a1lV target_name_r8a - flat_info_r7W - ] - where - {- nonrec -} - AbsBinds - [t{-a1d5-}, t{-a1da-}, t{-a1dd-}, a{-a1dg-}, a{-a1di-}] - [d.Ord_a1du, d.MonadZero_a1dA] - [([t{-a1d5-}, t{-a1da-}, t{-a1dd-}, a{-a1dg-}, a{-a1di-}], - vertices_defining_r7Y, - vertices_defining_a1cU)] - d.Monad_a1dw = - PrelBase.scsel_MonadZeroPrelBaseMonad{-a1m0,p-} - a{-a1dg-} - d.MonadZero_a1dA - elementOf_a1lZ = - Set.elementOf{-rh5,p-} - a{-a1di-} - d.Ord_a1du - >>=_a1lY = - PrelBase.>>={-811,p-} - a{-a1dg-} - d.Monad_a1dw - d.Monad_a1dy = - d.Monad_a1dw - return_a1lX = - PrelBase.return{-816,p-} - a{-a1dg-} - d.Monad_a1dy - zero_a1lW = - PrelBase.zero{-810,p-} - a{-a1dg-} - d.MonadZero_a1dA - vertices_defining_a1cU - name_r80 flat_info_r82 - = [ vertex_r84 | - (vertex_r84, names_defined_r85, _, _) <- flat_info_r82, name_r80 - elementOf_a1lZ names_defined_r85 - ] - {- nonrec -} - vertices_defining_a1lV = - vertices_defining_r7Y - [vertex{-a1cO-}, Set.Set{-rh2,p-} name{-a1cR-}, code{-a1cS-}, PrelBase.[]{-3j,p-}, name{-a1cR-}] - [d.Ord_a1ek, d.MonadZero_a1el] -{- nonrec -} -{- nonrec -} -AbsBinds -[vertex{-a1eC-}, name{-a1eD-}, code{-a1eE-}] -[] -[([name{-a1eD-}, code{-a1eE-}, vertex{-a1eC-}], - mkVertices{-r6u,x-}, - mkVertices_a1ez)] - mkVertices_a1ez - info_r7Q - = [ vertex_r7S | - (vertex_r7S, _, _, _) <- info_r7Q ] -{- nonrec -} -{- nonrec -} -AbsBinds -[vertex{-a1ff-}] -[d.Eq_a1fs] -[([vertex{-a1ff-}], isCyclic{-r6s,x-}, isCyclic_a1fc)] - d.Eq_a1fw = - d.Eq_a1fs - d.Eq_a1fx = - d.Eq_a1fs - d.Eq_a1fu = - PrelTup.$d9{-rEY,p-} - [vertex{-a1ff-}, vertex{-a1ff-}] - [d.Eq_a1fw, d.Eq_a1fx] - elem_a1m1 = - PrelList.elem{-rF6,p-} - (vertex{-a1ff-}, vertex{-a1ff-}) - d.Eq_a1fu - isCyclic_a1fc - edges_r7w [v_r7y] - = (v_r7y, v_r7y) elem_a1m1 edges_r7w - isCyclic_a1fc - edges_r7A vs_r7C - = PrelBase.True{-5E,p-}{i} -{- nonrec -} -{- rec -} -AbsBinds -[t{-a1gi-}] -[d.Eq_a1gA] -[([t{-a1gi-}], dfs{-r6y,x-}, dfs_a1fz)] - elem_a1m2 = - PrelList.elem{-rF6,p-} - t{-a1gi-} - d.Eq_a1gA - dfs_a1fz - r_r7f (vs_r7h, ns_r7i) PrelBase.[]{-5i,p-}{i} - = (vs_r7h, ns_r7i) - dfs_a1fz - r_r7l (vs_r7n, ns_r7o) (x_r7q PrelBase.:{-55,p-}{i} xs_r7r) - | [x_r7q elem_a1m2 vs_r7n] = - dfs_a1fz r_r7l (vs_r7n, ns_r7o) xs_r7r - | [PrelBase.otherwise{-818,p-}] = - dfs_a1fz r_r7l - (vs'_r7t, - ++_a1lM - t{-a1gi-} - (PrelBase.:{-55,p-}{i} - t{-a1gi-} - x_r7q ns'_r7u) - ns_r7o) - xs_r7r - where - {- nonrec -} - AbsBinds [] [] [([], vs'_r7t, vs'_a1g4), ([], ns'_r7u, ns'_a1g5)] - (vs'_a1g4, ns'_a1g5) - = dfs_a1fz r_r7l - (PrelBase.:{-55,p-}{i} - t{-a1gi-} - x_r7q vs_r7n, - PrelBase.[]{-5i,p-}{i} - t{-a1gi-}) - r_r7l x_r7q - {- nonrec -} -{- nonrec -} -{- nonrec -} -AbsBinds -[vertex{-a1gK-}] -[d.Eq_a1ju] -[([vertex{-a1gK-}], - stronglyConnComp{-r6r,x-}, - stronglyConnComp_a1gH)] - d.Eq_a1jv = - d.Eq_a1ju - d.Eq_a1jq = - d.Eq_a1ju - d.Eq_a1jx = - d.Eq_a1ju - dfs_a1m3 = - dfs{-r6y,x-} - vertex{-a1gK-} - d.Eq_a1jx - d.Eq_a1jr = - d.Eq_a1ju - stronglyConnComp_a1gH - es_r6B vs_r6D - = PrelTup.snd{-rF4,p-} - [[vertex{-a1gK-}], [[vertex{-a1gK-}]]] span_tree_a1m4 new_range_a1m6 reversed_edges_r6F - (PrelBase.[]{-5i,p-}{i} - vertex{-a1gK-}, - PrelBase.[]{-5i,p-}{i} - [vertex{-a1gK-}]) - PrelTup.snd{-rF4,p-} - [[vertex{-a1gK-}], [vertex{-a1gK-}]] dfs_a1m3 new_range_a1m5 es_r6B - (PrelBase.[]{-5i,p-}{i} - vertex{-a1gK-}, - PrelBase.[]{-5i,p-}{i} - vertex{-a1gK-}) - vs_r6D - where - {- rec -} - AbsBinds - [t{-a1h2-}] - [d.Eq_a1hJ] - [([t{-a1h2-}], span_tree_r6I, span_tree_a1gO)] - elem_a1m8 = - PrelList.elem{-rF6,p-} - t{-a1h2-} - d.Eq_a1hJ - d.Eq_a1hL = - d.Eq_a1hJ - dfs_a1m7 = - dfs{-r6y,x-} - t{-a1h2-} - d.Eq_a1hL - span_tree_a1gO - r_r6Y (vs_r70, ns_r71) PrelBase.[]{-5i,p-}{i} - = (vs_r70, ns_r71) - span_tree_a1gO - r_r74 (vs_r76, ns_r77) (x_r79 PrelBase.:{-55,p-}{i} xs_r7a) - | [x_r79 elem_a1m8 vs_r76] = - span_tree_a1gO r_r74 (vs_r76, ns_r77) xs_r7a - | [PrelBase.otherwise{-818,p-}] = - span_tree_a1gO r_r74 - (vs'_r7c, - PrelBase.:{-55,p-}{i} - [t{-a1h2-}] - (PrelBase.:{-55,p-}{i} - t{-a1h2-} - x_r79 ns'_r7d) - ns_r77) - xs_r7a - where - {- nonrec -} - AbsBinds - [] - [] - [([], vs'_r7c, vs'_a1hj), ([], ns'_r7d, ns'_a1hk)] - (vs'_a1hj, ns'_a1hk) - = dfs_a1m7 r_r74 - (PrelBase.:{-55,p-}{i} - t{-a1h2-} - x_r79 vs_r76, - PrelBase.[]{-5i,p-}{i} - t{-a1h2-}) - r_r74 x_r79 - {- nonrec -} - {- nonrec -} - span_tree_a1m4 = - span_tree_r6I - vertex{-a1gK-} - d.Eq_a1jv - {- rec -} - AbsBinds - [t{-a1hV-}, t{-a1i0-}] - [d.Eq_a1ig] - [([t{-a1hV-}, t{-a1i0-}], new_range_r6H, new_range_a1hN)] - ==_a1m9 = - PrelBase.=={-8Y,p-} - t{-a1i0-} - d.Eq_a1ig - new_range_a1hN - PrelBase.[]{-5i,p-}{i} w_r6Q - = PrelBase.[]{-5i,p-}{i} - t{-a1hV-} - new_range_a1hN - ((x_r6S, y_r6T) PrelBase.:{-55,p-}{i} xys_r6U) w_r6W - = if x_r6S ==_a1m9 w_r6W then - PrelBase.:{-55,p-}{i} - t{-a1hV-} - y_r6T (new_range_a1hN xys_r6U w_r6W) - else - new_range_a1hN xys_r6U w_r6W - {- nonrec -} - new_range_a1m6 = - new_range_r6H - [vertex{-a1gK-}, vertex{-a1gK-}] - d.Eq_a1jq - new_range_a1m5 = - new_range_r6H - [vertex{-a1gK-}, vertex{-a1gK-}] - d.Eq_a1jr - {- nonrec -} - AbsBinds [v{-a1iv-}] [] [([v{-a1iv-}], swap_r6G, swap_a1im)] - swap_a1im - (x_r6M, y_r6N) - = (y_r6N, x_r6M) - {- nonrec -} - {- nonrec -} - AbsBinds [] [] [([], reversed_edges_r6F, reversed_edges_a1iy)] - reversed_edges_a1iy - = map_a1lN - [Edge{-r8K,x-} vertex{-a1gK-}, Edge{-r8K,x-} vertex{-a1gK-}] swap_r6G - vertex{-a1gK-} - es_r6B - {- nonrec -} -{- nonrec -} -{- nonrec -} -AbsBinds -[vertex{-a1jI-}] -[d.Eq_a1kA] -[([vertex{-a1jI-}], topSort{-r6t,x-}, topSort_a1jF)] - d.Eq_a1kI = - d.Eq_a1kA - isCyclic_a1mb = - isCyclic{-r6s,x-} - vertex{-a1jI-} - d.Eq_a1kI - d.Eq_a1kK = - d.Eq_a1kA - stronglyConnComp_a1ma = - stronglyConnComp{-r6r,x-} - vertex{-a1jI-} - d.Eq_a1kK - topSort_a1jF - edges_r7E vertices_r7G - = case cycles_r7J of - PrelBase.[]{-5i,p-}{i} - -> Succeeded{-r4G,x-}{i} - [[vertex{-a1jI-}], [[vertex{-a1jI-}]]] [ v_r7N | - [v_r7N] <- singletons_r7K - ] - _ -> Failed{-r4F,x-}{i} - [[vertex{-a1jI-}], [[vertex{-a1jI-}]]] cycles_r7J - where - {- nonrec -} - AbsBinds [] [] [([], sccs_r7I, sccs_a1jM)] - sccs_a1jM - = stronglyConnComp_a1ma edges_r7E vertices_r7G - {- nonrec -} - {- nonrec -} - AbsBinds - [] - [] - [([], cycles_r7J, cycles_a1jT), ([], - singletons_r7K, - singletons_a1jU)] - (cycles_a1jT, singletons_a1jU) - = List.partition{-rhM,p-} - [vertex{-a1jI-}] isCyclic_a1mb edges_r7E sccs_r7I - {- nonrec -} -{- nonrec -} -{- nonrec -} -AbsBinds -[vertex{-a1kQ-}] -[] -[([vertex{-a1kQ-}], mkDigraph{-r6z,x-}, mkDigraph_a1kM)] - mkDigraph_a1kM - = MkDigraph{-r8L,x-}{i} - vertex{-a1kQ-} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ Digraphs 1 -_instance_modules_ -ArrBase Foreign IO PrelNum -_usages_ -List 1 :: partition 1; -PrelBase 1 :: $d14 1 $d15 1 $d22 1 $d23 1 $d24 1 $d25 1 $d26 1 $d27 1 $d32 1 $d34 1 $d37 1 $d39 1 $d41 1 $d44 1 $d45 1 $d46 1 $d49 1 $d51 1 $d6 1 $d7 1 otherwise 1 Eq 1 Eval 1 Functor 1 Monad 1 MonadPlus 1 MonadZero 1 Ord 1 Ordering 1; -PrelList 1 :: elem 1 head 1; -PrelNum 1 :: $d17 1 $d18 1; -PrelTup 1 :: $d11 1 $d13 1 $d15 1 $d49 1 $d51 1 $d9 1 snd 1; -Set 2 :: $d1 2 elementOf 2 setToList 2 Set 1; -_exports_ -Digraphs dfs isCyclic isRecursiveCycle lookupVertex mkDigraph mkEdges mkVertices stronglyConnComp topSort Cycle Digraph(MkDigraph) Edge FlattenedDependencyInfo MaybeErr(Succeeded Failed); -_instances_ -instance _forall_ [a b] => {PrelBase.Eval (MaybeErr a b)} = $d1; -instance _forall_ [a] => {PrelBase.Eval (Digraph a)} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a b] => {PrelBase.Eval (MaybeErr a b)} ;; -1 $d2 _:_ _forall_ [a] => {PrelBase.Eval (Digraph a)} ;; -1 type Cycle r8C = [r8C] ; -1 data Digraph r8G = MkDigraph [r8G] ; -1 type Edge r8E = (r8E, r8E) ; -1 type FlattenedDependencyInfo r8y r8z r8A = [(r8y, Set.Set r8z, Set.Set r8z, r8A)] ; -1 data MaybeErr r8v r8w = Succeeded r8v | Failed r8w ; -1 dfs _:_ _forall_ [a] {PrelBase.Eq a} => (a -> [a]) -> ([a], [a]) -> [a] -> ([a], [a]) ;; -1 isCyclic _:_ _forall_ [a] {PrelBase.Eq a} => [Edge a] -> [a] -> PrelBase.Bool ;; -1 isRecursiveCycle _:_ _forall_ [a] {PrelBase.Eq a} => Cycle a -> [Edge a] -> PrelBase.Bool ;; -1 lookupVertex _:_ _forall_ [a b c] {PrelBase.Eq b, PrelBase.Ord a} => FlattenedDependencyInfo b a c -> b -> c ;; -1 mkDigraph _:_ _forall_ [a] => [a] -> Digraph a ;; -1 mkEdges _:_ _forall_ [a b c] {PrelBase.Eq c, PrelBase.Ord a} => [c] -> FlattenedDependencyInfo c a b -> [Edge c] ;; -1 mkVertices _:_ _forall_ [a b c] => FlattenedDependencyInfo c a b -> [c] ;; -1 stronglyConnComp _:_ _forall_ [a] {PrelBase.Eq a} => [Edge a] -> [a] -> [[a]] ;; -1 topSort _:_ _forall_ [a] {PrelBase.Eq a} => [Edge a] -> [a] -> MaybeErr [a] [[a]] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc066.hs b/ghc/compiler/tests/typecheck/should_succeed/tc066.hs deleted file mode 100644 index 7c929516bc0011aeee15892211652035969c285e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc066.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -data Pair a b = MkPair a b -f x = [ a | (MkPair c a) <- x ] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc066.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc066.stderr deleted file mode 100644 index c9ad8870f2298428f42da6c0a58496936a808f6c..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc066.stderr +++ /dev/null @@ -1,50 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -MkPair{-r3n,x-}{i} = - _/\_ a{-r3k-} b{-r3l-} -> \ tpl_B1 tpl_B2 -> - MkPair{-r3n,x-}{i} - {_@_ a{-r3k-} _@_ b{-r3l-} tpl_B1 tpl_B2} -{- rec -} -AbsBinds -[a{-aHg-}, b{-aHh-}] -[] -[([a{-aHg-}, b{-aHh-}], $d1{-rHk,x-}, d.Eval_aHc)] - d.Eval_aHc = - ({-dict-} [] []) -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aGO-}, t{-aGR-}, a{-aGT-}] -[d.Monad_aH3] -[([t{-aGO-}, t{-aGR-}, a{-aGT-}], f{-r3m,x-}, f_aGG)] - >>=_aHm = - PrelBase.>>={-811,p-} - a{-aGT-} - d.Monad_aH3 - d.Monad_aH5 = - d.Monad_aH3 - return_aHl = - PrelBase.return{-816,p-} - a{-aGT-} - d.Monad_aH5 - f_aGG - x_r3f = [ a_r3i | - (MkPair{-r3n,x-}{i} c_r3h a_r3i) <- x_r3f ] -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1 Monad 1 MonadZero 1; -_exports_ -ShouldSucceed f Pair(MkPair); -_instances_ -instance _forall_ [a b] => {PrelBase.Eval (Pair a b)} = $d1; -_declarations_ -1 $d1 _:_ _forall_ [a b] => {PrelBase.Eval (Pair a b)} ;; -1 data Pair r3k r3l = MkPair r3k r3l ; -1 f _:_ _forall_ [a b c :: (* -> *)] {PrelBase.Monad c} => c (Pair a b) -> c b ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc067.hs b/ghc/compiler/tests/typecheck/should_succeed/tc067.hs deleted file mode 100644 index 59df10316cdcde55743013e7216ef9630ce30c09..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc067.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucc where - -f [] = [] -f (x:xs) = x : (f xs) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc067.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc067.stderr deleted file mode 100644 index 7302e4618fb01fb76fd4e47ab5467ebd692543e0..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc067.stderr +++ /dev/null @@ -1,25 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- rec -} -AbsBinds [t{-ana-}] [] [([t{-ana-}], f{-r3g,x-}, f_an4)] - f_an4 - PrelBase.[]{-5i,p-}{i} - = PrelBase.[]{-5i,p-}{i} - t{-ana-} - f_an4 - (x_r3e PrelBase.:{-55,p-}{i} xs_r3f) - = PrelBase.:{-55,p-}{i} - t{-ana-} - x_r3e (f_an4 xs_r3f) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucc 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucc f; -_declarations_ -1 f _:_ _forall_ [a] => [a] -> [a] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc068.hs b/ghc/compiler/tests/typecheck/should_succeed/tc068.hs deleted file mode 100644 index 01f2d872e6ccd2a092d4a96af82d857d72da8b02..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc068.hs +++ /dev/null @@ -1,18 +0,0 @@ -module ShouldSucc where - -data T a = D (B a) | C -data B b = X | Y b - -instance (Eq a) => Eq (T a) where - (D x) == (D y) = x == y - C == C = True - a == b = False - - a /= b = not (a == b) - -instance (Eq b) => Eq (B b) where - X == X = True - (Y a) == (Y b) = a == b - a == b = False - - a /= b = not (a == b) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc068.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc068.stderr deleted file mode 100644 index f9784b4e9e214083705c4665b707afa7ccb53186..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc068.stderr +++ /dev/null @@ -1,114 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -X{-r4,x-}{i} = - _/\_ b{-r42-} -> - X{-r4,x-}{i} - {_@_ b{-r42-}} -Y{-r3,x-}{i} = - _/\_ b{-r42-} -> \ tpl_B1 -> - Y{-r3,x-}{i} - {_@_ b{-r42-} tpl_B1} -{- nonrec -} -D{-r9,x-}{i} = - _/\_ a{-r44-} -> \ tpl_B1 -> - D{-r9,x-}{i} - {_@_ a{-r44-} tpl_B1} -C{-r8,x-}{i} = - _/\_ a{-r44-} -> - C{-r8,x-}{i} - {_@_ a{-r44-}} -{- rec -} -AbsBinds [b{-aIF-}] [] [([b{-aIF-}], $d3{-rIJ,x-}, d.Eval_aH4)] - d.Eval_aH4 = - ({-dict-} [] []) -{- rec -} -AbsBinds [a{-aIG-}] [] [([a{-aIG-}], $d4{-rIL,x-}, d.Eval_aHa)] - d.Eval_aHa = - ({-dict-} [] []) -{- rec -} -AbsBinds -[b{-aHm-}] -[d.Eq_aHO] -[([b{-aHm-}], $d1{-rIM,x-}, d.Eq_aHg)] - d.Eq_aHS = - d.Eq_aHO - ==_aIQ = - PrelBase.=={-8Y,p-} - b{-aHm-} - d.Eq_aHS - ==_aIP = - ==_aIO - AbsBinds [] [] [([], ==_aIO, ==_aHj)] - ==_aHj - X{-r4,x-}{i} X{-r4,x-}{i} - = PrelBase.True{-5E,p-}{i} - ==_aHj - (Y{-r3,x-}{i} a_r3s) (Y{-r3,x-}{i} b_r3u) - = a_r3s ==_aIQ b_r3u - ==_aHj - a_r3w b_r3y - = PrelBase.False{-58,p-}{i} - AbsBinds [] [] [([], /=_aIN, /=_aHH)] - /=_aHH - a_r3C b_r3E - = PrelBase.not{-rfZ,p-} a_r3C ==_aIP b_r3E - d.Eq_aHg = - ({-dict-} [] [==_aIO, /=_aIN]) -{- rec -} -AbsBinds -[a{-aI7-}] -[d.Eq_aIx] -[([a{-aI7-}], $d2{-rIR,x-}, d.Eq_aHZ)] - d.Eq_aID = - d.Eq_aIx - d.Eq_aIB = - $d1{-rIM,x-} - a{-aI7-} - d.Eq_aID - ==_aIV = - PrelBase.=={-8Y,p-} - (B{-r45,x-} a{-aI7-}) - d.Eq_aIB - ==_aIU = - ==_aIT - AbsBinds [] [] [([], ==_aIT, ==_aI2)] - ==_aI2 - (D{-r9,x-}{i} x_r3L) (D{-r9,x-}{i} y_r3N) - = x_r3L ==_aIV y_r3N - ==_aI2 - C{-r8,x-}{i} C{-r8,x-}{i} - = PrelBase.True{-5E,p-}{i} - ==_aI2 - a_r3R b_r3T - = PrelBase.False{-58,p-}{i} - AbsBinds [] [] [([], /=_aIS, /=_aIq)] - /=_aIq - a_r3X b_r3Z - = PrelBase.not{-rfZ,p-} a_r3X ==_aIU b_r3Z - d.Eq_aHZ = - ({-dict-} [] [==_aIT, /=_aIS]) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucc 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d15 1 $d32 1 $d37 1 $d39 1 $d41 1 $d46 1 $d7 1 not 1 Eq 1 Eval 1; -PrelNum 1 :: $d18 1; -_exports_ -ShouldSucc B(X Y) T(D C); -_instances_ -instance _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (B a)} = $d1; -instance _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} = $d2; -instance _forall_ [a] => {PrelBase.Eval (B a)} = $d3; -instance _forall_ [a] => {PrelBase.Eval (T a)} = $d4; -_declarations_ -1 $d1 _:_ _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (B a)} ;; -1 $d2 _:_ _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} ;; -1 $d3 _:_ _forall_ [a] => {PrelBase.Eval (B a)} ;; -1 $d4 _:_ _forall_ [a] => {PrelBase.Eval (T a)} ;; -1 data B r42 = X | Y r42 ; -1 data T r44 = D (B r44) | C ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc069.hs b/ghc/compiler/tests/typecheck/should_succeed/tc069.hs deleted file mode 100644 index 539b3046da70e5a483ca1cc7a0bc157ef7edd81d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc069.hs +++ /dev/null @@ -1,4 +0,0 @@ -module ShouldSucceed where - -x = 'a' -(y:ys) = ['a','b','c'] where p = x diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc069.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc069.stderr deleted file mode 100644 index 65df942f12c0b1f59c49624abe71f74b5b04f9d3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc069.stderr +++ /dev/null @@ -1,31 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], x{-r3i,x-}, x_an6)] - x_an6 - = 'a' -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], y{-r3h,x-}, y_ana), ([], ys{-r3g,x-}, ys_anb)] - (y_ana PrelBase.:{-55,p-}{i} ys_anb) - = ['a', 'b', 'c'] (PrelBase.Char{-38,p-}) - where - {- nonrec -} - AbsBinds [] [] [([], p_r3f, p_anj)] - p_anj - = x{-r3i,x-} - {- nonrec -} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucceed x y ys; -_declarations_ -1 x _:_ PrelBase.Char ;; -1 y _:_ PrelBase.Char ;; -1 ys _:_ [PrelBase.Char] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc070.hs b/ghc/compiler/tests/typecheck/should_succeed/tc070.hs deleted file mode 100644 index 831195f9f6269fb3634cab100d0880d1fa68cf20..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc070.hs +++ /dev/null @@ -1,9 +0,0 @@ -module ShouldSucceed where - - -data Boolean = FF | TT - - -idb :: Boolean -> Boolean -idb x = x - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc070.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc070.stderr deleted file mode 100644 index 5b346e862491a75aa1144cf4dcaf629b746d21d3..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc070.stderr +++ /dev/null @@ -1,35 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -FF{-r5,x-}{i} = - FF{-r5,x-}{i} - {} -TT{-r4,x-}{i} = - TT{-r4,x-}{i} - {} -{- rec -} -AbsBinds [] [] [([], $d1{-rG8,x-}, d.Eval_aG5)] - d.Eval_aG5 = - ({-dict-} [] []) -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], idb{-r6,x-}, idb_aFY)] - idb_aFY - x_r3k = x_r3k -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1; -_exports_ -ShouldSucceed idb Boolean(FF TT); -_instances_ -instance {PrelBase.Eval Boolean} = $d1; -_declarations_ -1 $d1 _:_ {PrelBase.Eval Boolean} ;; -1 data Boolean = FF | TT ; -1 idb _:_ Boolean -> Boolean ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc073.hs b/ghc/compiler/tests/typecheck/should_succeed/tc073.hs deleted file mode 100644 index ea4cb74675cd37584df9192188e4dd1be8439f2a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc073.hs +++ /dev/null @@ -1,5 +0,0 @@ - -module ShouldSucc where - -f [] = [] -f (x:xs) = x : (f xs) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc073.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc073.stderr deleted file mode 100644 index 7302e4618fb01fb76fd4e47ab5467ebd692543e0..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc073.stderr +++ /dev/null @@ -1,25 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- rec -} -AbsBinds [t{-ana-}] [] [([t{-ana-}], f{-r3g,x-}, f_an4)] - f_an4 - PrelBase.[]{-5i,p-}{i} - = PrelBase.[]{-5i,p-}{i} - t{-ana-} - f_an4 - (x_r3e PrelBase.:{-55,p-}{i} xs_r3f) - = PrelBase.:{-55,p-}{i} - t{-ana-} - x_r3e (f_an4 xs_r3f) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucc 1 -_instance_modules_ -ArrBase IO PrelNum -_exports_ -ShouldSucc f; -_declarations_ -1 f _:_ _forall_ [a] => [a] -> [a] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc074.hs b/ghc/compiler/tests/typecheck/should_succeed/tc074.hs deleted file mode 100644 index 01f2d872e6ccd2a092d4a96af82d857d72da8b02..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc074.hs +++ /dev/null @@ -1,18 +0,0 @@ -module ShouldSucc where - -data T a = D (B a) | C -data B b = X | Y b - -instance (Eq a) => Eq (T a) where - (D x) == (D y) = x == y - C == C = True - a == b = False - - a /= b = not (a == b) - -instance (Eq b) => Eq (B b) where - X == X = True - (Y a) == (Y b) = a == b - a == b = False - - a /= b = not (a == b) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc074.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc074.stderr deleted file mode 100644 index f9784b4e9e214083705c4665b707afa7ccb53186..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc074.stderr +++ /dev/null @@ -1,114 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -X{-r4,x-}{i} = - _/\_ b{-r42-} -> - X{-r4,x-}{i} - {_@_ b{-r42-}} -Y{-r3,x-}{i} = - _/\_ b{-r42-} -> \ tpl_B1 -> - Y{-r3,x-}{i} - {_@_ b{-r42-} tpl_B1} -{- nonrec -} -D{-r9,x-}{i} = - _/\_ a{-r44-} -> \ tpl_B1 -> - D{-r9,x-}{i} - {_@_ a{-r44-} tpl_B1} -C{-r8,x-}{i} = - _/\_ a{-r44-} -> - C{-r8,x-}{i} - {_@_ a{-r44-}} -{- rec -} -AbsBinds [b{-aIF-}] [] [([b{-aIF-}], $d3{-rIJ,x-}, d.Eval_aH4)] - d.Eval_aH4 = - ({-dict-} [] []) -{- rec -} -AbsBinds [a{-aIG-}] [] [([a{-aIG-}], $d4{-rIL,x-}, d.Eval_aHa)] - d.Eval_aHa = - ({-dict-} [] []) -{- rec -} -AbsBinds -[b{-aHm-}] -[d.Eq_aHO] -[([b{-aHm-}], $d1{-rIM,x-}, d.Eq_aHg)] - d.Eq_aHS = - d.Eq_aHO - ==_aIQ = - PrelBase.=={-8Y,p-} - b{-aHm-} - d.Eq_aHS - ==_aIP = - ==_aIO - AbsBinds [] [] [([], ==_aIO, ==_aHj)] - ==_aHj - X{-r4,x-}{i} X{-r4,x-}{i} - = PrelBase.True{-5E,p-}{i} - ==_aHj - (Y{-r3,x-}{i} a_r3s) (Y{-r3,x-}{i} b_r3u) - = a_r3s ==_aIQ b_r3u - ==_aHj - a_r3w b_r3y - = PrelBase.False{-58,p-}{i} - AbsBinds [] [] [([], /=_aIN, /=_aHH)] - /=_aHH - a_r3C b_r3E - = PrelBase.not{-rfZ,p-} a_r3C ==_aIP b_r3E - d.Eq_aHg = - ({-dict-} [] [==_aIO, /=_aIN]) -{- rec -} -AbsBinds -[a{-aI7-}] -[d.Eq_aIx] -[([a{-aI7-}], $d2{-rIR,x-}, d.Eq_aHZ)] - d.Eq_aID = - d.Eq_aIx - d.Eq_aIB = - $d1{-rIM,x-} - a{-aI7-} - d.Eq_aID - ==_aIV = - PrelBase.=={-8Y,p-} - (B{-r45,x-} a{-aI7-}) - d.Eq_aIB - ==_aIU = - ==_aIT - AbsBinds [] [] [([], ==_aIT, ==_aI2)] - ==_aI2 - (D{-r9,x-}{i} x_r3L) (D{-r9,x-}{i} y_r3N) - = x_r3L ==_aIV y_r3N - ==_aI2 - C{-r8,x-}{i} C{-r8,x-}{i} - = PrelBase.True{-5E,p-}{i} - ==_aI2 - a_r3R b_r3T - = PrelBase.False{-58,p-}{i} - AbsBinds [] [] [([], /=_aIS, /=_aIq)] - /=_aIq - a_r3X b_r3Z - = PrelBase.not{-rfZ,p-} a_r3X ==_aIU b_r3Z - d.Eq_aHZ = - ({-dict-} [] [==_aIT, /=_aIS]) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucc 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d15 1 $d32 1 $d37 1 $d39 1 $d41 1 $d46 1 $d7 1 not 1 Eq 1 Eval 1; -PrelNum 1 :: $d18 1; -_exports_ -ShouldSucc B(X Y) T(D C); -_instances_ -instance _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (B a)} = $d1; -instance _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} = $d2; -instance _forall_ [a] => {PrelBase.Eval (B a)} = $d3; -instance _forall_ [a] => {PrelBase.Eval (T a)} = $d4; -_declarations_ -1 $d1 _:_ _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (B a)} ;; -1 $d2 _:_ _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} ;; -1 $d3 _:_ _forall_ [a] => {PrelBase.Eval (B a)} ;; -1 $d4 _:_ _forall_ [a] => {PrelBase.Eval (T a)} ;; -1 data B r42 = X | Y r42 ; -1 data T r44 = D (B r44) | C ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc075.hs b/ghc/compiler/tests/typecheck/should_succeed/tc075.hs deleted file mode 100644 index f7c31d8926c76a785645588c04fac1a4ddd3d51e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc075.hs +++ /dev/null @@ -1,8 +0,0 @@ -module ShouldSucceed where - ---!!! giving methods in a pattern binding (for no v good reason...) - -data Foo = MkFoo Int - -instance Eq Foo where - ((==), (/=)) = (\x -> \y -> True, \x -> \y -> False) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc075.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc075.stderr deleted file mode 100644 index 134637b8d4c323a79fa41ffbc2ebf7b64ae9b088..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc075.stderr +++ /dev/null @@ -1,9 +0,0 @@ - -tc075.hs:8: - Can't handle multiple methods defined by one pattern binding - `(==, /=) - = (\ x -> \ y -> True, - (\ x -> \ y -> False))' - - -Compilation had errors diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc076.hs b/ghc/compiler/tests/typecheck/should_succeed/tc076.hs deleted file mode 100644 index 5bf422e5c937444afe0c6ffa7157359b1f938e26..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc076.hs +++ /dev/null @@ -1,8 +0,0 @@ ---!!! scoping in list comprehensions right way 'round? --- a bug reported by Jon Hill --- -module ShouldSucceed where - -x = [[True]] -xs :: [Bool] -xs = [x | x <- x, x <- x] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc076.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc076.stderr deleted file mode 100644 index 97720b4cb21a2798e44dabb86c9d47272376354a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc076.stderr +++ /dev/null @@ -1,39 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Monad_aGO = - PrelBase.$d24{-rb1,p-} ->>=_aGV = - PrelBase.>>={-811,p-} - PrelBase.[]{-3j,p-} - d.Monad_aGO -d.Monad_aGR = - d.Monad_aGO -return_aGW = - PrelBase.return{-816,p-} - PrelBase.[]{-3j,p-} - d.Monad_aGR -{- nonrec -} -AbsBinds [] [] [([], x{-r3,x-}, x_aGp)] - x_aGp - = [[PrelBase.True{-5E,p-}{i}] (PrelBase.Bool{-34,p-})] ([PrelBase.Bool{-34,p-}]) -{- nonrec -} -{- nonrec -} -AbsBinds [] [] [([], xs{-r2,x-}, xs_aGx)] - xs_aGx - = [ x_r3j | - x_r3h <- x{-r3,x-}, x_r3j <- x_r3h ] -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d23 1 $d24 1 Monad 1 MonadZero 1; -_exports_ -ShouldSucceed x xs; -_declarations_ -1 x _:_ [[PrelBase.Bool]] ;; -1 xs _:_ [PrelBase.Bool] ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc077.hs b/ghc/compiler/tests/typecheck/should_succeed/tc077.hs deleted file mode 100644 index c9bb8d53a8864d5f4e75d1eec08fc999d3110f8d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc077.hs +++ /dev/null @@ -1,9 +0,0 @@ ---!!! make sure context of EQ is minimised in interface file. --- -module M where - -data NUM = ONE | TWO -class (Num a) => ORD a - -class (ORD a, Show a) => EQ a where - (===) :: a -> a -> Bool diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc077.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc077.stderr deleted file mode 100644 index 9894b8d9506e545a1c59e42c1741437b7173b2ec..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc077.stderr +++ /dev/null @@ -1,62 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -ONE{-r7,x-}{i} = - ONE{-r7,x-}{i} - {} -TWO{-r6,x-}{i} = - TWO{-r6,x-}{i} - {} -{- nonrec -} -scsel_EQMORD{-aHj,x-} = - _/\_ a{-r3k-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,,){-63,p-}{i} tpl_B1 tpl_B2 tpl_B3 -> - tpl_B1;} -scsel_EQPrelBaseShow{-aHk,x-} = - _/\_ a{-r3k-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,,){-63,p-}{i} tpl_B1 tpl_B2 tpl_B3 -> - tpl_B2;} -==={-r3q,x-} = - _/\_ a{-r3k-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,,){-63,p-}{i} tpl_B1 tpl_B2 tpl_B3 -> - tpl_B3;} -{- nonrec -} -AbsBinds -[a{-aHi-}] -[d.EQ_aHb] -[([a{-aHi-}], $m==={-rHl,x-}, ===_aHd)] - AbsBinds [] [] [([], ===_aHd, ===_aHf)] - ===_aHf - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-aHi-} - -> a{-aHi-} - -> PrelBase.Bool{-34,p-}) "Class EQ Method ===" -{- nonrec -} -scsel_ORDPrelBaseNum{-aHm,x-} = - _/\_ a{-r3p-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -{- rec -} -AbsBinds [] [] [([], $d1{-rHp,x-}, d.Eval_aH8)] - d.Eval_aH8 = - ({-dict-} [] []) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ M 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -M EQ(===) NUM(ONE TWO) ORD; -_instances_ -instance {PrelBase.Eval NUM} = $d1; -_declarations_ -1 class {PrelBase.Num r3p} => ORD r3p ; -1 $d1 _:_ {PrelBase.Eval NUM} ;; -1 $m=== _:_ _forall_ [a] {EQ a} => a -> a -> PrelBase.Bool ;; -1 class {ORD r3k, PrelBase.Show r3k} => EQ r3k where {=== :: r3k -> r3k -> PrelBase.Bool} ; -1 data NUM = ONE | TWO ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc078.hs b/ghc/compiler/tests/typecheck/should_succeed/tc078.hs deleted file mode 100644 index a35afef81e050964d10eeeaec05e7a8f67cdf50a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc078.hs +++ /dev/null @@ -1,8 +0,0 @@ ---!!! instance decls with no binds --- -module M where - -data Bar a = MkBar Int a - -instance Eq a => Eq (Bar a) -instance Ord a => Ord (Bar a) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc078.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc078.stderr deleted file mode 100644 index 1baa76ef3d0f8add24a50e8e55e274634e90cb1d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc078.stderr +++ /dev/null @@ -1,132 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -MkBar{-r3l,x-}{i} = - _/\_ a{-r3k-} -> \ tpl_B1 tpl_B2 -> - MkBar{-r3l,x-}{i} - {_@_ a{-r3k-} tpl_B1 tpl_B2} -{- rec -} -AbsBinds [a{-aId-}] [] [([a{-aId-}], $d3{-rIh,x-}, d.Eval_aGn)] - d.Eval_aGn = - ({-dict-} [] []) -{- rec -} -AbsBinds -[a{-aGA-}] -[d.Ord_aHn, d.Eq_aHo] -[([a{-aGA-}], $d1{-rIi,x-}, d.Ord_aGt)] - d.Eq_aHp = - d.Eq_aHo - d.Ord_aHt = - d.Ord_aGt - $mcompare_aIp = - PrelBase.$mcompare{-rbW,p-} - (Bar{-r3m,x-} a{-aGA-}) - d.Ord_aHt - d.Ord_aHv = - d.Ord_aGt - $m<_aIo = - PrelBase.$m<{-rbO,p-} - (Bar{-r3m,x-} a{-aGA-}) - d.Ord_aHv - d.Ord_aHx = - d.Ord_aGt - $m<=_aIn = - PrelBase.$m<={-rbP,p-} - (Bar{-r3m,x-} a{-aGA-}) - d.Ord_aHx - d.Ord_aHz = - d.Ord_aGt - $m>=_aIm = - PrelBase.$m>={-rbS,p-} - (Bar{-r3m,x-} a{-aGA-}) - d.Ord_aHz - d.Ord_aHB = - d.Ord_aGt - $m>_aIl = - PrelBase.$m>{-rbR,p-} - (Bar{-r3m,x-} a{-aGA-}) - d.Ord_aHB - d.Ord_aHD = - d.Ord_aGt - $mmax_aIk = - PrelBase.$mmax{-rc5,p-} - (Bar{-r3m,x-} a{-aGA-}) - d.Ord_aHD - d.Ord_aHF = - d.Ord_aGt - $mmin_aIj = - PrelBase.$mmin{-rc7,p-} - (Bar{-r3m,x-} a{-aGA-}) - d.Ord_aHF - AbsBinds [] [] [([], compare_aGv, compare_aGx)] - compare_aGx - = $mcompare_aIp - AbsBinds [] [] [([], <_aGE, <_aGG)] - <_aGG - = $m<_aIo - AbsBinds [] [] [([], <=_aGM, <=_aGO)] - <=_aGO - = $m<=_aIn - AbsBinds [] [] [([], >=_aGU, >=_aGW)] - >=_aGW - = $m>=_aIm - AbsBinds [] [] [([], >_aH2, >_aH4)] - >_aH4 - = $m>_aIl - AbsBinds [] [] [([], max_aHa, max_aHc)] - max_aHc - = $mmax_aIk - AbsBinds [] [] [([], min_aHi, min_aHk)] - min_aHk - = $mmin_aIj - d.Ord_aGt = - ({-dict-} - [d.Eq_aHp] - [compare_aGv, <_aGE, <=_aGM, >=_aGU, >_aH2, max_aHa, min_aHi]) -{- rec -} -AbsBinds -[a{-aHW-}] -[d.Eq_aI5] -[([a{-aHW-}], $d2{-rIq,x-}, d.Eq_aHP)] - d.Eq_aI9 = - d.Eq_aHP - $m==_aIs = - PrelBase.$m=={-rbQ,p-} - (Bar{-r3m,x-} a{-aHW-}) - d.Eq_aI9 - d.Eq_aIb = - d.Eq_aHP - $m/=_aIr = - PrelBase.$m/={-rbN,p-} - (Bar{-r3m,x-} a{-aHW-}) - d.Eq_aIb - AbsBinds [] [] [([], ==_aHR, ==_aHT)] - ==_aHT - = $m==_aIs - AbsBinds [] [] [([], /=_aI0, /=_aI2)] - /=_aI2 - = $m/=_aIr - d.Eq_aHP = - ({-dict-} [] [==_aHR, /=_aI0]) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ M 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d14 1 $d15 1 $d32 1 $d34 1 $d37 1 $d39 1 $d41 1 $d45 1 $d46 1 $d49 1 $d51 1 $d6 1 $d7 1 Eq 1 Eval 1 Ord 1 Ordering 1; -PrelNum 1 :: $d17 1 $d18 1; -_exports_ -M Bar(MkBar); -_instances_ -instance _forall_ [a] {PrelBase.Ord a} => {PrelBase.Ord (Bar a)} = $d1; -instance _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (Bar a)} = $d2; -instance _forall_ [a] => {PrelBase.Eval (Bar a)} = $d3; -_declarations_ -1 $d1 _:_ _forall_ [a] {PrelBase.Ord a, PrelBase.Eq (Bar a)} => {PrelBase.Ord (Bar a)} ;; -1 $d2 _:_ _forall_ [a] {PrelBase.Eq a} => {PrelBase.Eq (Bar a)} ;; -1 $d3 _:_ _forall_ [a] => {PrelBase.Eval (Bar a)} ;; -1 data Bar r3k = MkBar PrelBase.Int r3k ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc079.hs b/ghc/compiler/tests/typecheck/should_succeed/tc079.hs deleted file mode 100644 index d49f4ce43a6bca853b49e36775cecf28173af78a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc079.hs +++ /dev/null @@ -1,16 +0,0 @@ ---!!! small class decl with local polymorphism; ---!!! "easy" to check default methods and such... ---!!! (this is the example given in TcClassDcl) --- -module Test where - -class Foo a where - op1 :: a -> Bool - op2 :: Ord b => a -> b -> b -> b - - op1 x = True - op2 x y z = if (op1 x) && (y < z) then y else z - -instance Foo Int where {} - -instance Foo a => Foo [a] where {} diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc079.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc079.stderr deleted file mode 100644 index c26a3f4ca1db036208a9adc32b61d0885a41fa0a..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc079.stderr +++ /dev/null @@ -1,122 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -op1{-r3F,x-} = - _/\_ a{-r3l-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B1;} -op2{-r3E,x-} = - _/\_ a{-r3l-} -> \ tpl_B1 -> - case tpl_B1 of { PrelTup.(,){-62,p-}{i} tpl_B1 tpl_B2 -> tpl_B2;} -{- nonrec -} -AbsBinds -[a{-aI8-}] -[d.Foo_aI2] -[([a{-aI8-}], $mop1{-rGN,x-}, op1_aIG)] - AbsBinds [] [] [([], op1_aIG, op1_aI5)] - op1_aI5 - x_r3u = PrelBase.True{-5E,p-}{i} -AbsBinds -[a{-aI8-}] -[d.Foo_aIb] -[([a{-aI8-}], $mop2{-rGQ,x-}, op2_aIJ)] - d.Foo_aIA = - d.Foo_aIb - op1_aIK = - op1{-r3F,x-} - a{-aI8-} - d.Foo_aIA - AbsBinds [b{-aIm-}] [d.Ord_aIw] [([b{-aIm-}], op2_aIJ, op2_aIg)] - d.Ord_aIy = - d.Ord_aIw - <_aIL = - PrelBase.<{-rd6,p-} - b{-aIm-} - d.Ord_aIy - op2_aIg - x_r3y y_r3A z_r3C - = if (op1_aIK x_r3y) - PrelBase.&&{-r3D,p-} (y_r3A <_aIL z_r3C) then - y_r3A - else - z_r3C -{- rec -} -AbsBinds -[a{-aGT-}] -[d.Foo_aHg] -[([a{-aGT-}], $d1{-rIM,x-}, d.Foo_aGK)] - d.Foo_aHi = - d.Foo_aGK - $mop1_aIO = - $mop1{-rGN,x-} - [a{-aGT-}] - d.Foo_aHi - d.Foo_aHk = - d.Foo_aGK - $mop2_aIN = - $mop2{-rGQ,x-} - [a{-aGT-}] - d.Foo_aHk - AbsBinds [] [] [([], op1_aGM, op1_aGP)] - op1_aGP - = $mop1_aIO - AbsBinds [b{-aH7-}] [d.Ord_aHd] [([b{-aH7-}], op2_aGY, op2_aH1)] - d.Ord_aHf = - d.Ord_aHd - $mop2_aIP = - $mop2_aIN - b{-aH7-} - d.Ord_aHf - op2_aH1 - = $mop2_aIP - d.Foo_aGK = - ({-dict-} [] [op1_aGM, op2_aGY]) -{- rec -} -AbsBinds [] [] [([], $d2{-rIQ,x-}, d.Foo_aHq)] - AbsBinds [] [] [([], op1_aHs, op1_aHu)] - op1_aHu - = $mop1_aII - AbsBinds [b{-aHL-}] [d.Ord_aHR] [([b{-aHL-}], op2_aHC, op2_aHF)] - d.Ord_aHV = - d.Ord_aHR - $mop2_aIR = - $mop2_aIH - b{-aHL-} - d.Ord_aHV - op2_aHF - = $mop2_aIR - d.Foo_aHq = - ({-dict-} [] [op1_aHs, op2_aHC]) -{- nonrec -} -d.Foo_aIC = - $d2{-rIQ,x-} -$mop1_aII = - $mop1{-rGN,x-} - PrelBase.Int{-3g,p-} - d.Foo_aIC -d.Foo_aIF = - d.Foo_aIC -$mop2_aIH = - $mop2{-rGQ,x-} - PrelBase.Int{-3g,p-} - d.Foo_aIF -ghc: module version changed to 1; reason: no old .hi file -_interface_ Test 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d14 1 $d15 1 $d26 1 $d27 1 $d32 1 $d34 1 $d49 1 $d51 1 $d6 1 $d7 1 && 1 Eq 1 Ord 1 Ordering 1; -PrelNum 1 :: $d17 1 $d18 1; -_exports_ -Test Foo(op1 op2); -_instances_ -instance _forall_ [a] {Foo a} => {Foo [a]} = $d1; -instance {Foo PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {Foo a} => {Foo [a]} ;; -1 $d2 _:_ {Foo PrelBase.Int} ;; -1 $mop1 _:_ _forall_ [a] {Foo a} => a -> PrelBase.Bool ;; -1 $mop2 _:_ _forall_ [a] {Foo a} => _forall_ [b] {PrelBase.Ord b} => a -> b -> b -> b ;; -1 class Foo r3l where {op1 :: r3l -> PrelBase.Bool; op2 :: _forall_ [r3p] {PrelBase.Ord r3p} => r3l -> r3p -> r3p -> r3p} ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc080.hs b/ghc/compiler/tests/typecheck/should_succeed/tc080.hs deleted file mode 100644 index d9ad6e9902f4918d1d583f1bbe099b8bed4a8013..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc080.hs +++ /dev/null @@ -1,53 +0,0 @@ ---module Parse(Parse(..),whiteSpace,seperatedBy) where ---import StdLib -class Parse a where - parseFile :: String -> [a] - parseFile string | all forced x = x - where x = map parseLine (lines' string) - parseLine :: String -> a - parseLine = pl.parse where pl (a,_) = a - parse :: String -> (a,String) - parse = parseType.whiteSpace - parseType :: String -> (a,String) - forced :: a -> Bool - forced x = True - -instance Parse Int where - parseType str = pl (span' isDigit str) - where pl (l,r) = (strToInt l,r) - forced n | n>=0 = True - -instance Parse Char where - parseType (ch:str) = (ch,str) - forced n = True - -instance (Parse a) => Parse [a] where - parseType more = (map parseLine (seperatedBy ',' (l++",")),out) - where (l,']':out) = span' (\x->x/=']') (tail more) - forced = all forced - -seperatedBy :: Char -> String -> [String] -seperatedBy ch [] = [] -seperatedBy ch xs = twaddle ch (span' (\x->x/=ch) xs) - where twaddle ch (l,_:r) = l:seperatedBy ch r - -whiteSpace :: String -> String -whiteSpace = dropWhile isSpace - -span' :: (a->Bool) -> [a] -> ([a],[a]) -span' p [] = ([],[]) -span' p (x:xs') | p x = fixLeak x (span' p xs') where fixLeak x (xs,ys) = (x:xs,ys) -span' _ xs = ([],xs) - -lines' :: [Char] -> [[Char]] -lines' "" = [] -lines' s = plumb (span' ((/=) '\n') s) - where plumb (l,s') = l:if null s' then [] else lines' (tail s') - -strToInt :: String -> Int -strToInt x = strToInt' (length x-1) x - where strToInt' _ [] = 0 - strToInt' x (a:l) = (charToInt a)*(10^x) + (strToInt' (x-1) l) - -charToInt :: Char -> Int -charToInt x = (ord x - ord '0') diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc080.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc080.stderr deleted file mode 100644 index ef30af27aebd8b6329a059f0a4a5e74ed6313f26..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc080.stderr +++ /dev/null @@ -1 +0,0 @@ -tc080.hs:15:1: Signature appears after definition in class body on input: "instance" diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc081.hs b/ghc/compiler/tests/typecheck/should_succeed/tc081.hs deleted file mode 100644 index 6590550cf670ae95778a5c35457645eb7473e89e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc081.hs +++ /dev/null @@ -1,28 +0,0 @@ ---!!! an example Simon made up --- -module ShouldSucceed where - -f x = (x+1, x<3, g True, g 'c') - where - g y = if x>2 then [] else [y] -{- -Here the type-check of g will yield an LIE with an Ord dict -for x. g still has type forall a. a -> [a]. The dictionary is -free, bound by the x. - -It should be ok to add the signature: --} - -f2 x = (x+1, x<3, g2 True, g2 'c') - where - -- NB: this sig: - g2 :: a -> [a] - g2 y = if x>2 then [] else [y] -{- -or to write: --} - -f3 x = (x+1, x<3, g3 True, g3 'c') - where - -- NB: this line: - g3 = (\ y -> if x>2 then [] else [y])::(a -> [a]) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc081.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc081.stderr deleted file mode 100644 index 96670584a2c82d90e0eea3a23696c0c6b865f238..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc081.stderr +++ /dev/null @@ -1,179 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aY0-}] -[d.Num_aY7, d.Ord_aYc] -[([t{-aY0-}], f3{-r3A,x-}, f3_aXr)] - +_a100 = - PrelBase.+{-rcZ,p-} - t{-aY0-} - d.Num_aY7 - d.Num_aYa = - d.Num_aY7 - fromInt_aZZ = - PrelBase.fromInt{-8R,p-} - t{-aY0-} - d.Num_aYa - lit_aZY = - fromInt_aZZ PrelBase.I#{-5b,p-}{i} 1# - <_aZX = - PrelBase.<{-raS,p-} - t{-aY0-} - d.Ord_aYc - fromInt_aZW = - fromInt_aZZ - lit_aZV = - fromInt_aZW PrelBase.I#{-5b,p-}{i} 3# - d.Ord_aYf = - d.Ord_aYc - >_aZU = - PrelBase.>{-rd6,p-} - t{-aY0-} - d.Ord_aYf - fromInt_aZT = - fromInt_aZZ - lit_aZS = - fromInt_aZT PrelBase.I#{-5b,p-}{i} 2# - f3_aXr - x_r3t = (x_r3t +_a100 lit_aZY, - x_r3t <_aZX lit_aZV, - g3_r3v - PrelBase.Bool{-34,p-} PrelBase.True{-5E,p-}{i}, - g3_r3v - PrelBase.Char{-38,p-} 'c') - where - {- nonrec -} - AbsBinds [a{-aXM-}] [] [([a{-aXM-}], g3_r3v, g3_aXv)] - g3_aXv - = \ y_r3x -> if x_r3t >_aZU lit_aZS then - PrelBase.[]{-5i,p-}{i} - a{-aXM-} - else - [y_r3x] (a{-aXM-}) - {- nonrec -} -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aYP-}] -[d.Num_aYW, d.Ord_aZ1] -[([t{-aYP-}], f2{-r3B,x-}, f2_aYi)] - +_a109 = - PrelBase.+{-rcZ,p-} - t{-aYP-} - d.Num_aYW - d.Num_aYZ = - d.Num_aYW - fromInt_a108 = - PrelBase.fromInt{-8R,p-} - t{-aYP-} - d.Num_aYZ - lit_a107 = - fromInt_a108 PrelBase.I#{-5b,p-}{i} 1# - <_a106 = - PrelBase.<{-raS,p-} - t{-aYP-} - d.Ord_aZ1 - fromInt_a105 = - fromInt_a108 - lit_a104 = - fromInt_a105 PrelBase.I#{-5b,p-}{i} 3# - d.Ord_aZ4 = - d.Ord_aZ1 - >_a103 = - PrelBase.>{-rd6,p-} - t{-aYP-} - d.Ord_aZ4 - fromInt_a102 = - fromInt_a108 - lit_a101 = - fromInt_a102 PrelBase.I#{-5b,p-}{i} 2# - f2_aYi - x_r3l = (x_r3l +_a109 lit_a107, - x_r3l <_a106 lit_a104, - g2_r3n - PrelBase.Bool{-34,p-} PrelBase.True{-5E,p-}{i}, - g2_r3n - PrelBase.Char{-38,p-} 'c') - where - {- nonrec -} - AbsBinds [a{-aYr-}] [] [([a{-aYr-}], g2_r3n, g2_aYo)] - g2_aYo - y_r3r = if x_r3l >_a103 lit_a101 then - PrelBase.[]{-5i,p-}{i} - a{-aYr-} - else - [y_r3r] (a{-aYr-}) - {- nonrec -} -{- nonrec -} -{- nonrec -} -AbsBinds -[t{-aZC-}] -[d.Num_aZJ, d.Ord_aZO] -[([t{-aZC-}], f{-r3C,x-}, f_aZ7)] - +_a10j = - PrelBase.+{-rcZ,p-} - t{-aZC-} - d.Num_aZJ - d.Num_aZM = - d.Num_aZJ - fromInt_a10i = - PrelBase.fromInt{-8R,p-} - t{-aZC-} - d.Num_aZM - lit_a10h = - fromInt_a10i PrelBase.I#{-5b,p-}{i} 1# - <_a10g = - PrelBase.<{-raS,p-} - t{-aZC-} - d.Ord_aZO - fromInt_a10f = - fromInt_a10i - lit_a10e = - fromInt_a10f PrelBase.I#{-5b,p-}{i} 3# - d.Ord_aZR = - d.Ord_aZO - >_a10d = - PrelBase.>{-rd6,p-} - t{-aZC-} - d.Ord_aZR - fromInt_a10c = - fromInt_a10i - lit_a10a = - fromInt_a10c PrelBase.I#{-5b,p-}{i} 2# - f_aZ7 - x_r3f = (x_r3f +_a10j lit_a10h, - x_r3f <_a10g lit_a10e, - g_r3h - PrelBase.Bool{-34,p-} PrelBase.True{-5E,p-}{i}, - g_r3h - PrelBase.Char{-38,p-} 'c') - where - {- nonrec -} - AbsBinds [t{-aZn-}] [] [([t{-aZn-}], g_r3h, g_aZb)] - g_aZb - y_r3j = if x_r3f >_a10d lit_a10a then - PrelBase.[]{-5i,p-}{i} - t{-aZn-} - else - [y_r3j] (t{-aZn-}) - {- nonrec -} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ ShouldSucceed 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d14 1 $d15 1 $d2 1 $d21 1 $d26 1 $d27 1 $d3 1 $d32 1 $d33 1 $d34 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d45 1 $d46 1 $d49 1 $d50 1 $d51 1 $d54 1 $d55 1 $d6 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Ord 1 Ordering 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1; -PrelTup 1 :: $d11 1 $d15 1 $d2 1 $d51 1; -_exports_ -ShouldSucceed f f2 f3; -_declarations_ -1 f _:_ _forall_ [a] {PrelBase.Num a, PrelBase.Ord a} => a -> (a, PrelBase.Bool, [PrelBase.Bool], [PrelBase.Char]) ;; -1 f2 _:_ _forall_ [a] {PrelBase.Num a, PrelBase.Ord a} => a -> (a, PrelBase.Bool, [PrelBase.Bool], [PrelBase.Char]) ;; -1 f3 _:_ _forall_ [a] {PrelBase.Num a, PrelBase.Ord a} => a -> (a, PrelBase.Bool, [PrelBase.Bool], [PrelBase.Char]) ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc082.hs b/ghc/compiler/tests/typecheck/should_succeed/tc082.hs deleted file mode 100644 index f2ccb367361b60b9d0630f03de041273637bdd37..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc082.hs +++ /dev/null @@ -1,12 +0,0 @@ ---!!! tc082: an instance for functions --- -module N where - -class Normal a - where - normal :: a -> Bool - -instance Normal ( a -> b ) where - normal _ = True - -f x = normal id diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc082.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc082.stderr deleted file mode 100644 index 4dadbcebed6dcef789ce7146cb1dec3b01ec4741..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc082.stderr +++ /dev/null @@ -1,56 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -normal{-r3q,x-} = - _/\_ a{-r3o-} -> \ tpl_B1 -> - tpl_B1 -{- nonrec -} -AbsBinds -[a{-avr-}] -[d.Normal_avk] -[([a{-avr-}], $mnormal{-ruO,x-}, normal_avm)] - AbsBinds [] [] [([], normal_avm, normal_avo)] - normal_avo - = GHCerr.noDefaultMethodError{-8k,p-} - (a{-avr-} -> PrelBase.Bool{-34,p-}) "Class Normal Method normal" -{- rec -} -AbsBinds -[a{-avf-}, b{-avg-}] -[] -[([a{-avf-}, b{-avg-}], $d1{-rvs,x-}, d.Normal_av9)] - AbsBinds [] [] [([], normal_avt, normal_avc)] - normal_avc - _ = PrelBase.True{-5E,p-}{i} - d.Normal_av9 = - ({-dict-} [] [normal_avt]) -{- nonrec -} -{- nonrec -} -AbsBinds [t{-auZ-}] [] [([t{-auZ-}], f{-r3p,x-}, f_auN)] - d.Normal_av1 = - $d1{-rvs,x-} - [GHC.Void{-3T,p-}, GHC.Void{-3T,p-}] - normal_avu = - normal{-r3q,x-} - (GHC.Void{-3T,p-} -> GHC.Void{-3T,p-}) - d.Normal_av1 - f_auN - x_r3f = normal_avu PrelBase.id{-raJ,p-} - GHC.Void{-3T,p-} -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ N 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: id 1; -_exports_ -N f Normal(normal); -_instances_ -instance _forall_ [a b] => {Normal (a -> b)} = $d1; -_declarations_ -1 $d1 _:_ _forall_ [a b] => {Normal (a -> b)} ;; -1 $mnormal _:_ _forall_ [a] {Normal a} => a -> PrelBase.Bool ;; -1 class Normal r3o where {normal :: r3o -> PrelBase.Bool} ; -1 f _:_ _forall_ [a] => a -> PrelBase.Bool ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc083.hs b/ghc/compiler/tests/typecheck/should_succeed/tc083.hs deleted file mode 100644 index 1c5321e63115783956422bb3f130edac86d482f5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc083.hs +++ /dev/null @@ -1,10 +0,0 @@ ---!!! instances with no binds; ---!!! be sure we get a legit .hi file --- -module Bar where - -import ClassFoo - -instance Foo Int - -instance Foo a => Foo [a] diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc083.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc083.stderr deleted file mode 100644 index 818976feaaff5eb42bddcf6096095ea1860b8c59..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc083.stderr +++ /dev/null @@ -1,65 +0,0 @@ - - ---================================================================================ -Typechecked: -{- rec -} -AbsBinds -[a{-auS-}] -[d.Foo_av1] -[([a{-auS-}], $d1{-rvF,x-}, d.Foo_auJ)] - d.Foo_av5 = - d.Foo_auJ - $mop1_avJ = - ClassFoo.$mop1{-ruM,p-} - [a{-auS-}] - d.Foo_av5 - d.Foo_av7 = - d.Foo_auJ - $mop2_avI = - ClassFoo.$mop2{-ruP,p-} - [a{-auS-}] - d.Foo_av7 - AbsBinds [] [] [([], op1_auL, op1_auO)] - op1_auO - = $mop1_avJ - AbsBinds [] [] [([], op2_auW, op2_auY)] - op2_auY - = $mop2_avI - d.Foo_auJ = - ({-dict-} [] [op1_auL, op2_auW]) -{- rec -} -AbsBinds [] [] [([], $d2{-rvK,x-}, d.Foo_avd)] - AbsBinds [] [] [([], op1_avf, op1_avh)] - op1_avh - = $mop1_avH - AbsBinds [] [] [([], op2_avo, op2_avq)] - op2_avq - = $mop2_avG - d.Foo_avd = - ({-dict-} [] [op1_avf, op2_avo]) -{- nonrec -} -d.Foo_avB = - $d2{-rvK,x-} -$mop1_avH = - ClassFoo.$mop1{-ruM,p-} - PrelBase.Int{-3g,p-} - d.Foo_avB -d.Foo_avE = - d.Foo_avB -$mop2_avG = - ClassFoo.$mop2{-ruP,p-} - PrelBase.Int{-3g,p-} - d.Foo_avE -ghc: module version changed to 1; reason: no old .hi file -_interface_ Bar 1 -_instance_modules_ -ArrBase Bar IO PrelNum -_usages_ -ClassFoo 1 :: Foo 1; -_exports_ -_instances_ -instance _forall_ [a] {ClassFoo.Foo a} => {ClassFoo.Foo [a]} = $d1; -instance {ClassFoo.Foo PrelBase.Int} = $d2; -_declarations_ -1 $d1 _:_ _forall_ [a] {ClassFoo.Foo a} => {ClassFoo.Foo [a]} ;; -1 $d2 _:_ {ClassFoo.Foo PrelBase.Int} ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc084.hs b/ghc/compiler/tests/typecheck/should_succeed/tc084.hs deleted file mode 100644 index 572bbe31dc97f6153169f869be6d9f056d3830e5..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc084.hs +++ /dev/null @@ -1,23 +0,0 @@ -{- This program shows up a bug in the handling of - the monomorphism restriction in an earlier version of - ghc. With ghc 0.18 and before, f gets a type with - an unbound type variable, which shows up in the - interface file. Reason: it was being monomorphised. - - Simon PJ --} - -module Foo where - - -g :: Num a => Bool -> a -> b -> a -g b x y = if b then x+x else x-x - --- Everything is ok if this signature is put in --- but the program should be perfectly legal without it. --- f :: Num a => a -> b -> a -f = g True - -h y x = f (x::Int) y - -- This use of f binds the overloaded monomorphic - -- type to Int diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc084.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc084.stderr deleted file mode 100644 index 630058c708d2bb731c05a54dab9819cc2a522167..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc084.stderr +++ /dev/null @@ -1,57 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -d.Num_aHu = - PrelBase.$d3{-rbi,p-} -{- nonrec -} -AbsBinds -[a{-aH2-}, b{-aH5-}] -[d.Num_aHd] -[([b{-aH5-}, a{-aH2-}], g{-r3h,x-}, g_aGY)] - d.Num_aHf = - d.Num_aHd - +_aHG = - PrelBase.+{-rcQ,p-} - a{-aH2-} - d.Num_aHf - d.Num_aHh = - d.Num_aHd - -_aHF = - PrelBase.-{-817,p-} - a{-aH2-} - d.Num_aHh - g_aGY - b_r3l x_r3n y_r3p - = if b_r3l then x_r3n +_aHG x_r3n else x_r3n -_aHF x_r3n -{- nonrec -} -{- nonrec -} -AbsBinds [b{-aHp-}] [] [([b{-aHp-}], f{-r3j,x-}, f_aHj)] - g_aHH = - g{-r3h,x-} - [b{-aHp-}, PrelBase.Int{-3g,p-}] - d.Num_aHu - f_aHj - = g_aHH PrelBase.True{-5E,p-}{i} -{- nonrec -} -{- nonrec -} -AbsBinds [b{-aHE-}] [] [([b{-aHE-}], h{-r3i,x-}, h_aHw)] - h_aHw - y_r3r x_r3t - = f{-r3j,x-} - b{-aHE-} x_r3t y_r3r -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ Foo 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -PrelBase 1 :: $d1 1 $d11 1 $d15 1 $d2 1 $d21 1 $d27 1 $d3 1 $d32 1 $d33 1 $d37 1 $d38 1 $d39 1 $d41 1 $d42 1 $d44 1 $d46 1 $d54 1 $d7 1 $d8 1 Eq 1 Eval 1 Num 1 Show 1 String 1; -PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1; -_exports_ -Foo f g h; -_declarations_ -1 f _:_ _forall_ [a] => PrelBase.Int -> a -> PrelBase.Int ;; -1 g _:_ _forall_ [a b] {PrelBase.Num b} => PrelBase.Bool -> b -> a -> b ;; -1 h _:_ _forall_ [a] => a -> PrelBase.Int -> PrelBase.Int ;; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc085.hs b/ghc/compiler/tests/typecheck/should_succeed/tc085.hs deleted file mode 100644 index fe5ad6a8ae7fa68d0d68cd116f33bb418dc2de57..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc085.hs +++ /dev/null @@ -1,9 +0,0 @@ ---!!! From a bug report from Satnam. ---!!! To do with re-exporting importees from PreludeGla* modules. -module Foo ( module GlaExts, module Foo ) where - ---OLD: import PreludeGlaIO -import GlaExts - -type FooType = Int -data FooData = FooData diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc085.stderr b/ghc/compiler/tests/typecheck/should_succeed/tc085.stderr deleted file mode 100644 index f47847008187b7da0a7fd8cf6ff57925980c4004..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc085.stderr +++ /dev/null @@ -1,38 +0,0 @@ - - ---================================================================================ -Typechecked: -{- nonrec -} -FooData{-r2,x-}{i} = - FooData{-r2,x-}{i} - {} -{- rec -} -AbsBinds [] [] [([], $d1{-rGv,x-}, d.Eval_aGs)] - d.Eval_aGs = - ({-dict-} [] []) -{- nonrec -} -ghc: module version changed to 1; reason: no old .hi file -_interface_ Foo 1 -_instance_modules_ -ArrBase IO PrelNum -_usages_ -GlaExts 1 :: ; -PrelBase 1 :: $d37 1 $d39 1 $d41 1 $d46 1 Eval 1; -_exports_ -ArrBase boundsOfArray boundsOfByteArray freezeAddrArray freezeArray freezeCharArray freezeDoubleArray freezeFloatArray freezeIntArray indexAddrArray indexAddrOffAddr indexCharArray indexCharOffAddr indexDoubleArray indexDoubleOffAddr indexFloatArray indexFloatOffAddr indexIntArray indexIntOffAddr newAddrArray newArray newCharArray newDoubleArray newFloatArray newIntArray readAddrArray readArray readCharArray readDoubleArray readFloatArray readIntArray thawArray unsafeFreezeArray unsafeFreezeByteArray writeAddrArray writeArray writeCharArray writeDoubleArray writeFloatArray writeIntArray ByteArray(ByteArray) MutableArray(MutableArray) MutableByteArray(MutableByteArray); -Foo FooData(FooData) FooType; -Foreign Addr(A#) Word(W#); -GHC *# *## **## +# +## -# -## /## /=# /=## <# <## <=# <=## ==# ==## ># >## >=# >=## acosDouble# acosFloat# addr2Int# and# asinDouble# asinFloat# atanDouble# atanFloat# chr# cmpInteger# cosDouble# cosFloat# coshDouble# coshFloat# deRefStablePtr# decodeDouble# decodeFloat# delay# divideFloat# double2Float# double2Int# encodeDouble# encodeFloat# eqAddr# eqChar# eqFloat# eqWord# errorIO# expDouble# expFloat# float2Double# float2Int# fork# geAddr# geChar# geFloat# geWord# gtAddr# gtChar# gtFloat# gtWord# iShiftL# iShiftRA# iShiftRL# indexAddrArray# indexAddrOffAddr# indexArray# indexCharArray# indexCharOffAddr# indexDoubleArray# indexDoubleOffAddr# indexFloatArray# indexFloatOffAddr# indexIntArray# indexIntOffAddr# int2Addr# int2Double# int2Float# int2Integer# int2Word# integer2Int# leAddr# leChar# leFloat# leWord# logDouble# logFloat# ltAddr# ltChar# ltFloat# ltWord# makeForeignObj# makeStablePtr# minusFloat# minusInteger# neAddr# neChar# neFloat# neWord# negateDouble# negateFloat# negateInt# negateInteger# newAddrArray# newArray# newCharArray# newDoubleArray# newFloatArray# newIntArray# newSynchVar# not# or# ord# par# parAt# parAtForNow# parGlobal# parLocal# plusFloat# plusInteger# powerFloat# putMVar# quotInt# quotRemInteger# readAddrArray# readArray# readCharArray# readDoubleArray# readFloatArray# readIntArray# realWorld# remInt# sameMutableArray# sameMutableByteArray# seq# shiftL# shiftRA# shiftRL# sinDouble# sinFloat# sinhDouble# sinhFloat# sqrtDouble# sqrtFloat# takeMVar# tanDouble# tanFloat# tanhDouble# tanhFloat# timesFloat# timesInteger# unsafeFreezeArray# unsafeFreezeByteArray# waitRead# waitWrite# word2Int# writeAddrArray# writeArray# writeCharArray# writeDoubleArray# writeFloatArray# writeForeignObj# writeIntArray# -> Addr# All Array# ByteArray# Char# Double# Float# ForeignObj# Int# MutableArray# MutableByteArray# RealWorld StablePtr# State# SynchVar# Void Word#; -IOBase ioToPrimIO ioToST primIOToIO seqIO_Prim stToIO thenIO_Prim trace; -Ix Ix; -PrelBase Char(C#) Double(D#) Float(F#) Int(I#) Integer(J#); -STBase fixPrimIO listPrimIO mapAndUnzipPrimIO mapPrimIO returnPrimIO seqPrimIO thenPrimIO unsafeInterleavePrimIO unsafePerformPrimIO PrimIO ST; -_fixities_ -infixr 1 seqIO_Prim; -infixr 1 thenIO_Prim; -_instances_ -instance {PrelBase.Eval FooData} = $d1; -_declarations_ -1 $d1 _:_ {PrelBase.Eval FooData} ;; -1 data FooData = FooData ; -1 type FooType = PrelBase.Int ; diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc086.hs b/ghc/compiler/tests/typecheck/should_succeed/tc086.hs deleted file mode 100644 index 4d9ba6edb6461442c5572c6229841f134e87ee2e..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc086.hs +++ /dev/null @@ -1,60 +0,0 @@ -{- - From: Marc van Dongen <dongen@cs.ucc.ie> - Date: Sat, 31 May 1997 19:57:46 +0100 (BST) - - panic! (the `impossible' happened): - tcLookupTyVar:a_r6F - - Please report it as a compiler bug to glasgow-haskell-bugs@dcs.gla.ac.uk. - - -If the instance definition for (*) at the end of this toy module -is replaced by the definition that is commented, this all compiles -fine. Strange, because the two implementations are equivalent modulo -the theory {(*) = multiply}. - -Remove the `multiply :: a -> a -> a' part, and it compiles without -problems. - - -SPJ note: the type signature on "multiply" should be - multiply :: Group a => a -> a -> a - --} - -module Rings( Group, Ring ) where - -import qualified Prelude( Ord(..), Eq(..), Num(..) ) -import Prelude hiding( Ord(..), Eq(..), Num(..), MonadZero( zero ) ) - -class Group a where - compare :: a -> a -> Prelude.Ordering - fromInteger :: Integer -> a - (+) :: a -> a -> a - (-) :: a -> a -> a - zero :: a - one :: a - zero = fromInteger 0 - one = fromInteger 1 - --- class (Group a) => Ring a where --- (*) :: a -> a -> a --- (*) a b = --- case (compare a zero) of --- EQ -> zero --- LT -> zero - ((*) (zero - a) b) --- GT -> case compare a one of --- EQ -> b --- _ -> b + ((*) (a - one) b) - -class (Group a) => Ring a where - (*) :: a -> a -> a - (*) a b = multiply a b - where multiply :: Group a => a -> a ->a - multiply a b - = case (compare a zero) of - EQ -> zero - LT -> zero - (multiply (zero - a) b) - GT -> case compare a one of - EQ -> b - _ -> b + (multiply (a - one) b) diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc087.hs b/ghc/compiler/tests/typecheck/should_succeed/tc087.hs deleted file mode 100644 index 8477427e1176b7fe125736ec595f6f0c10133c1d..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc087.hs +++ /dev/null @@ -1,32 +0,0 @@ -module SOL where - -import GlaExts - -data SeqView t a = Null - | Cons a (t a) - -class PriorityQueue q where - empty :: (Ord a) => q a - single :: (Ord a) => a -> q a - insert :: (Ord a) => a -> q a -> q a - meld :: (Ord a) => q a -> q a -> q a - splitMin :: (Ord a) => q a -> SeqView q a - insert a q = single a `meld` q - -toOrderedList q = case splitMin q of - Null -> [] - Cons a q -> a : toOrderedList q - -insertMany x q = foldr insert q x -pqSort q x = toOrderedList (insertMany x q) - -check :: (PriorityQueue q) => (Ord a => q a) -> IO () -check empty = do - putStr "*** sorting\n" - out (pqSort empty [1 .. 99]) - out (pqSort empty [1.0, 1.1 ..99.9]) - -out :: (Num a) => [a] -> IO () -out x | sum x == 0 = putStr "ok\n" - | otherwise = putStr "ok\n" - diff --git a/ghc/compiler/tests/typecheck/should_succeed/tc088.hs b/ghc/compiler/tests/typecheck/should_succeed/tc088.hs deleted file mode 100644 index e1b8b88dd6eb07b0dfc43e2a55f131d6fe7570d2..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/should_succeed/tc088.hs +++ /dev/null @@ -1,18 +0,0 @@ --- Check that "->" is an instance of Eval - -module Foo where - -instance (Eq b) => Eq (a -> b) where - (==) f g = error "attempt to compare functions" - - -- Since Eval is a superclass of Num this fails - -- unless -> is an instance of Eval -instance (Num b) => Num (a -> b) where - f + g = \a -> f a + g a - f - g = \a -> f a - g a - f * g = \a -> f a * g a - negate f = \a -> negate (f a) - abs f = \a -> abs (f a) - signum f = \a -> signum (f a) - fromInteger n = \a -> fromInteger n - fromInt n = \a -> fromInt n diff --git a/ghc/compiler/tests/typecheck/stress/Makefile b/ghc/compiler/tests/typecheck/stress/Makefile deleted file mode 100644 index 641ad12986ebaa877f3d47440e919459aec472dd..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/stress/Makefile +++ /dev/null @@ -1,16 +0,0 @@ -TOP = ../../../.. -include $(TOP)/mk/boilerplate.mk - -HS_SRCS = $(wildcard *.hs) - -SRC_RUNTEST_OPTS += -o1 $*.stdout -o2 $*.stderr -x 0 -HC_OPTS += -noC -ddump-tc -dcore-lint -hi - -%.o : %.hs - -%.o : %.hs - $(RUNTEST) $(HC) $(RUNTEST_OPTS) -- $(HC_OPTS) -c $< -o $@ -osuf $(subst .,,$(suffix $@)) - -all :: $(HS_OBJS) - -include $(TOP)/mk/target.mk diff --git a/ghc/compiler/tests/typecheck/stress/tcstress001.hs b/ghc/compiler/tests/typecheck/stress/tcstress001.hs deleted file mode 100644 index bbb6508b3808b910b7aa31bba580bbc048a1f403..0000000000000000000000000000000000000000 --- a/ghc/compiler/tests/typecheck/stress/tcstress001.hs +++ /dev/null @@ -1,73 +0,0 @@ - -module Prims where - -import Prelude hiding (head) - -one = one - -head (x:xs) = x - -bottom = head - -absIf a b c = a - -absAnd a b = head [a,b] - -fac_rec fac0 n a - = (absIf (absAnd (s_3_0 n) one) - (s_2_0 a) - (fac0 (absAnd (s_3_2 n) one) (absAnd (s_3_1 n) (s_2_1 a)))) - -f_rec f0 a - = (f0 (s_1_0 a)) - -g_rec g0 g1 x y z p - = (absIf (absAnd (s_3_0 p) one) - (absAnd (s_1_0 x) (s_3_0 z)) - (absAnd - (g0 (s_1_0 y) one one (absAnd (s_3_1 p) one)) - (g1 (s_3_2 z) (s_3_1 z) one (absAnd (s_3_2 p) one)))) - -s_2_0 (v0,v1) = v0 -s_2_1 (v0,v1) = v1 -s_1_0 v0 = v0 -s_3_0 (v0,v1,v2) = v0 -s_3_1 (v0,v1,v2) = v1 -s_3_2 (v0,v1,v2) = v2 - -fac n a - = (fac_rec fac_rec4 n a) - -fac_rec4 n a = (fac_rec fac_rec3 n a) -fac_rec3 n a = (fac_rec fac_rec2 n a) -fac_rec2 n a = (fac_rec fac_rec1 n a) -fac_rec1 n a = (fac_rec fac_rec0 n a) -fac_rec0 n a = (bottom [n,a]) - -f a - = (f_rec f_rec2 a) - -f_rec2 a = (f_rec f_rec1 a) -f_rec1 a = (f_rec f_rec0 a) -f_rec0 a = (bottom [a]) - -g x y z p - = (g_rec g_rec16 g_rec16 x y z p) - -g_rec16 x y z p = (g_rec g_rec15 g_rec15 x y z p) -g_rec15 x y z p = (g_rec g_rec14 g_rec14 x y z p) -g_rec14 x y z p = (g_rec g_rec13 g_rec13 x y z p) -g_rec13 x y z p = (g_rec g_rec12 g_rec12 x y z p) -g_rec12 x y z p = (g_rec g_rec11 g_rec11 x y z p) -g_rec11 x y z p = (g_rec g_rec10 g_rec10 x y z p) -g_rec10 x y z p = (g_rec g_rec9 g_rec9 x y z p) -g_rec9 x y z p = (g_rec g_rec8 g_rec8 x y z p) -g_rec8 x y z p = (g_rec g_rec7 g_rec7 x y z p) -g_rec7 x y z p = (g_rec g_rec6 g_rec6 x y z p) -g_rec6 x y z p = (g_rec g_rec5 g_rec5 x y z p) -g_rec5 x y z p = (g_rec g_rec4 g_rec4 x y z p) -g_rec4 x y z p = (g_rec g_rec3 g_rec3 x y z p) -g_rec3 x y z p = (g_rec g_rec2 g_rec2 x y z p) -g_rec2 x y z p = (g_rec g_rec1 g_rec1 x y z p) -g_rec1 x y z p = (g_rec g_rec0 g_rec0 x y z p) -g_rec0 x y z p = (bottom [x,y,z,p]) diff --git a/ghc/compiler/tests/typecheck/stress/tcstress001.stderr b/ghc/compiler/tests/typecheck/stress/tcstress001.stderr deleted file mode 100644 index e69de29bb2d1d6434b8b29ae775ad8c2e48c5391..0000000000000000000000000000000000000000