From 16ff3d468749718e68ef81c7d35cc5d4703d85ac Mon Sep 17 00:00:00 2001
From: sof <unknown>
Date: Wed, 3 Sep 1997 23:33:51 +0000
Subject: [PATCH] [project @ 1997-09-03 23:33:46 by sof] moved from
 ghc/compiler/tests/etc

---
 ghc/tests/etc/wdp-array.hs      |  4 ++++
 ghc/tests/etc/wdp-otherwise.hs  | 11 +++++++++++
 ghc/tests/etc/wdp-ppr.hs        | 13 +++++++++++++
 ghc/tests/etc/wdp-prel-insts.hs |  8 ++++++++
 4 files changed, 36 insertions(+)
 create mode 100644 ghc/tests/etc/wdp-array.hs
 create mode 100644 ghc/tests/etc/wdp-otherwise.hs
 create mode 100644 ghc/tests/etc/wdp-ppr.hs
 create mode 100644 ghc/tests/etc/wdp-prel-insts.hs

diff --git a/ghc/tests/etc/wdp-array.hs b/ghc/tests/etc/wdp-array.hs
new file mode 100644
index 000000000000..f3432c2bdc9f
--- /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 000000000000..c59b949a48de
--- /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 000000000000..563e752b909e
--- /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 000000000000..00a06cbecef6
--- /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
-- 
GitLab