diff options
Diffstat (limited to 'ghc/compiler/tests/reader')
-rw-r--r-- | ghc/compiler/tests/reader/Jmakefile | 9 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/OneA.hi | 15 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/OneB.hi | 3 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/OneC.hi | 3 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/expr001.hs | 14 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/read001.hs | 113 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/read001.stderr | 593 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/read002.hs | 13 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/read002.stderr | 466 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/read003.hs | 5 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/read004.hs | 43 | ||||
-rw-r--r-- | ghc/compiler/tests/reader/read004.stderr | 0 |
12 files changed, 1277 insertions, 0 deletions
diff --git a/ghc/compiler/tests/reader/Jmakefile b/ghc/compiler/tests/reader/Jmakefile new file mode 100644 index 0000000000..60e7f91282 --- /dev/null +++ b/ghc/compiler/tests/reader/Jmakefile @@ -0,0 +1,9 @@ +runtests:: + @echo '###############################################################' + @echo '# Validation tests for the reader in the compiler. #' + @echo '###############################################################' + +RunStdTest(read001,$(GHC), -noC -ddump-rif2hs read001.hs -o2 read001.stderr) +RunStdTest(read002,$(GHC), -noC -ddump-rif2hs read002.hs -o2 read002.stderr) +/* gap 003 */ +RunStdTest(read004,$(GHC), -noC -fno-implicit-prelude -ddump-rif2hs read004.hs -o2 read004.stderr) diff --git a/ghc/compiler/tests/reader/OneA.hi b/ghc/compiler/tests/reader/OneA.hi new file mode 100644 index 0000000000..42ed194929 --- /dev/null +++ b/ghc/compiler/tests/reader/OneA.hi @@ -0,0 +1,15 @@ +interface OneA where + +import OneB ( fB ) renaming ( fB to fBa ) + +type SynA = Float + +data DataAA +data (Ord a) => DataAB a = ConAB1 a | ConAB2 deriving Text + +class (Ord a) => ClassA a where + clsA :: a -> String + +instance ClassA Int + +fA :: a -> a diff --git a/ghc/compiler/tests/reader/OneB.hi b/ghc/compiler/tests/reader/OneB.hi new file mode 100644 index 0000000000..78f55eee16 --- /dev/null +++ b/ghc/compiler/tests/reader/OneB.hi @@ -0,0 +1,3 @@ +interface OneB where + +fB :: a -> a diff --git a/ghc/compiler/tests/reader/OneC.hi b/ghc/compiler/tests/reader/OneC.hi new file mode 100644 index 0000000000..ded63ccf9e --- /dev/null +++ b/ghc/compiler/tests/reader/OneC.hi @@ -0,0 +1,3 @@ +interface OneC where + +fC :: a -> a diff --git a/ghc/compiler/tests/reader/expr001.hs b/ghc/compiler/tests/reader/expr001.hs new file mode 100644 index 0000000000..49853a74cf --- /dev/null +++ b/ghc/compiler/tests/reader/expr001.hs @@ -0,0 +1,14 @@ +{- +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 c then 1 else 2 +f x = x + 1::Int + +-- (the conditional/sig need to be parenthesised). If this is +-- problematic, let me know! diff --git a/ghc/compiler/tests/reader/read001.hs b/ghc/compiler/tests/reader/read001.hs new file mode 100644 index 0000000000..4a97768a78 --- /dev/null +++ b/ghc/compiler/tests/reader/read001.hs @@ -0,0 +1,113 @@ +-- this module supposedly includes one of each Haskell construct + +-- HsImpExp stuff + +module OneOfEverything ( + fixn, + FooData, + FooDataB(..), + FooDataC( .. ), + EqTree(EqLeaf, EqBranch), + EqClass(..), + OrdClass(orda, ordb), + OneC.. , + OneOfEverything.. + ) where + +import OneA renaming ( fA to renamedA ) +import OneB ( fB ) +import OneC hiding ( fC ) +import OneC hiding ( fC ) renaming ( fc to renamedC ) + +-- HsDecls stuff + +infix 6 `fixn` +infixl 7 +# +infixr 8 `fixr` + +fixn x y = x +fixl x y = x +fixr x y = x + +type Pair a b = (a, b) + +data FooData = FooCon Int + +data FooDataB = FooConB Double + +data (Eq a) => EqTree a = EqLeaf a | EqBranch (EqLeaf a) (EqLeaf a) + +class (Eq a) => EqClass a where + eqc :: a -> Char + eqc x = '?' + +class (Ord a) => OrdClass a where + orda :: a -> Char + ordb :: a -> Char + ordc :: a -> Char + +instance (Eq a) => EqClass (EqTree a) where + eqc x = 'a' + +default (Integer, Rational) + +-- HsBinds stuff + +singlebind x = x + +bindwith :: (OrdClass a, OrdClass b) => a -> b -> b +bindwith a b = b + +reca a = recb a +recb a = reca a + +(~(a,b,c)) | nullity b = a + | nullity c = a + | otherwise = a + where + nullity = null + +-- HsMatches stuff + +mat a b c d | foof a b = d + | foof a c = d + | foof b c = d + where + foof a b = a == b + +-- HsExpr stuff +expr a b c d + = a + + (:) a b + + (a : b) + + (1 - 'c' - "abc" - 1.293) + + ( \ x y z -> x ) 42 + + (9 *) + + (* 8) + + (case x of + [] | null x -> 99 + | otherwise -> 98 + | True -> 97 + where + null x = False + ) + + [ z | z <- c, isSpace z ] + + let y = foo + in y + + [1,2,3,4] + + (4,3,2,1) + + (4 :: Num a => a) + + (if 42 == 42.0 then 1 else 4) + + [1..] + + [2,4..] + + [3..5] + + [4,8..999] + +-- HsPat stuff +f _ x 1 1.93 'c' "dog" ~y z@(Foo a b) (c `Bar` d) [1,2] (3,4) (n+42) = y + +-- HsLit stuff -- done above + +-- HsTypes stuff +g :: (Num a, Eq b) => Foo a -> [b] -> (a,a,a) -> b +g x y z = head y diff --git a/ghc/compiler/tests/reader/read001.stderr b/ghc/compiler/tests/reader/read001.stderr new file mode 100644 index 0000000000..997116b7a5 --- /dev/null +++ b/ghc/compiler/tests/reader/read001.stderr @@ -0,0 +1,593 @@ +Parsed, Haskellised: +module OneOfEverything ( + fixn, + FooData, + FooDataB(..), + FooDataC(..), + EqTree(EqLeaf, EqBranch), + EqClass(..), + OrdClass(orda, ordb), + OneC.., + OneOfEverything.. + ) where +import Prelude {- + interface Prelude where + import PreludeBuiltin ( trace, Char ) + import PreludeCore ( Bool, String, ReadS, ShowS, Text ) + import PreludeRatio ( + %, numerator, denominator, approxRational ) + import PreludeComplex ( + realPart, + imagPart, + conjugate, + mkPolar, + cis, + polar, + magnitude, + phase ) + import PreludeList ( + head, + last, + tail, + init, + null, + \\, + genericLength, + length, + !!, + filter, + partition, + foldl1, + scanl, + scanl1, + foldr1, + scanr, + scanr1, + iterate, + repeat, + cycle, + take, + drop, + splitAt, + takeWhile, + dropWhile, + span, + break, + lines, + words, + unlines, + unwords, + nub, + reverse, + and, + or, + any, + all, + elem, + notElem, + sum, + product, + sums, + products, + maximum, + minimum, + concat, + transpose, + zip, + zip3, + zip4, + zip5, + zip6, + zip7, + zipWith, + zipWith3, + zipWith4, + zipWith5, + zipWith6, + zipWith7, + unzip, + unzip3, + unzip4, + unzip5, + unzip6, + unzip7 ) + import PreludeArray ( + array, + listArray, + !, + bounds, + indices, + elems, + assocs, + accumArray, + //, + accum, + amap, + ixmap ) + import PreludeText ( + reads, + shows, + show, + read, + showChar, + readLitChar, + showLitChar, + readSigned, + showSigned, + readDec, + showInt, + readFloat, + showFloat ) + import PreludeIO ( + stdin, + stdout, + stderr, + stdecho, + done, + readFile, + writeFile, + appendFile, + readBinFile, + writeBinFile, + appendBinFile, + deleteFile, + statusFile, + readChan, + appendChan, + readBinChan, + appendBinChan, + statusChan, + echo, + getArgs, + getProgName, + getEnv, + setEnv, + abort, + exit, + print, + prints, + interact ) + instance (Eq a, Eq b) => Eq (a, b) + instance (Ord a, Ord b) => Ord (a, b) + instance (Ix a, Ix b) => Ix (a, b) + instance (Text a, Text b) => Text (a, b) + instance (Binary a, Binary b) => Binary (a, b) + instance (Eq a, Eq b, Eq c) => Eq (a, b, c) + instance (Ord a, Ord b, Ord c) => Ord (a, b, c) + instance (Ix a, Ix b, Ix c) => Ix (a, b, c) + instance (Text a, Text b, Text c) => Text (a, b, c) + instance (Binary a, Binary b, Binary c) => Binary (a, b, c) + instance (Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) + instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) + instance (Ix a, Ix b, Ix c, Ix d) => Ix (a, b, c, d) + instance (Text a, Text b, Text c, Text d) => Text (a, b, c, d) + instance (Binary a, Binary b, Binary c, Binary d) => Binary (a, + b, + c, + d) + ^ :: (Num b, Integral a) => b -> a -> b + ^^ :: (Fractional b, Integral a) => b -> a -> b + appendBin :: Bin -> Bin -> Bin + asTypeOf :: a -> a -> a + atan2 :: RealFloat a => a -> a -> a + chr :: Int -> Char + fromIntegral :: (Integral a, Num b) => a -> b + fromRealFrac :: (RealFrac a, Fractional b) => a -> b + gcd :: Integral a => a -> a -> a + isAlpha :: Char -> Bool + isAlphanum :: Char -> Bool + isAscii :: Char -> Bool + isControl :: Char -> Bool + isDigit :: Char -> Bool + isLower :: Char -> Bool + isNullBin :: Bin -> Bool + isPrint :: Char -> Bool + isSpace :: Char -> Bool + isUpper :: Char -> Bool + lcm :: Integral a => a -> a -> a + maxChar :: Char + maxInt :: Int + minChar :: Char + minInt :: Int + nullBin :: Bin + ord :: Char -> Int + subtract :: Num a => a -> a -> a + toLower :: Char -> Char + toUpper :: Char -> Char + until :: (a -> Bool) -> (a -> a) -> a -> a + trace :: String -> a -> a + % :: Integral a => a -> a -> Ratio a + numerator :: Integral a => Ratio a -> a + denominator :: Integral a => Ratio a -> a + approxRational :: RealFrac a => a -> a -> Rational + cis :: RealFloat a => a -> Complex a + conjugate :: RealFloat a => Complex a -> Complex a + imagPart :: RealFloat a => Complex a -> a + magnitude :: RealFloat a => Complex a -> a + mkPolar :: RealFloat a => a -> a -> Complex a + phase :: RealFloat a => Complex a -> a + polar :: RealFloat a => Complex a -> (a, a) + realPart :: RealFloat a => Complex a -> a + !! :: Integral a => [b] -> a -> b + \\ :: Eq a => [a] -> [a] -> [a] + all :: (a -> Bool) -> [a] -> Bool + and :: [Bool] -> Bool + any :: (a -> Bool) -> [a] -> Bool + break :: (a -> Bool) -> [a] -> ([a], [a]) + concat :: [[a]] -> [a] + cycle :: [a] -> [a] + drop :: Integral a => a -> [b] -> [b] + dropWhile :: (a -> Bool) -> [a] -> [a] + elem :: Eq a => a -> [a] -> Bool + filter :: (a -> Bool) -> [a] -> [a] + foldl1 :: (a -> a -> a) -> [a] -> a + foldr1 :: (a -> a -> a) -> [a] -> a + genericLength :: Num b => [a] -> b + head :: [a] -> a + init :: [a] -> [a] + iterate :: (a -> a) -> a -> [a] + last :: [a] -> a + length :: [a] -> Int + lines :: [Char] -> [[Char]] + maximum :: Ord a => [a] -> a + minimum :: Ord a => [a] -> a + notElem :: Eq a => a -> [a] -> Bool + nub :: Eq a => [a] -> [a] + null :: [a] -> Bool + or :: [Bool] -> Bool + partition :: (a -> Bool) -> [a] -> ([a], [a]) + product :: Num a => [a] -> a + products :: Num a => [a] -> [a] + repeat :: a -> [a] + reverse :: [a] -> [a] + scanl :: (b -> a -> b) -> b -> [a] -> [b] + scanl1 :: (a -> a -> a) -> [a] -> [a] + scanr :: (a -> b -> b) -> b -> [a] -> [b] + scanr1 :: (a -> a -> a) -> [a] -> [a] + span :: (a -> Bool) -> [a] -> ([a], [a]) + splitAt :: Integral a => a -> [b] -> ([b], [b]) + sum :: Num a => [a] -> a + sums :: Num a => [a] -> [a] + tail :: [a] -> [a] + take :: Integral a => a -> [b] -> [b] + takeWhile :: (a -> Bool) -> [a] -> [a] + transpose :: [[a]] -> [[a]] + unlines :: [[Char]] -> [Char] + unwords :: [[Char]] -> [Char] + unzip :: [(a, b)] -> ([a], [b]) + unzip3 :: [(a, b, c)] -> ([a], [b], [c]) + unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) + unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e]) + unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) + unzip7 :: + [(a, b, c, d, e, f, g)] + -> ([a], [b], [c], [d], [e], [f], [g]) + words :: [Char] -> [[Char]] + zip :: [a] -> [b] -> [(a, b)] + zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] + zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)] + zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)] + zip6 :: + [a] + -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)] + zip7 :: + [a] + -> [b] + -> [c] + -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] + zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] + zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] + zipWith4 :: + (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] + zipWith5 :: + (a -> b -> c -> d -> e -> f) + -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] + zipWith6 :: + (a -> b -> c -> d -> e -> f -> g) + -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] + zipWith7 :: + (a -> b -> c -> d -> e -> f -> g -> h) + -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] + ! :: Ix a => Array a b -> a -> b + // :: Ix a => Array a b -> [Assoc a b] -> Array a b + accum :: + Ix b => (c -> a -> c) + -> Array b c -> [Assoc b a] -> Array b c + accumArray :: + Ix b => (c -> a -> c) + -> c -> (b, b) -> [Assoc b a] -> Array b c + amap :: Ix b => (a -> c) -> Array b a -> Array b c + array :: Ix a => (a, a) -> [Assoc a b] -> Array a b + assocs :: Ix a => Array a b -> [Assoc a b] + bounds :: Ix b => Array b a -> (b, b) + elems :: Ix a => Array a b -> [b] + indices :: Ix b => Array b a -> [b] + ixmap :: + (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c + listArray :: Ix a => (a, a) -> [b] -> Array a b + read :: Text a => [Char] -> a + readDec :: Integral a => [Char] -> [(a, [Char])] + readFloat :: RealFloat a => [Char] -> [(a, [Char])] + readLitChar :: [Char] -> [(Char, [Char])] + readSigned :: + Real a => ([Char] -> [(a, [Char])]) + -> [Char] -> [(a, [Char])] + reads :: Text a => [Char] -> [(a, [Char])] + show :: Text a => a -> [Char] + showChar :: Char -> [Char] -> [Char] + showFloat :: RealFloat a => a -> [Char] -> [Char] + showInt :: Integral a => a -> [Char] -> [Char] + showLitChar :: Char -> [Char] -> [Char] + showSigned :: + Real a => (a -> [Char] -> [Char]) + -> Int -> a -> [Char] -> [Char] + shows :: Text a => a -> [Char] -> [Char] + abort :: IOError -> [Response] -> [Request] + appendBinChan :: + [Char] + -> Bin + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + appendBinFile :: + [Char] + -> Bin + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + appendChan :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + appendFile :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + binDispatch :: + (IOError -> [Response] -> a) + -> (Bin -> [Response] -> a) -> [Response] -> a + deleteFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + done :: [Response] -> [Request] + echo :: + Bool + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + exit :: IOError -> [Response] -> [Request] + getArgs :: + (IOError -> [Response] -> [Request]) + -> ([[Char]] -> [Response] -> [Request]) + -> [Response] -> [Request] + getEnv :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + getProgName :: + (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + interact :: ([Char] -> [Char]) -> [Response] -> [Request] + print :: Text a => a -> [Response] -> [Request] + prints :: Text a => a -> [Char] -> [Response] -> [Request] + readBinChan :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> (Bin -> [Response] -> [Request]) + -> [Response] -> [Request] + readBinFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> (Bin -> [Response] -> [Request]) + -> [Response] -> [Request] + readChan :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + readFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + setEnv :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + statusChan :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + statusFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + stdecho :: [Char] + stderr :: [Char] + stdin :: [Char] + stdout :: [Char] + strDispatch :: + (IOError -> [Response] -> a) + -> ([Char] -> [Response] -> a) -> [Response] -> a + strListDispatch :: + (IOError -> [Response] -> a) + -> ([[Char]] -> [Response] -> a) -> [Response] -> a + succDispatch :: + (IOError -> [Response] -> a) + -> ([Response] -> a) -> [Response] -> a + writeBinFile :: + [Char] + -> Bin + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + writeFile :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + -} +import OneA {- + interface OneA where + import OneB ( fB ) renaming (fB to fBa) + type SynA = Float + data DataAA + data Ord a => DataAB a + = ConAB1 a + | ConAB2 + deriving (Text) + class Ord a => ClassA a where + clsA :: a -> String + instance ClassA Int + fA :: a -> a + -} +renaming (fA to renamedA) +import OneB {- + interface OneB where + fB :: a -> a + -} + (fB) +import OneC {- + interface OneC where + fC :: a -> a + -} + hiding (fC) +import OneC {- + interface OneC where + fC :: a -> a + -} + hiding (fC) +renaming (fc to renamedC) +infixr 9 . +infixr 8 ^ +infixr 8 ^^ +infixr 3 && +infixr 2 || +infixr 0 $ +infixl 9 ! +infixl 9 // +infix 1 := +infix 6 :+ +infixr 8 ** +infixl 7 * +infixl 7 / +infixl 7 `quot` +infixl 7 `rem` +infixl 7 `div` +infixl 7 `mod` +infixl 6 + +infixl 6 - +infix 4 == +infix 4 /= +infix 4 < +infix 4 <= +infix 4 >= +infix 4 > +infixl 9 !! +infix 5 \\ +infix 4 `elem` +infix 4 `notElem` +infixl 7 % +infix 6 `fixn` +infixl 7 +# +infixr 8 `fixr` +type Pair a b = (a, b) +data FooData + = FooCon Int +data FooDataB + = FooConB Double +data Eq a => EqTree a + = EqLeaf a + | EqBranch (EqLeaf a) (EqLeaf a) +class Eq a => EqClass a where + eqc :: a -> Char + eqc x = '?' +class Ord a => OrdClass a where + orda :: a -> Char + ordb :: a -> Char + ordc :: a -> Char +instance Eq a => EqClass EqTree a where + eqc x = 'a' +default (Integer, Rational) +bindwith :: (OrdClass a, OrdClass b) => a -> b -> b +g :: (Num a, Eq b) => Foo a -> [b] -> (a, a, a) -> b +{- rec -} +fixn x y = x +fixl x y = x +fixr x y = x +singlebind + x = x +bindwith + a b = b +reca a = recb a +recb a = reca a +~(a, b, c) + | nullity b = a + | nullity c = a + | otherwise = a + where + {- rec -} + nullity = null +mat a b c d | foof a b = d + | foof a c = d + | foof b c = d + where + {- rec -} + foof a b = a == b +expr a b c d = ((((((((a + ((:) a b)) + (a : b)) + + (((1 - 'c') - "abc") - 1.2929999999999999)) + + ((\ x y z -> x) 42)) + + ((9 *))) + + ((* 8))) + + (case x of + [] | null x -> 99 + | otherwise -> 98 + | True -> 97 + where + {- rec -} + null x = False)) + + ([ z | z <- c, isSpace z ])) + + (let + {- rec -} + y = foo + in (((((((y + ([1, 2, 3, 4])) + ((4, 3, 2, 1))) + + ((4 :: Num a => a))) + + (if 42 == 42.000000000000000 then 1 else 4)) + + ([ 1 .. ])) + + ([ 2, 4 .. ])) + + ([ 3 .. 5 ])) + + ([ 4, 8 .. 999 ])) +f _ + x + 1 + 1.9299999999999999 + 'c' + "dog" + ~y + (z@(Foo a b)) + (c Bar d) + [1, 2] + (3, 4) + (n+42) = y +g x y z = head y + +Enter trace(0): +doRenamings:tossing them away +Exit trace(0) + +Unknown name in export list: FooDataC +"read001.hs", line 38: undefined type constructor: EqLeaf +"read001.hs", line 38: undefined type constructor: EqLeaf +"read001.hs", line 112: undefined type constructor: Foo +"read001.hs", line 95: undefined value: x +"read001.hs", line 95: undefined value: x +"read001.hs", line 95: undefined value: foo +"read001.hs", line 107: undefined value: Foo +"read001.hs", line 107: undefined value: Bar +Fail: Compilation errors found + +ghc: execution of the Haskell compiler had trouble diff --git a/ghc/compiler/tests/reader/read002.hs b/ghc/compiler/tests/reader/read002.hs new file mode 100644 index 0000000000..9cc2153956 --- /dev/null +++ b/ghc/compiler/tests/reader/read002.hs @@ -0,0 +1,13 @@ +--!!! tests fixity reading and printing + +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/ghc/compiler/tests/reader/read002.stderr b/ghc/compiler/tests/reader/read002.stderr new file mode 100644 index 0000000000..f8a86008aa --- /dev/null +++ b/ghc/compiler/tests/reader/read002.stderr @@ -0,0 +1,466 @@ +Parsed, Haskellised: +module Main where +import Prelude {- + interface Prelude where + import PreludeBuiltin ( trace, Char ) + import PreludeCore ( Bool, String, ReadS, ShowS, Text ) + import PreludeRatio ( + %, numerator, denominator, approxRational ) + import PreludeComplex ( + realPart, + imagPart, + conjugate, + mkPolar, + cis, + polar, + magnitude, + phase ) + import PreludeList ( + head, + last, + tail, + init, + null, + \\, + genericLength, + length, + !!, + filter, + partition, + foldl1, + scanl, + scanl1, + foldr1, + scanr, + scanr1, + iterate, + repeat, + cycle, + take, + drop, + splitAt, + takeWhile, + dropWhile, + span, + break, + lines, + words, + unlines, + unwords, + nub, + reverse, + and, + or, + any, + all, + elem, + notElem, + sum, + product, + sums, + products, + maximum, + minimum, + concat, + transpose, + zip, + zip3, + zip4, + zip5, + zip6, + zip7, + zipWith, + zipWith3, + zipWith4, + zipWith5, + zipWith6, + zipWith7, + unzip, + unzip3, + unzip4, + unzip5, + unzip6, + unzip7 ) + import PreludeArray ( + array, + listArray, + !, + bounds, + indices, + elems, + assocs, + accumArray, + //, + accum, + amap, + ixmap ) + import PreludeText ( + reads, + shows, + show, + read, + showChar, + readLitChar, + showLitChar, + readSigned, + showSigned, + readDec, + showInt, + readFloat, + showFloat ) + import PreludeIO ( + stdin, + stdout, + stderr, + stdecho, + done, + readFile, + writeFile, + appendFile, + readBinFile, + writeBinFile, + appendBinFile, + deleteFile, + statusFile, + readChan, + appendChan, + readBinChan, + appendBinChan, + statusChan, + echo, + getArgs, + getProgName, + getEnv, + setEnv, + abort, + exit, + print, + prints, + interact ) + instance (Eq a, Eq b) => Eq (a, b) + instance (Ord a, Ord b) => Ord (a, b) + instance (Ix a, Ix b) => Ix (a, b) + instance (Text a, Text b) => Text (a, b) + instance (Binary a, Binary b) => Binary (a, b) + instance (Eq a, Eq b, Eq c) => Eq (a, b, c) + instance (Ord a, Ord b, Ord c) => Ord (a, b, c) + instance (Ix a, Ix b, Ix c) => Ix (a, b, c) + instance (Text a, Text b, Text c) => Text (a, b, c) + instance (Binary a, Binary b, Binary c) => Binary (a, b, c) + instance (Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) + instance (Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) + instance (Ix a, Ix b, Ix c, Ix d) => Ix (a, b, c, d) + instance (Text a, Text b, Text c, Text d) => Text (a, b, c, d) + instance (Binary a, Binary b, Binary c, Binary d) => Binary (a, + b, + c, + d) + ^ :: (Num b, Integral a) => b -> a -> b + ^^ :: (Fractional b, Integral a) => b -> a -> b + appendBin :: Bin -> Bin -> Bin + asTypeOf :: a -> a -> a + atan2 :: RealFloat a => a -> a -> a + chr :: Int -> Char + fromIntegral :: (Integral a, Num b) => a -> b + fromRealFrac :: (RealFrac a, Fractional b) => a -> b + gcd :: Integral a => a -> a -> a + isAlpha :: Char -> Bool + isAlphanum :: Char -> Bool + isAscii :: Char -> Bool + isControl :: Char -> Bool + isDigit :: Char -> Bool + isLower :: Char -> Bool + isNullBin :: Bin -> Bool + isPrint :: Char -> Bool + isSpace :: Char -> Bool + isUpper :: Char -> Bool + lcm :: Integral a => a -> a -> a + maxChar :: Char + maxInt :: Int + minChar :: Char + minInt :: Int + nullBin :: Bin + ord :: Char -> Int + subtract :: Num a => a -> a -> a + toLower :: Char -> Char + toUpper :: Char -> Char + until :: (a -> Bool) -> (a -> a) -> a -> a + trace :: String -> a -> a + % :: Integral a => a -> a -> Ratio a + numerator :: Integral a => Ratio a -> a + denominator :: Integral a => Ratio a -> a + approxRational :: RealFrac a => a -> a -> Rational + cis :: RealFloat a => a -> Complex a + conjugate :: RealFloat a => Complex a -> Complex a + imagPart :: RealFloat a => Complex a -> a + magnitude :: RealFloat a => Complex a -> a + mkPolar :: RealFloat a => a -> a -> Complex a + phase :: RealFloat a => Complex a -> a + polar :: RealFloat a => Complex a -> (a, a) + realPart :: RealFloat a => Complex a -> a + !! :: Integral a => [b] -> a -> b + \\ :: Eq a => [a] -> [a] -> [a] + all :: (a -> Bool) -> [a] -> Bool + and :: [Bool] -> Bool + any :: (a -> Bool) -> [a] -> Bool + break :: (a -> Bool) -> [a] -> ([a], [a]) + concat :: [[a]] -> [a] + cycle :: [a] -> [a] + drop :: Integral a => a -> [b] -> [b] + dropWhile :: (a -> Bool) -> [a] -> [a] + elem :: Eq a => a -> [a] -> Bool + filter :: (a -> Bool) -> [a] -> [a] + foldl1 :: (a -> a -> a) -> [a] -> a + foldr1 :: (a -> a -> a) -> [a] -> a + genericLength :: Num b => [a] -> b + head :: [a] -> a + init :: [a] -> [a] + iterate :: (a -> a) -> a -> [a] + last :: [a] -> a + length :: [a] -> Int + lines :: [Char] -> [[Char]] + maximum :: Ord a => [a] -> a + minimum :: Ord a => [a] -> a + notElem :: Eq a => a -> [a] -> Bool + nub :: Eq a => [a] -> [a] + null :: [a] -> Bool + or :: [Bool] -> Bool + partition :: (a -> Bool) -> [a] -> ([a], [a]) + product :: Num a => [a] -> a + products :: Num a => [a] -> [a] + repeat :: a -> [a] + reverse :: [a] -> [a] + scanl :: (b -> a -> b) -> b -> [a] -> [b] + scanl1 :: (a -> a -> a) -> [a] -> [a] + scanr :: (a -> b -> b) -> b -> [a] -> [b] + scanr1 :: (a -> a -> a) -> [a] -> [a] + span :: (a -> Bool) -> [a] -> ([a], [a]) + splitAt :: Integral a => a -> [b] -> ([b], [b]) + sum :: Num a => [a] -> a + sums :: Num a => [a] -> [a] + tail :: [a] -> [a] + take :: Integral a => a -> [b] -> [b] + takeWhile :: (a -> Bool) -> [a] -> [a] + transpose :: [[a]] -> [[a]] + unlines :: [[Char]] -> [Char] + unwords :: [[Char]] -> [Char] + unzip :: [(a, b)] -> ([a], [b]) + unzip3 :: [(a, b, c)] -> ([a], [b], [c]) + unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) + unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e]) + unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f]) + unzip7 :: + [(a, b, c, d, e, f, g)] + -> ([a], [b], [c], [d], [e], [f], [g]) + words :: [Char] -> [[Char]] + zip :: [a] -> [b] -> [(a, b)] + zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] + zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)] + zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)] + zip6 :: + [a] + -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)] + zip7 :: + [a] + -> [b] + -> [c] + -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)] + zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] + zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] + zipWith4 :: + (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] + zipWith5 :: + (a -> b -> c -> d -> e -> f) + -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] + zipWith6 :: + (a -> b -> c -> d -> e -> f -> g) + -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] + zipWith7 :: + (a -> b -> c -> d -> e -> f -> g -> h) + -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] + ! :: Ix a => Array a b -> a -> b + // :: Ix a => Array a b -> [Assoc a b] -> Array a b + accum :: + Ix b => (c -> a -> c) + -> Array b c -> [Assoc b a] -> Array b c + accumArray :: + Ix b => (c -> a -> c) + -> c -> (b, b) -> [Assoc b a] -> Array b c + amap :: Ix b => (a -> c) -> Array b a -> Array b c + array :: Ix a => (a, a) -> [Assoc a b] -> Array a b + assocs :: Ix a => Array a b -> [Assoc a b] + bounds :: Ix b => Array b a -> (b, b) + elems :: Ix a => Array a b -> [b] + indices :: Ix b => Array b a -> [b] + ixmap :: + (Ix b, Ix a) => (b, b) -> (b -> a) -> Array a c -> Array b c + listArray :: Ix a => (a, a) -> [b] -> Array a b + read :: Text a => [Char] -> a + readDec :: Integral a => [Char] -> [(a, [Char])] + readFloat :: RealFloat a => [Char] -> [(a, [Char])] + readLitChar :: [Char] -> [(Char, [Char])] + readSigned :: + Real a => ([Char] -> [(a, [Char])]) + -> [Char] -> [(a, [Char])] + reads :: Text a => [Char] -> [(a, [Char])] + show :: Text a => a -> [Char] + showChar :: Char -> [Char] -> [Char] + showFloat :: RealFloat a => a -> [Char] -> [Char] + showInt :: Integral a => a -> [Char] -> [Char] + showLitChar :: Char -> [Char] -> [Char] + showSigned :: + Real a => (a -> [Char] -> [Char]) + -> Int -> a -> [Char] -> [Char] + shows :: Text a => a -> [Char] -> [Char] + abort :: IOError -> [Response] -> [Request] + appendBinChan :: + [Char] + -> Bin + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + appendBinFile :: + [Char] + -> Bin + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + appendChan :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + appendFile :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + binDispatch :: + (IOError -> [Response] -> a) + -> (Bin -> [Response] -> a) -> [Response] -> a + deleteFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + done :: [Response] -> [Request] + echo :: + Bool + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + exit :: IOError -> [Response] -> [Request] + getArgs :: + (IOError -> [Response] -> [Request]) + -> ([[Char]] -> [Response] -> [Request]) + -> [Response] -> [Request] + getEnv :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + getProgName :: + (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + interact :: ([Char] -> [Char]) -> [Response] -> [Request] + print :: Text a => a -> [Response] -> [Request] + prints :: Text a => a -> [Char] -> [Response] -> [Request] + readBinChan :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> (Bin -> [Response] -> [Request]) + -> [Response] -> [Request] + readBinFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> (Bin -> [Response] -> [Request]) + -> [Response] -> [Request] + readChan :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + readFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + setEnv :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + statusChan :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + statusFile :: + [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Char] -> [Response] -> [Request]) + -> [Response] -> [Request] + stdecho :: [Char] + stderr :: [Char] + stdin :: [Char] + stdout :: [Char] + strDispatch :: + (IOError -> [Response] -> a) + -> ([Char] -> [Response] -> a) -> [Response] -> a + strListDispatch :: + (IOError -> [Response] -> a) + -> ([[Char]] -> [Response] -> a) -> [Response] -> a + succDispatch :: + (IOError -> [Response] -> a) + -> ([Response] -> a) -> [Response] -> a + writeBinFile :: + [Char] + -> Bin + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + writeFile :: + [Char] + -> [Char] + -> (IOError -> [Response] -> [Request]) + -> ([Response] -> [Request]) -> [Response] -> [Request] + -} +infixr 9 . +infixr 8 ^ +infixr 8 ^^ +infixr 3 && +infixr 2 || +infixr 0 $ +infixl 9 ! +infixl 9 // +infix 1 := +infix 6 :+ +infixr 8 ** +infixl 7 * +infixl 7 / +infixl 7 `quot` +infixl 7 `rem` +infixl 7 `div` +infixl 7 `mod` +infixl 6 + +infixl 6 - +infix 4 == +infix 4 /= +infix 4 < +infix 4 <= +infix 4 >= +infix 4 > +infixl 9 !! +infix 5 \\ +infix 4 `elem` +infix 4 `notElem` +infixl 7 % +infixl 1 `f` +infixr 2 \\\ +infix 3 :==> +infix 4 `MkFoo` +data Foo + = MkFoo Int + | (:==>) Float Double +\\\ :: Eq a => [a] -> [a] -> [a] +{- rec -} +f x y = x +(\\\) + xs ys = xs + diff --git a/ghc/compiler/tests/reader/read003.hs b/ghc/compiler/tests/reader/read003.hs new file mode 100644 index 0000000000..0bb8a24ccf --- /dev/null +++ b/ghc/compiler/tests/reader/read003.hs @@ -0,0 +1,5 @@ +~(a,b,c) | nullity b = a + | nullity c = a + | otherwise = a + where + nullity = null diff --git a/ghc/compiler/tests/reader/read004.hs b/ghc/compiler/tests/reader/read004.hs new file mode 100644 index 0000000000..77ab5a0268 --- /dev/null +++ b/ghc/compiler/tests/reader/read004.hs @@ -0,0 +1,43 @@ +--!!! string gaps +--!!! + +----------- + +main = appendChan stdout "\ + +\Some girls give me money\n\ + +\Some girls buy me clothes\n\ + +\..." + exit done + +----------- + +main2 = appendChan stdout "\ +\ \ +..." exit done + +----------- + +main3 = appendChan stdout "\ + +\Some girls give me money\n\ +-- and here is a comment +\Some girls buy me clothes\n\ + +\..." + exit done + +----------- + +main3 = appendChan stdout "\ +{- + and here is a nested {- comment -} +-} +\Some girls give me money\n\ + +\Some girls buy me clothes\n\ + +\..." + exit done diff --git a/ghc/compiler/tests/reader/read004.stderr b/ghc/compiler/tests/reader/read004.stderr new file mode 100644 index 0000000000..e69de29bb2 --- /dev/null +++ b/ghc/compiler/tests/reader/read004.stderr |