diff options
Diffstat (limited to 'testsuite/tests/parser/should_compile')
89 files changed, 949 insertions, 0 deletions
diff --git a/testsuite/tests/parser/should_compile/DoAndIfThenElse.hs b/testsuite/tests/parser/should_compile/DoAndIfThenElse.hs new file mode 100644 index 0000000000..5bfb6edc86 --- /dev/null +++ b/testsuite/tests/parser/should_compile/DoAndIfThenElse.hs @@ -0,0 +1,9 @@ + +{-# LANGUAGE DoAndIfThenElse #-} + +module DoAndIfThenElse where + +foo :: IO () +foo = do if True + then return () + else return () diff --git a/testsuite/tests/parser/should_compile/EmptyDecls.hs b/testsuite/tests/parser/should_compile/EmptyDecls.hs new file mode 100644 index 0000000000..9583f23e32 --- /dev/null +++ b/testsuite/tests/parser/should_compile/EmptyDecls.hs @@ -0,0 +1,9 @@ +module Main where { + +f x = x; +; +; +g y z = z; + +main = print (g (f False) (f True)); +} diff --git a/testsuite/tests/parser/should_compile/Makefile b/testsuite/tests/parser/should_compile/Makefile new file mode 100644 index 0000000000..9101fbd40a --- /dev/null +++ b/testsuite/tests/parser/should_compile/Makefile @@ -0,0 +1,3 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk diff --git a/testsuite/tests/parser/should_compile/NondecreasingIndentation.hs b/testsuite/tests/parser/should_compile/NondecreasingIndentation.hs new file mode 100644 index 0000000000..05273097ed --- /dev/null +++ b/testsuite/tests/parser/should_compile/NondecreasingIndentation.hs @@ -0,0 +1,10 @@ + +{-# LANGUAGE NondecreasingIndentation #-} + +module ShouldCompile where + +f :: IO () +f = do if True then f else do + f + if True then f else do + f diff --git a/testsuite/tests/parser/should_compile/T2245.hs b/testsuite/tests/parser/should_compile/T2245.hs new file mode 100644 index 0000000000..bf8287ba33 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T2245.hs @@ -0,0 +1,7 @@ +default (T) + +data T = T deriving (Eq, Ord, Read, Show) +instance Num T +instance Fractional T + +main = interact $ show . (< 1e400) . read
\ No newline at end of file diff --git a/testsuite/tests/parser/should_compile/T2245.stderr b/testsuite/tests/parser/should_compile/T2245.stderr new file mode 100644 index 0000000000..b1754ff0c5 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T2245.stderr @@ -0,0 +1,34 @@ + +T2245.hs:4:10: + Warning: No explicit method nor default method for `+' + In the instance declaration for `Num T' + +T2245.hs:4:10: + Warning: No explicit method nor default method for `*' + In the instance declaration for `Num T' + +T2245.hs:4:10: + Warning: No explicit method nor default method for `abs' + In the instance declaration for `Num T' + +T2245.hs:4:10: + Warning: No explicit method nor default method for `signum' + In the instance declaration for `Num T' + +T2245.hs:4:10: + Warning: No explicit method nor default method for `fromInteger' + In the instance declaration for `Num T' + +T2245.hs:5:10: + Warning: No explicit method nor default method for `fromRational' + In the instance declaration for `Fractional T' + +T2245.hs:7:29: + Warning: Defaulting the following constraint(s) to type `T' + (Fractional b0) arising from the literal `1e400' + at T2245.hs:7:29-33 + (Ord b0) arising from a use of `<' at T2245.hs:7:27 + (Read b0) arising from a use of `read' at T2245.hs:7:38-41 + In the second argument of `(<)', namely `1e400' + In the first argument of `(.)', namely `(< 1e400)' + In the second argument of `(.)', namely `(< 1e400) . read' diff --git a/testsuite/tests/parser/should_compile/T3303.hs b/testsuite/tests/parser/should_compile/T3303.hs new file mode 100644 index 0000000000..08de52e6cd --- /dev/null +++ b/testsuite/tests/parser/should_compile/T3303.hs @@ -0,0 +1,8 @@ + +module T3303 where + +import T3303A + +bar :: Int +bar = foo + diff --git a/testsuite/tests/parser/should_compile/T3303.stderr b/testsuite/tests/parser/should_compile/T3303.stderr new file mode 100644 index 0000000000..6e0b5629b3 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T3303.stderr @@ -0,0 +1,7 @@ + +T3303.hs:4:1: + Warning: In the use of `foo' + (imported from T3303A): + Deprecated: "This is a multi-line + deprecation message + for foo" diff --git a/testsuite/tests/parser/should_compile/T3303A.hs b/testsuite/tests/parser/should_compile/T3303A.hs new file mode 100644 index 0000000000..daa4bfb91d --- /dev/null +++ b/testsuite/tests/parser/should_compile/T3303A.hs @@ -0,0 +1,10 @@ + +module T3303A where + +{-# DEPRECATED foo + ["This is a multi-line", + "deprecation message", + "for foo"] #-} +foo :: Int +foo = 4 + diff --git a/testsuite/tests/parser/should_compile/T3741.hs b/testsuite/tests/parser/should_compile/T3741.hs new file mode 100644 index 0000000000..20d5c2d095 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T3741.hs @@ -0,0 +1,4 @@ +笑 :: Int +笑 = 3 + +main = print 笑 diff --git a/testsuite/tests/parser/should_compile/T5243.hs b/testsuite/tests/parser/should_compile/T5243.hs new file mode 100644 index 0000000000..e58ace299b --- /dev/null +++ b/testsuite/tests/parser/should_compile/T5243.hs @@ -0,0 +1 @@ + { import T5243A; main = print bar } diff --git a/testsuite/tests/parser/should_compile/T5243.stderr b/testsuite/tests/parser/should_compile/T5243.stderr new file mode 100644 index 0000000000..450e001237 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T5243.stderr @@ -0,0 +1,3 @@ +[1 of 2] Compiling T5243A ( T5243A.hs, T5243A.o ) +[2 of 2] Compiling Main ( T5243.hs, T5243.o ) +Linking T5243 ... diff --git a/testsuite/tests/parser/should_compile/T5243A.hs b/testsuite/tests/parser/should_compile/T5243A.hs new file mode 100644 index 0000000000..2332c84004 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T5243A.hs @@ -0,0 +1,2 @@ +module T5243A where +bar = True diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T new file mode 100644 index 0000000000..328c0651c3 --- /dev/null +++ b/testsuite/tests/parser/should_compile/all.T @@ -0,0 +1,94 @@ + +test('read001', normal, compile, ['']) +test('read002', normal, compile, ['']) +test('read003', normal, compile, ['']) +test('read004', normal, compile, ['']) +test('read005', normal, compile, ['']) + +# Missing: +# test('read006', normal, compile, ['']) +# test('read007', normal, compile, ['']) + +test('read008', normal, compile, ['']) +test('read009', normal, compile, ['']) +test('read010', normal, compile, ['']) +test('read011', normal, compile, ['']) + +# Missing: +# test('read012', normal, compile, ['']) +# test('read013', normal, compile, ['']) + +test('read014', normal, compile, ['-Wall -fno-warn-orphans']) +test('read015', normal, compile, ['']) +test('read016', normal, compile, ['']) +test('read017', normal, compile, ['']) +test('read018', normal, compile, ['']) +test('read019', normal, compile, ['']) + +# Missing: +# test('read020', normal, compile, ['']) + +test('read021', normal, compile, ['']) +test('read022', normal, compile, ['']) + +# we don't support strict Haskell 98 with respect to qualified identifiers +# any more (read023), see #1215. This test is in fact incorrect Haskell 98 +# anyway, so expect_fail would be wrong. +test('read023', skip, compile, ['']) + +test('read024', normal, compile, ['']) +test('read025', normal, compile, ['']) +test('read026', normal, compile, ['']) +test('read027', normal, compile, ['']) +test('read028', normal, compile, ['']) +test('read029', normal, compile, ['']) +test('read030', normal, compile, ['']) +test('read031', normal, compile, ['']) +test('read032', normal, compile, ['']) +test('read033', if_compiler_type('hugs', expect_fail), compile, ['']) +test('read034', if_compiler_type('hugs', expect_fail), compile, ['']) +test('read036', normal, compile, ['']) +test('read037', normal, compile, ['']) +test('read038', normal, compile, ['']) +test('read039', normal, compile, ['-fno-code']) +test('read040', normal, compile, ['']) +test('read041', literate, compile, ['']) +test('read042', normal, compile, ['']) +test('read043', normal, compile, ['']) +test('read044', normal, compile, ['']) +test('read045', normal, compile, ['']) +test('read046', normal, compile, ['']) +test('read047', normal, compile, ['']) +test('read048', normal, compile, ['']) +test('read049', normal, compile, ['']) +test('read050', normal, compile, ['']) +test('read051', normal, compile, ['']) +test('read052', normal, compile, ['']) +test('read053', normal, compile, ['']) +test('read054', normal, compile, ['']) +test('read055', normal, compile, ['']) +test('read056', normal, compile, ['']) +test('read057', normal, compile, ['']) +test('read058', omit_ways(['profc']), compile, ['']) +test('read059', omit_ways(['profc']), compile, ['']) +test('read060', normal, compile, ['']) +test('read061', normal, compile, ['']) +test('read062', normal, compile, ['']) +test('read063', normal, compile, ['']) +test('read064', normal, compile, ['']) +test('read066', normal, compile, ['']) +test('read067', normal, compile, ['']) +test('read068', normal, compile, ['']) +test('read069', normal, compile, ['']) +test('read_1821', normal, compile, ['']) +test('T2245', normal, compile, ['-fwarn-type-defaults']) +test('T3303', extra_clean(['T3303A.hi', 'T3303A.o']), + multimod_compile, ['T3303', '-v0']) +test('T3741', normal, compile, ['']) +test('DoAndIfThenElse', normal, compile, ['']) +test('NondecreasingIndentation', normal, compile, ['']) +test('mc15', normal, compile, ['']) +test('mc16', normal, compile, ['']) +test('EmptyDecls', normal, compile, ['']) + +test('T5243', normal, multimod_compile, ['T5243','']) diff --git a/testsuite/tests/parser/should_compile/mc15.hs b/testsuite/tests/parser/should_compile/mc15.hs new file mode 100644 index 0000000000..2976694803 --- /dev/null +++ b/testsuite/tests/parser/should_compile/mc15.hs @@ -0,0 +1,13 @@ + +{-# LANGUAGE MonadComprehensions, ParallelListComp #-} + +module Foo where + +import Control.Monad.Zip + +foo :: (MonadZip m, Monad m) => m () +foo = [ () + | () <- foo + | () <- foo + ] + diff --git a/testsuite/tests/parser/should_compile/mc16.hs b/testsuite/tests/parser/should_compile/mc16.hs new file mode 100644 index 0000000000..3f80c04abb --- /dev/null +++ b/testsuite/tests/parser/should_compile/mc16.hs @@ -0,0 +1,16 @@ +{-# OPTIONS_GHC -XMonadComprehensions -XTransformListComp #-} + +module Foo where + +import Data.List +import GHC.Exts + +foo = [ () + | x <- [1..10] + , then take 5 + , then sortWith by x + , then group by x + , then group using inits + , then group by x using groupWith + ] + diff --git a/testsuite/tests/parser/should_compile/read001.hs b/testsuite/tests/parser/should_compile/read001.hs new file mode 100644 index 0000000000..d0a84ff7e5 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read001.hs @@ -0,0 +1,8 @@ +-- !!! import qualified Prelude should leave (), [] etc in scope + +module ShouldCompile where + +import qualified Prelude + +f :: Prelude.IO () +f = Prelude.return () diff --git a/testsuite/tests/parser/should_compile/read002.hs b/testsuite/tests/parser/should_compile/read002.hs new file mode 100644 index 0000000000..5b069fe2c6 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read002.hs @@ -0,0 +1,14 @@ +-- !!! tests fixity reading and printing +module ShouldCompile where + +infixl 1 `f` +infixr 2 \\\ +infix 3 :==> +infix 4 `MkFoo` + +data Foo = MkFoo Int | Float :==> Double + +x `f` y = x + +(\\\) :: (Eq a) => [a] -> [a] -> [a] +(\\\) xs ys = xs diff --git a/testsuite/tests/parser/should_compile/read002.stderr b/testsuite/tests/parser/should_compile/read002.stderr new file mode 100644 index 0000000000..e69de29bb2 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read002.stderr diff --git a/testsuite/tests/parser/should_compile/read003.hs b/testsuite/tests/parser/should_compile/read003.hs new file mode 100644 index 0000000000..afc3a21007 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read003.hs @@ -0,0 +1,20 @@ +-- !!! Testing layout rule +module ShouldCompile where + +l1 :: IO () +l1 = do + return a + where + a = () + +l2 :: IO () +l2 = do + return a + where + a = () + +l3 :: IO () +l3 = do + return a + where + a = () diff --git a/testsuite/tests/parser/should_compile/read004.hs b/testsuite/tests/parser/should_compile/read004.hs new file mode 100644 index 0000000000..0741d0cd92 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read004.hs @@ -0,0 +1,16 @@ +module ShouldCompile where + +{- +From: Kevin Hammond <kh> +To: partain +Subject: Re: parsing problem w/ queens +Date: Wed, 9 Oct 91 17:31:46 BST + +OK, I've fixed that little problem by disallowing, +-} + +f x = x + if True then 1 else 2 +g x = x + 1::Int + +-- (the conditional/sig need to be parenthesised). If this is +-- problematic, let me know! diff --git a/testsuite/tests/parser/should_compile/read005.hs b/testsuite/tests/parser/should_compile/read005.hs new file mode 100644 index 0000000000..6e2c575902 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read005.hs @@ -0,0 +1,4 @@ +module ShouldCompile where + +-- !!! Empty comments terminating a file.. +main = print "Hello" -- diff --git a/testsuite/tests/parser/should_compile/read007.stderr b/testsuite/tests/parser/should_compile/read007.stderr new file mode 100644 index 0000000000..e69de29bb2 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read007.stderr diff --git a/testsuite/tests/parser/should_compile/read008.hs b/testsuite/tests/parser/should_compile/read008.hs new file mode 100644 index 0000000000..20060b0c4d --- /dev/null +++ b/testsuite/tests/parser/should_compile/read008.hs @@ -0,0 +1,4 @@ +module ShouldCompile where + +{-# SPECIALISE f :: Int -> Int #-} +f n = n + 1 diff --git a/testsuite/tests/parser/should_compile/read009.hs b/testsuite/tests/parser/should_compile/read009.hs new file mode 100644 index 0000000000..5294012de1 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read009.hs @@ -0,0 +1,7 @@ +-- !!! combining undeclared infix operators +module ShouldCompile where + +-- should default to 'infixl 9' + +test = let f x y = x+y in 1 `f` 2 `f` 3 + diff --git a/testsuite/tests/parser/should_compile/read010.hs b/testsuite/tests/parser/should_compile/read010.hs new file mode 100644 index 0000000000..d20f5fcc86 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read010.hs @@ -0,0 +1,4 @@ +-- !!! Infix record constructor. +module ShouldCompile where + +data Rec = (:<-:) { a :: Int, b :: Float } diff --git a/testsuite/tests/parser/should_compile/read010.stderr b/testsuite/tests/parser/should_compile/read010.stderr new file mode 100644 index 0000000000..e69de29bb2 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read010.stderr diff --git a/testsuite/tests/parser/should_compile/read011.hs b/testsuite/tests/parser/should_compile/read011.hs new file mode 100644 index 0000000000..7e20d468f0 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read011.hs @@ -0,0 +1,24 @@ +-- !!! do & where interaction +module ShouldCompile where + +f1 :: IO a -> IO [a] +f1 x = do + v <- x + return [v] + where + g x = [x,x] + +f2 :: IO a -> IO [a] +f2 x = do + v <- x + return (g v) + where + g x = [x,x] + +f3 :: IO a -> IO [a] +f3 x = do + v <- x + return (g v) + where + g x = [x,x] + diff --git a/testsuite/tests/parser/should_compile/read014.hs b/testsuite/tests/parser/should_compile/read014.hs new file mode 100644 index 0000000000..55fc053a8b --- /dev/null +++ b/testsuite/tests/parser/should_compile/read014.hs @@ -0,0 +1,8 @@ +-- !!! Empty export lists are legal (and useful.) +module ShouldCompile () where + +ng1 x y = negate y + +instance (Num a, Num b) => Num (a,b) + where + negate (a,b) = (ng 'c' a, ng1 'c' b) where ng x y = negate y diff --git a/testsuite/tests/parser/should_compile/read014.stderr-ghc b/testsuite/tests/parser/should_compile/read014.stderr-ghc new file mode 100644 index 0000000000..85f36b16da --- /dev/null +++ b/testsuite/tests/parser/should_compile/read014.stderr-ghc @@ -0,0 +1,28 @@ +
+read014.hs:4:1:
+ Warning: Top-level binding with no type signature:
+ ng1 :: forall t a. Num a => t -> a -> a
+
+read014.hs:4:5: Warning: Defined but not used: `x'
+
+read014.hs:6:10:
+ Warning: No explicit method nor default method for `+'
+ In the instance declaration for `Num (a, b)'
+
+read014.hs:6:10:
+ Warning: No explicit method nor default method for `*'
+ In the instance declaration for `Num (a, b)'
+
+read014.hs:6:10:
+ Warning: No explicit method nor default method for `abs'
+ In the instance declaration for `Num (a, b)'
+
+read014.hs:6:10:
+ Warning: No explicit method nor default method for `signum'
+ In the instance declaration for `Num (a, b)'
+
+read014.hs:6:10:
+ Warning: No explicit method nor default method for `fromInteger'
+ In the instance declaration for `Num (a, b)'
+
+read014.hs:8:53: Warning: Defined but not used: `x'
diff --git a/testsuite/tests/parser/should_compile/read015.hs b/testsuite/tests/parser/should_compile/read015.hs new file mode 100644 index 0000000000..7ba6140662 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read015.hs @@ -0,0 +1,2 @@ +-- !!! Testing whether the parser likes empty declarations.. +module ShouldCompile where { ;;;;;x=let{;;;;;y=2;;;;}in y;;;;;} diff --git a/testsuite/tests/parser/should_compile/read016.hs b/testsuite/tests/parser/should_compile/read016.hs new file mode 100644 index 0000000000..5c482f510d --- /dev/null +++ b/testsuite/tests/parser/should_compile/read016.hs @@ -0,0 +1,10 @@ +-- !!! Checking that both import lists and 'hiding' lists might +-- !!! be empty. +module ShouldCompile where + +import Data.List () +import Data.List hiding () + +x :: Int +x = 1 + diff --git a/testsuite/tests/parser/should_compile/read017.hs b/testsuite/tests/parser/should_compile/read017.hs new file mode 100644 index 0000000000..4349cb27ca --- /dev/null +++ b/testsuite/tests/parser/should_compile/read017.hs @@ -0,0 +1,15 @@ +-- !!! Checking that empty declarations are permitted. +module ShouldCompile where + + +class Foo a where + +class Foz a + +x = 2 where +y = 3 + +instance Foo Int where + +f = f where g = g where +type T = Int diff --git a/testsuite/tests/parser/should_compile/read018.hs b/testsuite/tests/parser/should_compile/read018.hs new file mode 100644 index 0000000000..91eef518be --- /dev/null +++ b/testsuite/tests/parser/should_compile/read018.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE DatatypeContexts #-} +-- !!! Checking that empty contexts are permitted. +module ShouldCompile where + +data () => Foo a = Foo a + +newtype () => Bar = Bar Int + +f :: () => Int -> Int +f = (+1) + + +class () => Fob a where + +instance () => Fob Int where +instance () => Fob Float + diff --git a/testsuite/tests/parser/should_compile/read018.stderr b/testsuite/tests/parser/should_compile/read018.stderr new file mode 100644 index 0000000000..30d1315840 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read018.stderr @@ -0,0 +1,3 @@ + +read018.hs:1:14: + Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. diff --git a/testsuite/tests/parser/should_compile/read019.hs b/testsuite/tests/parser/should_compile/read019.hs new file mode 100644 index 0000000000..3de6a9b71d --- /dev/null +++ b/testsuite/tests/parser/should_compile/read019.hs @@ -0,0 +1,10 @@ +-- !!! Checking what's legal in the body of a class declaration. +module ShouldCompile where + +class Foo a where { + (--<>--) :: a -> a -> Int ; + infixl 5 --<>-- ; + (--<>--) _ _ = 2 ; -- empty decl at the end. +}; + + diff --git a/testsuite/tests/parser/should_compile/read021.hs b/testsuite/tests/parser/should_compile/read021.hs new file mode 100644 index 0000000000..8d5856e9b6 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read021.hs @@ -0,0 +1,6 @@ +-- !!! Empty export list + +module ShouldCompile() where + +instance Show (a->b) where + show f = "<<function>>" diff --git a/testsuite/tests/parser/should_compile/read022.hs b/testsuite/tests/parser/should_compile/read022.hs new file mode 100644 index 0000000000..4ab04cabb8 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read022.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE ScopedTypeVariables #-} +module ShouldCompile where + +f (x :: Int) = x + 1 diff --git a/testsuite/tests/parser/should_compile/read023.hs b/testsuite/tests/parser/should_compile/read023.hs new file mode 100644 index 0000000000..3410afe946 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read023.hs @@ -0,0 +1,23 @@ +module ShouldCompile where + +-- M.<keyword> isn't a qualified identifier +f = Just.let x=id in x + +-- --------------------------------------------------------------------------- +-- we changed the behaviour of this one in GHC, but the following test +-- is strictly speaking legal Haskell: + +-- f' = Just.\1 where (.\) = ($) + +-- ----------------------------------------------------- +-- M.{as,hiding,qualified} *are* qualified identifiers: + +g = ShouldCompile.as + +-- --------------------------------------------------------------------------- +-- special symbols (!, -) can be qualified to make varids. + +g' = (ShouldCompile.!) + +as x = x +(!) x = x diff --git a/testsuite/tests/parser/should_compile/read024.hs b/testsuite/tests/parser/should_compile/read024.hs new file mode 100644 index 0000000000..f00ddb002c --- /dev/null +++ b/testsuite/tests/parser/should_compile/read024.hs @@ -0,0 +1,33 @@ +-- !!! checking that special ids are correctly handled. +module ShouldCompile where + +as :: [as] +as = [head as] + +qualified :: [qualified] +qualified = [head qualified] + +hiding :: [hiding] +hiding = [head hiding] + +export :: [export] +export = [head export] + +label :: [label] +label = [head label] + +dynamic :: [dynamic] +dynamic = [head dynamic] + +unsafe :: [unsafe] +unsafe = [head unsafe] + +interruptible :: [interruptible] +interruptible = [head interruptible] + +stdcall :: [stdcall] +stdcall = [head stdcall] + +ccall :: [ccall] +ccall = [head ccall] + diff --git a/testsuite/tests/parser/should_compile/read025.hs b/testsuite/tests/parser/should_compile/read025.hs new file mode 100644 index 0000000000..7eca04e85c --- /dev/null +++ b/testsuite/tests/parser/should_compile/read025.hs @@ -0,0 +1,9 @@ +-- !!! Check the handling of 'qualified' and 'as' clauses +module ShouldCompile where + +import Data.List as L ( intersperse ) + +x = L.intersperse + +y = intersperse + diff --git a/testsuite/tests/parser/should_compile/read026.hs b/testsuite/tests/parser/should_compile/read026.hs new file mode 100644 index 0000000000..0ea695d373 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read026.hs @@ -0,0 +1,6 @@ +module ShouldCompile where + +(<>) :: (a -> Maybe b) -> (b -> Maybe c) -> (a -> Maybe c) +(m1 <> m2) a1 = case m1 a1 of + Nothing -> Nothing + Just a2 -> m2 a2 diff --git a/testsuite/tests/parser/should_compile/read027.hs b/testsuite/tests/parser/should_compile/read027.hs new file mode 100644 index 0000000000..a6893450f8 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read027.hs @@ -0,0 +1,14 @@ +module ShouldCompile where + +infix 5 |- +infix 9 := + +data Equal = Char := Int + +-- fails in GHC (all versions), due to not doing fixity resolution on +-- the lhs before deciding which is the function symbol. + +(|-) :: Int -> Equal -> Bool +0 |- x:=y = 1 |- x:=y -- XXX fails here +2 |- (x:=y) = 0 |- x:=y +_ |- _ = False diff --git a/testsuite/tests/parser/should_compile/read028.hs b/testsuite/tests/parser/should_compile/read028.hs new file mode 100644 index 0000000000..1f193a4584 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read028.hs @@ -0,0 +1,3 @@ +module ShouldCompile where + +data T a b = (:^:) a b diff --git a/testsuite/tests/parser/should_compile/read029.hs b/testsuite/tests/parser/should_compile/read029.hs new file mode 100644 index 0000000000..1a9e5c1c9e --- /dev/null +++ b/testsuite/tests/parser/should_compile/read029.hs @@ -0,0 +1,14 @@ +-- !!! Special Ids and ops + +-- The special ids 'as', 'qualified' and 'hiding' should be +-- OK in both qualified and unqualified form. +-- Ditto special ops + +module ShouldCompile where +import Prelude hiding ( (-) ) + +as = ShouldCompile.as +hiding = ShouldCompile.hiding +qualified = ShouldCompile.qualified +x!y = x ShouldCompile.! y +x-y = x ShouldCompile.- y diff --git a/testsuite/tests/parser/should_compile/read030.hs b/testsuite/tests/parser/should_compile/read030.hs new file mode 100644 index 0000000000..26883024ee --- /dev/null +++ b/testsuite/tests/parser/should_compile/read030.hs @@ -0,0 +1,10 @@ +-- !!! Infix decls w/ infix data constructors + +-- GHC used to barf on this... + +module ShouldCompile where + +infix 2 |-, |+ + +ps |- q:qs = undefined +ps |+ p:q:qs = undefined diff --git a/testsuite/tests/parser/should_compile/read031.hs b/testsuite/tests/parser/should_compile/read031.hs new file mode 100644 index 0000000000..d19f120ffd --- /dev/null +++ b/testsuite/tests/parser/should_compile/read031.hs @@ -0,0 +1,10 @@ +-- !!! "--" can start a legal lexeme + +module ShouldCompile where + +infix 2 --+, --> + +ps --> True = True + +(--+) a b = a && b + diff --git a/testsuite/tests/parser/should_compile/read032.hs b/testsuite/tests/parser/should_compile/read032.hs new file mode 100644 index 0000000000..634f6b5fa9 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read032.hs @@ -0,0 +1,4 @@ +module ShouldCompile where + +-- !!! Record declarations with zero fields are allowed +data Foo = Foo{} diff --git a/testsuite/tests/parser/should_compile/read033.hs b/testsuite/tests/parser/should_compile/read033.hs new file mode 100644 index 0000000000..2c8faf0343 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read033.hs @@ -0,0 +1,3 @@ +module ShouldCompile where + +x = const 1.0e+x where e = 3 diff --git a/testsuite/tests/parser/should_compile/read034.hs b/testsuite/tests/parser/should_compile/read034.hs new file mode 100644 index 0000000000..4fa7152f40 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read034.hs @@ -0,0 +1,12 @@ +module ShouldCompile where + +-- !!! Section precedences + +-- infixl 6 +, - +-- infixr 5 ++, : + +f = (++ [] ++ []) +g = (3 + 4 +) + +-- prefix negation is like infixl 6. +h x = (-x -) diff --git a/testsuite/tests/parser/should_compile/read036.hs b/testsuite/tests/parser/should_compile/read036.hs new file mode 100644 index 0000000000..81485f5a0f --- /dev/null +++ b/testsuite/tests/parser/should_compile/read036.hs @@ -0,0 +1,4 @@ +module ShouldCompile where + +f :: Double +f = 42e42 -- this should be a float diff --git a/testsuite/tests/parser/should_compile/read037.hs b/testsuite/tests/parser/should_compile/read037.hs new file mode 100644 index 0000000000..a9f822cc03 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read037.hs @@ -0,0 +1,6 @@ +module ShouldCompile where + +-- This file contains several non-breaking space characters, +-- aka '\xa0'. The compiler should recognise these as whitespace. + +f = ( + ) diff --git a/testsuite/tests/parser/should_compile/read038.hs b/testsuite/tests/parser/should_compile/read038.hs new file mode 100644 index 0000000000..30e20774fa --- /dev/null +++ b/testsuite/tests/parser/should_compile/read038.hs @@ -0,0 +1,5 @@ +module ShouldCompile where +a ---> b = a + a +foo = 3 + ---> 4 + ---> 5 diff --git a/testsuite/tests/parser/should_compile/read039.hs b/testsuite/tests/parser/should_compile/read039.hs new file mode 100644 index 0000000000..032c64f624 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read039.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE ForeignFunctionInterface, CPP #-} +-- Test the LANGUAGE pragma +module ShouldCompile where + +#if 1 +foreign import ccall "foo" foo :: Int -> IO Int +#endif diff --git a/testsuite/tests/parser/should_compile/read040.hs b/testsuite/tests/parser/should_compile/read040.hs new file mode 100644 index 0000000000..e6d6629744 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read040.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE ScopedTypeVariables #-} +-- A type signature on the LHS of a do-stmt was a parse +-- error in 6.4.2, but ok thereafter + +module ShouldCompile where + +f () = do { x :: Bool <- return True + ; return x } diff --git a/testsuite/tests/parser/should_compile/read041.lhs b/testsuite/tests/parser/should_compile/read041.lhs new file mode 100644 index 0000000000..30274e85a1 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read041.lhs @@ -0,0 +1,10 @@ +-- Tests trac #210. + +module ShouldCompile where + +\begin{code} + main = foo +\end{code} + +> foo = putStrLn "Foo" + diff --git a/testsuite/tests/parser/should_compile/read042.hs b/testsuite/tests/parser/should_compile/read042.hs new file mode 100644 index 0000000000..922b7b12bb --- /dev/null +++ b/testsuite/tests/parser/should_compile/read042.hs @@ -0,0 +1,29 @@ +{-# OPTIONS -XBangPatterns #-} + +-- Various bang-pattern and lazy-pattern tests + +module ShouldCompile where + +main1,main2,main3,main4,main5,main6,main7 :: IO () + +main1 = do + !c <- return () + return () + +main2 = return () >>= \ !c -> return () + +main3 = do + (!c) <- return () + return () + +main4 = return () >>= \ (!c) -> return () + +main5 = let !x = 1 in return () + +main6 = do + ~c <- return () + return () + +main7 = return () >>= \ ~c -> return () + + diff --git a/testsuite/tests/parser/should_compile/read043.hs b/testsuite/tests/parser/should_compile/read043.hs new file mode 100644 index 0000000000..c663a7526e --- /dev/null +++ b/testsuite/tests/parser/should_compile/read043.hs @@ -0,0 +1,11 @@ + +{-# OPTIONS -fwarn-tabs #-} + +-- Check we get a warning for tabs + +module ShouldCompile where + +tab1 = 'a' +notab = 'b' +tab2 = 'c' + diff --git a/testsuite/tests/parser/should_compile/read043.stderr b/testsuite/tests/parser/should_compile/read043.stderr new file mode 100644 index 0000000000..dc1e84466a --- /dev/null +++ b/testsuite/tests/parser/should_compile/read043.stderr @@ -0,0 +1,4 @@ + +read043.hs:8:5: Warning: Tab character + +read043.hs:10:5: Warning: Tab character diff --git a/testsuite/tests/parser/should_compile/read044.hs b/testsuite/tests/parser/should_compile/read044.hs new file mode 100644 index 0000000000..a92b48c298 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read044.hs @@ -0,0 +1,5 @@ +-- test case from #1091 +main = + case True of {- | -} + True -> putStrLn "Hello World\n" + False {- | -} -> putStrLn "Goodbye Cruel World\n" diff --git a/testsuite/tests/parser/should_compile/read045.hs b/testsuite/tests/parser/should_compile/read045.hs new file mode 100644 index 0000000000..844acdfc82 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read045.hs @@ -0,0 +1,4 @@ +{ +main = +putStr "hello"; +} diff --git a/testsuite/tests/parser/should_compile/read046.hs b/testsuite/tests/parser/should_compile/read046.hs new file mode 100644 index 0000000000..5cc602f5a4 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read046.hs @@ -0,0 +1,7 @@ + +{-# OPTIONS_GHC -XMagicHash #-} + +module Foo where + +foo# = 'a' + diff --git a/testsuite/tests/parser/should_compile/read047.hs b/testsuite/tests/parser/should_compile/read047.hs new file mode 100644 index 0000000000..0c7470156d --- /dev/null +++ b/testsuite/tests/parser/should_compile/read047.hs @@ -0,0 +1,7 @@ + +{-# LANGUAGE MagicHash #-} + +module Foo where + +foo# = 'a' + diff --git a/testsuite/tests/parser/should_compile/read048.hs b/testsuite/tests/parser/should_compile/read048.hs new file mode 100644 index 0000000000..cd8c974af6 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read048.hs @@ -0,0 +1,7 @@ + +{-# OPTIONS_GHC -XEmptyDataDecls #-} + +module Foo where + +data Foo + diff --git a/testsuite/tests/parser/should_compile/read049.hs b/testsuite/tests/parser/should_compile/read049.hs new file mode 100644 index 0000000000..8337a79634 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read049.hs @@ -0,0 +1,7 @@ + +{-# LANGUAGE EmptyDataDecls #-} + +module Foo where + +data Foo + diff --git a/testsuite/tests/parser/should_compile/read050.hs b/testsuite/tests/parser/should_compile/read050.hs new file mode 100644 index 0000000000..d991bb01c7 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read050.hs @@ -0,0 +1,7 @@ + +{-# OPTIONS_GHC -XKindSignatures #-} + +module Foo where + +data Foo (a :: *) = Foo a + diff --git a/testsuite/tests/parser/should_compile/read051.hs b/testsuite/tests/parser/should_compile/read051.hs new file mode 100644 index 0000000000..3e95241862 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read051.hs @@ -0,0 +1,7 @@ + +{-# LANGUAGE KindSignatures #-} + +module Foo where + +data Foo (a :: *) = Foo a + diff --git a/testsuite/tests/parser/should_compile/read052.hs b/testsuite/tests/parser/should_compile/read052.hs new file mode 100644 index 0000000000..8c65e62a1b --- /dev/null +++ b/testsuite/tests/parser/should_compile/read052.hs @@ -0,0 +1,7 @@ + +{-# OPTIONS_GHC -XMultiParamTypeClasses #-} + +module Foo where + +class Foo a b + diff --git a/testsuite/tests/parser/should_compile/read053.hs b/testsuite/tests/parser/should_compile/read053.hs new file mode 100644 index 0000000000..a277f31257 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read053.hs @@ -0,0 +1,7 @@ + +{-# LANGUAGE MultiParamTypeClasses #-} + +module Foo where + +class Foo a b + diff --git a/testsuite/tests/parser/should_compile/read054.hs b/testsuite/tests/parser/should_compile/read054.hs new file mode 100644 index 0000000000..4e0c589bf3 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read054.hs @@ -0,0 +1,10 @@ + +{-# OPTIONS_GHC -XParallelListComp #-} + +module Foo where + +foo = [ () + | () <- foo + | () <- foo + ] + diff --git a/testsuite/tests/parser/should_compile/read055.hs b/testsuite/tests/parser/should_compile/read055.hs new file mode 100644 index 0000000000..25db332a4d --- /dev/null +++ b/testsuite/tests/parser/should_compile/read055.hs @@ -0,0 +1,10 @@ + +{-# LANGUAGE ParallelListComp #-} + +module Foo where + +foo = [ () + | () <- foo + | () <- foo + ] + diff --git a/testsuite/tests/parser/should_compile/read056.hs b/testsuite/tests/parser/should_compile/read056.hs new file mode 100644 index 0000000000..bab900ad6a --- /dev/null +++ b/testsuite/tests/parser/should_compile/read056.hs @@ -0,0 +1,11 @@ + +{-# OPTIONS_GHC -XGeneralizedNewtypeDeriving #-} + +module Foo where + +class C a +instance C Int + +newtype Foo = Foo Int + deriving C + diff --git a/testsuite/tests/parser/should_compile/read057.hs b/testsuite/tests/parser/should_compile/read057.hs new file mode 100644 index 0000000000..f2cf84b3b5 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read057.hs @@ -0,0 +1,11 @@ + +{-# LANGUAGE GeneralizedNewtypeDeriving #-} + +module Foo where + +class C a +instance C Int + +newtype Foo = Foo Int + deriving C + diff --git a/testsuite/tests/parser/should_compile/read058.hs b/testsuite/tests/parser/should_compile/read058.hs new file mode 100644 index 0000000000..9d4f766ada --- /dev/null +++ b/testsuite/tests/parser/should_compile/read058.hs @@ -0,0 +1,11 @@ + +{-# OPTIONS_GHC -XRecursiveDo #-} + +module Foo where + +import Control.Monad.Fix + +z :: Maybe [Int] +z = mdo x <- return (1:x) + return (take 4 x) + diff --git a/testsuite/tests/parser/should_compile/read058.stderr b/testsuite/tests/parser/should_compile/read058.stderr new file mode 100644 index 0000000000..aa42286c89 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read058.stderr @@ -0,0 +1,3 @@ + +read058.hs:2:16: + Warning: -XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead diff --git a/testsuite/tests/parser/should_compile/read059.hs b/testsuite/tests/parser/should_compile/read059.hs new file mode 100644 index 0000000000..79989afd3f --- /dev/null +++ b/testsuite/tests/parser/should_compile/read059.hs @@ -0,0 +1,11 @@ + +{-# LANGUAGE RecursiveDo #-} + +module Foo where + +import Control.Monad.Fix + +z :: Maybe [Int] +z = mdo x <- return (1:x) + return (take 4 x) + diff --git a/testsuite/tests/parser/should_compile/read059.stderr b/testsuite/tests/parser/should_compile/read059.stderr new file mode 100644 index 0000000000..5d2ae6c397 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read059.stderr @@ -0,0 +1,3 @@ + +read059.hs:2:14: + Warning: -XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead diff --git a/testsuite/tests/parser/should_compile/read060.hs b/testsuite/tests/parser/should_compile/read060.hs new file mode 100644 index 0000000000..1b07dfa397 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read060.hs @@ -0,0 +1,8 @@ + +{-# OPTIONS_GHC -XFunctionalDependencies #-} +{-# OPTIONS_GHC -XMultiParamTypeClasses #-} + +module Foo where + +class Foo a b | a -> b + diff --git a/testsuite/tests/parser/should_compile/read061.hs b/testsuite/tests/parser/should_compile/read061.hs new file mode 100644 index 0000000000..1820e460f3 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read061.hs @@ -0,0 +1,8 @@ + +{-# LANGUAGE FunctionalDependencies #-} +{-# OPTIONS_GHC -XMultiParamTypeClasses #-} + +module Foo where + +class Foo a b | a -> b + diff --git a/testsuite/tests/parser/should_compile/read062.hs b/testsuite/tests/parser/should_compile/read062.hs new file mode 100644 index 0000000000..4d57585c10 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read062.hs @@ -0,0 +1,16 @@ +{-# OPTIONS_GHC -XTransformListComp #-}
+
+module Foo where
+
+import Data.List
+import GHC.Exts
+
+foo = [ ()
+ | x <- [1..10]
+ , then take 5
+ , then sortWith by x
+ , then group by x
+ , then group using inits
+ , then group by x using groupWith
+ ]
+
diff --git a/testsuite/tests/parser/should_compile/read063.hs b/testsuite/tests/parser/should_compile/read063.hs new file mode 100644 index 0000000000..faa7c4a4a5 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read063.hs @@ -0,0 +1,51 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} + +--module Foo where + +import GHC.Exts + +--you can use this if you want to test running it... +main = print (I# ( + f1pat 1# +# f1prepat 1# + +# f2pat 1# +# f2prepat 1# + +# f3pat 1# +# f3prepat 1# + )) + +--unboxed tuples are of sizes 1,2,3... +--(normal tuples are 0,2,3...) + +--make sure it's really the _unboxed_ tuples +--being used by putting unboxed values in, +--which are forbidden in boxed tuples + +f1 :: Int# -> (# Int# #) +f1 i = (# i #) +-- a space is needed in (# #) so that it's not +-- lexed/parsed as an operator named "##" +--(even though the error message about mismatched +--kinds for "instance Functor (# #)" names the type +--as "(##)" +-- Kind mis-match +-- Expected kind `* -> *', but `(##)' has kind `? -> (#)' +-- In the instance declaration for `Functor (##)' +f1prefix :: Int# -> (# #) Int# +f1prefix i = (# #) i +--test that prefix and non-prefix versions +--are the same type by switching the case-argument +f1pat a = case f1prefix a of (# i #) -> i +# 1# +f1prepat a = case f1 a of (# #) i -> i +# 1# + +f2 :: Int# -> (# Int#, Int# #) +f2 i = (# i, i #) +f2prefix :: Int# -> (#,#) Int# Int# +f2prefix i = (#,#) i i +f2pat a = case f2prefix a of (# i, j #) -> i +# j +f2prepat a = case f2 a of (#,#) i j -> i +# j + +f3 :: Int# -> (# Int#, Int#, Int# #) +f3 i = (# i, i, i #) +f3prefix :: Int# -> (#,,#) Int# Int# Int# +f3prefix i = (#,,#) i i i +f3pat a = case f3prefix a of (# i, j, k #) -> i +# j +# k +f3prepat a = case f3 a of (#,,#) i j k -> i +# j +# k + diff --git a/testsuite/tests/parser/should_compile/read064.hs b/testsuite/tests/parser/should_compile/read064.hs new file mode 100644 index 0000000000..386574244f --- /dev/null +++ b/testsuite/tests/parser/should_compile/read064.hs @@ -0,0 +1,7 @@ + +module Foo where + +{-# THISISATYPO foo #-} +foo :: () +foo = () + diff --git a/testsuite/tests/parser/should_compile/read064.stderr b/testsuite/tests/parser/should_compile/read064.stderr new file mode 100644 index 0000000000..8ed04fc629 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read064.stderr @@ -0,0 +1,2 @@ + +read064.hs:4:1: Unrecognised pragma diff --git a/testsuite/tests/parser/should_compile/read066.hs b/testsuite/tests/parser/should_compile/read066.hs new file mode 100644 index 0000000000..374f76126c --- /dev/null +++ b/testsuite/tests/parser/should_compile/read066.hs @@ -0,0 +1,8 @@ + +{-# OPTIONS_NO_SUCH_PRAGMA --no-such-flag #-} + +-- We should parse the above as an unrecognised pragma, not as an OPTIONS +-- pragma containing "_NO_SUCH_PRAGMA -wibble". Trac #2847. + +module Test where + diff --git a/testsuite/tests/parser/should_compile/read066.stderr b/testsuite/tests/parser/should_compile/read066.stderr new file mode 100644 index 0000000000..a094133754 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read066.stderr @@ -0,0 +1,2 @@ + +read066.hs:2:1: Unrecognised pragma diff --git a/testsuite/tests/parser/should_compile/read067.hs b/testsuite/tests/parser/should_compile/read067.hs new file mode 100644 index 0000000000..f65f56b498 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read067.hs @@ -0,0 +1,8 @@ + +{-# OPTIONS_HUGS --some-hugs-flag #-} + +-- We should ignore the above pragma, as we recognise that it is +-- hugs-specific. We shouldn't even warn about it. + +module Test where + diff --git a/testsuite/tests/parser/should_compile/read068.hs b/testsuite/tests/parser/should_compile/read068.hs new file mode 100644 index 0000000000..b6cf24fd0c --- /dev/null +++ b/testsuite/tests/parser/should_compile/read068.hs @@ -0,0 +1,27 @@ +-- Test for trac #3079 - parsing fails if a LANGUAGE pragma straddles +-- a 1024 byte boundary. +-- xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +-- xxxxxxxxxxxxxxxxxxxxxxx +-- xxxxxxxxxxxxxxxxxxxxxxxxxxxxx +-- +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +-- +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx +-- +--xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx + +{-# LANGUAGE NoImplicitPrelude #-} + +import Prelude + +main :: IO () +main = return () + diff --git a/testsuite/tests/parser/should_compile/read069.hs b/testsuite/tests/parser/should_compile/read069.hs new file mode 100644 index 0000000000..cff74b474b --- /dev/null +++ b/testsuite/tests/parser/should_compile/read069.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE RelaxedLayout #-} + +module ShouldFail where + +f x = case x of + False -> do + { return x; } + diff --git a/testsuite/tests/parser/should_compile/read_1821.hs b/testsuite/tests/parser/should_compile/read_1821.hs new file mode 100644 index 0000000000..f9669ab053 --- /dev/null +++ b/testsuite/tests/parser/should_compile/read_1821.hs @@ -0,0 +1,10 @@ + +-- Trac #1821 + +module Par where + +f x = x + where +-- ######### x86_64 machine code: + g y = y + h y = y |