diff --git a/ghc/tests/etc/wdp-array.hs b/ghc/tests/etc/wdp-array.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3432c2bdc9f8831fba801720cc0dc9ea0bd8ca9 --- /dev/null +++ b/ghc/tests/etc/wdp-array.hs @@ -0,0 +1,4 @@ +import MiniPrel + +a :: Array Int Int +a = array (1,100) ((1 := 1) : [i := i * a!(i-1) | i <- [2..100]]) diff --git a/ghc/tests/etc/wdp-otherwise.hs b/ghc/tests/etc/wdp-otherwise.hs new file mode 100644 index 0000000000000000000000000000000000000000..c59b949a48de791d3c584cafd862e06db48d1bf2 --- /dev/null +++ b/ghc/tests/etc/wdp-otherwise.hs @@ -0,0 +1,11 @@ +-- this is legal, I think (WDP) + +module Confused where + +import Prelude hiding (otherwise) + +otherwise = False + +f x | otherwise = 1 + +g otherwise | otherwise = 2 diff --git a/ghc/tests/etc/wdp-ppr.hs b/ghc/tests/etc/wdp-ppr.hs new file mode 100644 index 0000000000000000000000000000000000000000..563e752b909ea8c20dcb475cca0c4f54ec042558 --- /dev/null +++ b/ghc/tests/etc/wdp-ppr.hs @@ -0,0 +1,13 @@ +{- +From: Kubiak Ryszard <fozzie> +To: partain +Subject: You may test the new pretty-printer on the following text: +Date: Wed, 2 Oct 91 18:06:05 BST +-} + +data LList alpha = Nill | Conss alpha (LList alpha) + +append :: LList a -> LList a -> LList a +append xs ys = case xs of + Nill -> ys + (Conss z zs) -> Conss z (append zs ys) diff --git a/ghc/tests/etc/wdp-prel-insts.hs b/ghc/tests/etc/wdp-prel-insts.hs new file mode 100644 index 0000000000000000000000000000000000000000..00a06cbecef608f66880ecb52d94b0c2a9d33a57 --- /dev/null +++ b/ghc/tests/etc/wdp-prel-insts.hs @@ -0,0 +1,8 @@ +-- what error do you get if you redefined PreludeCore instances? + +module Test where + +f x@(a,b) y@(c,d) = x == y + +instance Eq (a,b) where + (m,n) == (o,p) = m == o