[project @ 1997-05-19 00:24:11 by sof]
authorsof <unknown>
Mon, 19 May 1997 00:24:33 +0000 (00:24 +0000)
committersof <unknown>
Mon, 19 May 1997 00:24:33 +0000 (00:24 +0000)
2.04 changes

22 files changed:
ghc/compiler/simplCore/MagicUFs.hi-boot [new file with mode: 0644]
ghc/compiler/simplCore/Simplify.hi-boot [new file with mode: 0644]
ghc/compiler/simplCore/SmplLoop.hs [new file with mode: 0644]
ghc/compiler/specialise/SpecEnv.hi-boot [new file with mode: 0644]
ghc/compiler/tests/typecheck/should_fail/tcfail069.hs [new file with mode: 0644]
ghc/compiler/tests/typecheck/should_fail/tcfail070.hs [new file with mode: 0644]
ghc/compiler/typecheck/TcEnv.hi-boot [new file with mode: 0644]
ghc/compiler/typecheck/TcGRHSs.hi-boot [new file with mode: 0644]
ghc/compiler/typecheck/TcLoop.hs [new file with mode: 0644]
ghc/compiler/typecheck/TcMLoop.hs [new file with mode: 0644]
ghc/compiler/typecheck/TcType.hi-boot [new file with mode: 0644]
ghc/compiler/types/Class.hi-boot [new file with mode: 0644]
ghc/compiler/types/TyCon.hi-boot [new file with mode: 0644]
ghc/compiler/types/TyLoop.hs [new file with mode: 0644]
ghc/compiler/types/TyVar.hi-boot [new file with mode: 0644]
ghc/compiler/types/Type.hi-boot [new file with mode: 0644]
ghc/compiler/utils/CharSeq.lhs [deleted file]
ghc/compiler/utils/HandleHack.hs [new file with mode: 0644]
ghc/compiler/utils/SpecLoop.hs [new file with mode: 0644]
ghc/compiler/utils/Ubiq.hs [new file with mode: 0644]
ghc/compiler/utils/UniqFM.hi-boot [new file with mode: 0644]
ghc/compiler/utils/Unpretty.lhs [deleted file]

diff --git a/ghc/compiler/simplCore/MagicUFs.hi-boot b/ghc/compiler/simplCore/MagicUFs.hi-boot
new file mode 100644 (file)
index 0000000..91cc850
--- /dev/null
@@ -0,0 +1,6 @@
+_interface_ MagicUFs 1
+_exports_
+MagicUFs MagicUnfoldingFun mkMagicUnfoldingFun;
+_declarations_
+1 data MagicUnfoldingFun;
+1 mkMagicUnfoldingFun _:_ Unique.Unique -> MagicUFs.MagicUnfoldingFun ;;
diff --git a/ghc/compiler/simplCore/Simplify.hi-boot b/ghc/compiler/simplCore/Simplify.hi-boot
new file mode 100644 (file)
index 0000000..a02a06c
--- /dev/null
@@ -0,0 +1,14 @@
+_interface_ Simplify 1
+_exports_
+Simplify simplBind simplExpr;
+_declarations_
+1 simplBind _:_ SimplEnv.SimplEnv
+            -> SimplEnv.InBinding
+            -> (SimplEnv.SimplEnv -> SimplMonad.SmplM SimplEnv.OutExpr)
+            -> SimplEnv.OutType
+            -> SimplMonad.SmplM SimplEnv.OutExpr ;;
+1 simplExpr _:_ SimplEnv.SimplEnv
+            -> SimplEnv.InExpr -> [SimplEnv.OutArg]
+            -> SimplEnv.OutType
+            -> SimplMonad.SmplM SimplEnv.OutExpr ;;
+
diff --git a/ghc/compiler/simplCore/SmplLoop.hs b/ghc/compiler/simplCore/SmplLoop.hs
new file mode 100644 (file)
index 0000000..f3f3d1d
--- /dev/null
@@ -0,0 +1,10 @@
+module SmplLoop 
+
+       (
+       module MagicUFs,
+        module Simplify
+       ) where
+
+import MagicUFs
+import Simplify
+
diff --git a/ghc/compiler/specialise/SpecEnv.hi-boot b/ghc/compiler/specialise/SpecEnv.hi-boot
new file mode 100644 (file)
index 0000000..466e8c4
--- /dev/null
@@ -0,0 +1,7 @@
+_interface_ SpecEnv 1
+_exports_
+SpecEnv SpecEnv nullSpecEnv isNullSpecEnv;
+_declarations_
+1 data SpecEnv;
+1 isNullSpecEnv _:_ SpecEnv.SpecEnv -> PrelBase.Bool ;;
+1 nullSpecEnv _:_ SpecEnv.SpecEnv ;;
diff --git a/ghc/compiler/tests/typecheck/should_fail/tcfail069.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail069.hs
new file mode 100644 (file)
index 0000000..73dd738
--- /dev/null
@@ -0,0 +1,48 @@
+{- 
+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/tcfail070.hs b/ghc/compiler/tests/typecheck/should_fail/tcfail070.hs
new file mode 100644 (file)
index 0000000..d6cd3d7
--- /dev/null
@@ -0,0 +1,14 @@
+{- 
+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/typecheck/TcEnv.hi-boot b/ghc/compiler/typecheck/TcEnv.hi-boot
new file mode 100644 (file)
index 0000000..073f24e
--- /dev/null
@@ -0,0 +1,6 @@
+_interface_ TcEnv 1
+_exports_
+TcEnv TcEnv initEnv;
+_declarations_
+1 data TcEnv a;
+1 initEnv _:_ _forall_ [a] => ArrBase.MutableArray a PrelBase.Int (UniqFM.UniqFM (TyVar.GenTyVar (ArrBase.MutableArray a PrelBase.Int (TcType.TcMaybe a)))) -> TcEnv.TcEnv a ;;
diff --git a/ghc/compiler/typecheck/TcGRHSs.hi-boot b/ghc/compiler/typecheck/TcGRHSs.hi-boot
new file mode 100644 (file)
index 0000000..3ac4122
--- /dev/null
@@ -0,0 +1,6 @@
+_interface_ TcGRHSs 1
+_exports_
+TcGRHSs tcGRHSsAndBinds;
+_declarations_
+1 tcGRHSsAndBinds _:_ _forall_ [a] => HsMatches.GRHSsAndBinds HsSyn.Fake HsSyn.Fake Name.Name (HsPat.InPat Name.Name) -> TcMonad.TcDown a -> TcEnv.TcEnv a -> GHC.State# a -> SST.FSST_R a (HsMatches.GRHSsAndBinds (TyVar.GenTyVar (ArrBase.MutableArray a PrelBase.Int (TcType.TcMaybe a))) Unique.Unique (TcHsSyn.TcIdOcc a) (HsPat.OutPat (TyVar.GenTyVar (ArrBase.MutableArray a PrelBase.Int (TcType.TcMaybe a))) Unique.Unique (TcHsSyn.TcIdOcc a)), Bag.Bag (Inst.Inst a), Type.GenType (TyVar.GenTyVar (ArrBase.MutableArray a PrelBase.Int (TcType.TcMaybe a))) Unique.Unique) PrelBase.() ;;
+
diff --git a/ghc/compiler/typecheck/TcLoop.hs b/ghc/compiler/typecheck/TcLoop.hs
new file mode 100644 (file)
index 0000000..2f60400
--- /dev/null
@@ -0,0 +1,7 @@
+module TcLoop 
+
+       (
+        module TcGRHSs
+       ) where
+
+import TcGRHSs
diff --git a/ghc/compiler/typecheck/TcMLoop.hs b/ghc/compiler/typecheck/TcMLoop.hs
new file mode 100644 (file)
index 0000000..4b55619
--- /dev/null
@@ -0,0 +1,9 @@
+module TcMLoop 
+
+       (
+        module TcType,
+       module TcEnv
+       ) where
+
+import TcType
+import TcEnv
diff --git a/ghc/compiler/typecheck/TcType.hi-boot b/ghc/compiler/typecheck/TcType.hi-boot
new file mode 100644 (file)
index 0000000..a540f45
--- /dev/null
@@ -0,0 +1,6 @@
+_interface_ TcType 1
+_exports_
+TcType TcMaybe;
+_declarations_
+1 data TcMaybe a;
+
diff --git a/ghc/compiler/types/Class.hi-boot b/ghc/compiler/types/Class.hi-boot
new file mode 100644 (file)
index 0000000..1b6a264
--- /dev/null
@@ -0,0 +1,9 @@
+_interface_ Class 1
+_exports_
+Class Class GenClass;
+_instances_
+instance {PrelBase.Eq Class.Class} = $d1;
+_declarations_
+1 $d1 _:_ {PrelBase.Eq Class.Class} ;;
+1 type Class = Class.GenClass TyVar.TyVar Usage.UVar;
+1 data GenClass a b;
diff --git a/ghc/compiler/types/TyCon.hi-boot b/ghc/compiler/types/TyCon.hi-boot
new file mode 100644 (file)
index 0000000..b449468
--- /dev/null
@@ -0,0 +1,5 @@
+_interface_ TyCon 1
+_exports_
+TyCon TyCon;
+_declarations_
+1 data TyCon;
diff --git a/ghc/compiler/types/TyLoop.hs b/ghc/compiler/types/TyLoop.hs
new file mode 100644 (file)
index 0000000..db0db58
--- /dev/null
@@ -0,0 +1,18 @@
+module TyLoop 
+       (
+        module Id,
+       module TyCon,
+        module TyVar,
+       module Type,
+       module TysWiredIn,
+       module TysPrim,
+       module Class,
+       ) where
+
+import Id
+import TyCon
+import Type
+import Class
+import TysWiredIn
+import TysPrim
+import TyVar
diff --git a/ghc/compiler/types/TyVar.hi-boot b/ghc/compiler/types/TyVar.hi-boot
new file mode 100644 (file)
index 0000000..c36f6d8
--- /dev/null
@@ -0,0 +1,7 @@
+_interface_ TyVar 1
+_exports_
+TyVar TyVar GenTyVar;
+_declarations_
+1 type TyVar = TyVar.GenTyVar Usage.Usage ;
+1 data GenTyVar a;
+
diff --git a/ghc/compiler/types/Type.hi-boot b/ghc/compiler/types/Type.hi-boot
new file mode 100644 (file)
index 0000000..887c5f0
--- /dev/null
@@ -0,0 +1,11 @@
+_interface_ Type 1
+_usages_
+TyVar 1 :: TyVar 1;
+Usage 1 :: Uage 1;
+_exports_
+Type Type GenType splitFunTy splitSigmaTy;
+_declarations_
+1 type Type = Type.GenType TyVar.TyVar Usage.UVar ;
+1 data GenType a b;
+1 splitFunTy _:_ _forall_ [a b] => Type.GenType a b -> ([GenType a b], Type.GenType a b) ;;
+1 splitSigmaTy _:_ _forall_ [a b] => Type.GenType a b -> ([a],[(Class.Class,Type.GenType a b)], Type.GenType a b) ;;
diff --git a/ghc/compiler/utils/CharSeq.lhs b/ghc/compiler/utils/CharSeq.lhs
deleted file mode 100644 (file)
index d5e7c33..0000000
+++ /dev/null
@@ -1,203 +0,0 @@
-%
-% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
-%
-\section[CharSeq]{Characters sequences: the @CSeq@ type}
-
-\begin{code}
-#if defined(COMPILING_GHC)
-# include "HsVersions.h"
-#else
-# define FAST_STRING String
-# define FAST_INT    Int
-# define ILIT(x)     (x)
-# define IBOX(x)     (x)
-# define _GE_       >=
-# define _ADD_      +
-# define _SUB_      -
-# define FAST_BOOL   Bool
-# define _TRUE_             True
-# define _FALSE_     False
-#endif
-
-module CharSeq (
-       CSeq,
-       cNil, cAppend, cIndent, cNL, cStr, cPStr, cCh, cInt,
-#if ! defined(COMPILING_GHC)
-       cLength,
-       cShows,
-#endif
-       cShow
-
-#if ! defined(COMPILING_GHC)
-   ) where
-#else
-       , cPutStr
-   ) where
-
-CHK_Ubiq() -- debugging consistency check
-IMPORT_1_3(IO)
-
-#endif
-\end{code}
-
-%************************************************
-%*                                             *
-       \subsection{The interface}
-%*                                             *
-%************************************************
-
-\begin{code}
-cShow  :: CSeq -> [Char]
-
-#if ! defined(COMPILING_GHC)
--- not used in GHC
-cShows :: CSeq -> ShowS
-cLength        :: CSeq -> Int
-#endif
-
-cNil    :: CSeq
-cAppend :: CSeq -> CSeq -> CSeq
-cIndent :: Int -> CSeq -> CSeq
-cNL    :: CSeq
-cStr   :: [Char] -> CSeq
-cPStr  :: FAST_STRING -> CSeq
-cCh    :: Char -> CSeq
-cInt   :: Int -> CSeq
-
-#if defined(COMPILING_GHC)
-cPutStr :: Handle -> CSeq -> IO ()
-#endif
-\end{code}
-
-%************************************************
-%*                                             *
-       \subsection{The representation}
-%*                                             *
-%************************************************
-
-\begin{code}
-data CSeq
-  = CNil
-  | CAppend    CSeq CSeq
-  | CIndent    Int  CSeq
-  | CNewline                   -- Move to start of next line, unless we're
-                               -- already at the start of a line.
-  | CStr       [Char]
-  | CCh                Char
-  | CInt       Int     -- equiv to "CStr (show the_int)"
-#if defined(COMPILING_GHC)
-  | CPStr      FAST_STRING
-#endif
-\end{code}
-
-The construction functions do pattern matching, to ensure that
-redundant CNils are eliminated.  This is bound to have some effect on
-evaluation order, but quite what I don't know.
-
-\begin{code}
-cNil = CNil
-\end{code}
-
-The following special cases were eating our lunch! They make the whole
-thing too strict.  A classic strictness bug!
-\begin{code}
--- cAppend CNil cs2  = cs2
--- cAppend cs1  CNil = cs1
-
-cAppend cs1 cs2 = CAppend cs1 cs2
-
-cIndent n cs = CIndent n cs
-
-cNL    = CNewline
-cStr   = CStr
-cCh    = CCh
-cInt   = CInt
-
-#if defined(COMPILING_GHC)
-cPStr  = CPStr
-#else
-cPStr  = CStr
-#endif
-
-cShow  seq     = flatten ILIT(0) _TRUE_ seq []
-
-#if ! defined(COMPILING_GHC)
-cShows seq rest = cShow seq ++ rest
-cLength seq = length (cShow seq) -- *not* the best way to do this!
-#endif
-\end{code}
-
-This code is {\em hammered}.  We are not above doing sleazy
-non-standard things.  (WDP 94/10)
-
-\begin{code}
-data WorkItem = WI FAST_INT CSeq -- indentation, and sequence
-
-flatten :: FAST_INT    -- Indentation
-       -> FAST_BOOL    -- True => just had a newline
-       -> CSeq         -- Current seq to flatten
-       -> [WorkItem]   -- Work list with indentation
-       -> String
-
-flatten n nlp CNil seqs = flattenS nlp seqs
-
-flatten n nlp (CAppend seq1 seq2) seqs = flatten n nlp seq1 ((WI n seq2) : seqs)
-flatten n nlp (CIndent IBOX(n2) seq) seqs = flatten (n2 _ADD_ n) nlp seq seqs
-
-flatten n _FALSE_ CNewline seqs = '\n' : flattenS _TRUE_ seqs
-flatten n _TRUE_  CNewline seqs = flattenS _TRUE_ seqs -- Already at start of line
-
-flatten n _FALSE_ (CStr s) seqs = s ++ flattenS _FALSE_ seqs
-flatten n _FALSE_ (CCh  c) seqs = c :  flattenS _FALSE_ seqs
-flatten n _FALSE_ (CInt i) seqs = show i ++ flattenS _FALSE_ seqs
-#if defined(COMPILING_GHC)
-flatten n _FALSE_ (CPStr s) seqs = _UNPK_ s ++ flattenS _FALSE_ seqs
-#endif
-
-flatten n _TRUE_  (CStr s) seqs = mkIndent n (s ++ flattenS _FALSE_ seqs)
-flatten n _TRUE_  (CCh  c) seqs = mkIndent n (c :  flattenS _FALSE_ seqs)
-flatten n _TRUE_  (CInt i) seqs = mkIndent n (show i ++ flattenS _FALSE_ seqs)
-#if defined(COMPILING_GHC)
-flatten n _TRUE_ (CPStr s) seqs = mkIndent n ( _UNPK_ s ++ flattenS _FALSE_ seqs)
-#endif
-\end{code}
-
-\begin{code}
-flattenS :: FAST_BOOL -> [WorkItem] -> String
-flattenS nlp [] = ""
-flattenS nlp ((WI col seq):seqs) = flatten col nlp seq seqs
-\end{code}
-
-\begin{code}
-mkIndent :: FAST_INT -> String -> String
-mkIndent ILIT(0) s = s
-mkIndent n       s
-  = if (n _GE_ ILIT(8))
-    then '\t' : mkIndent (n _SUB_ ILIT(8)) s
-    else ' '  : mkIndent (n _SUB_ ILIT(1)) s
-    -- Hmm.. a little Unix-y.
-\end{code}
-
-Now the I/O version.
-This code is massively {\em hammered}.
-It {\em ignores} indentation.
-
-(NB: 1.3 compiler: efficiency hacks removed for now!)
-
-\begin{code}
-#if defined(COMPILING_GHC)
-
-cPutStr handle sq = flat sq
-  where
-    flat CNil            = return ()
-    flat (CIndent n2 seq) = flat seq
-    flat (CAppend s1 s2)  = flat s1 >> flat s2
-    flat CNewline        = hPutChar handle '\n'
-    flat (CCh c)         = hPutChar handle c
-    flat (CInt i)        = hPutStr  handle (show i)
-    flat (CStr s)        = hPutStr  handle s
-    flat (CPStr s)       = hPutFS   handle s
-                            --hPutStr  handle (_UNPK_ s)
-
-#endif {- COMPILING_GHC -}
-\end{code}
diff --git a/ghc/compiler/utils/HandleHack.hs b/ghc/compiler/utils/HandleHack.hs
new file mode 100644 (file)
index 0000000..1c5baa9
--- /dev/null
@@ -0,0 +1 @@
+module HandleHack  where
diff --git a/ghc/compiler/utils/SpecLoop.hs b/ghc/compiler/utils/SpecLoop.hs
new file mode 100644 (file)
index 0000000..bcc1af9
--- /dev/null
@@ -0,0 +1,8 @@
+module SpecLoop 
+
+       (
+        module Name
+       ) where
+
+import Name
+
diff --git a/ghc/compiler/utils/Ubiq.hs b/ghc/compiler/utils/Ubiq.hs
new file mode 100644 (file)
index 0000000..c66085d
--- /dev/null
@@ -0,0 +1,10 @@
+module Ubiq 
+       (
+        module Unique,
+       module UniqFM
+
+       ) where
+
+import Unique
+import UniqFM
+
diff --git a/ghc/compiler/utils/UniqFM.hi-boot b/ghc/compiler/utils/UniqFM.hi-boot
new file mode 100644 (file)
index 0000000..a832e3f
--- /dev/null
@@ -0,0 +1,5 @@
+_interface_ UniqFM 1
+_exports_
+UniqFM Uniquable(uniqueOf);
+_declarations_
+1 class Uniquable a where {uniqueOf :: a -> Unique.Unique};
diff --git a/ghc/compiler/utils/Unpretty.lhs b/ghc/compiler/utils/Unpretty.lhs
deleted file mode 100644 (file)
index 3b0b912..0000000
+++ /dev/null
@@ -1,151 +0,0 @@
-%
-% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
-%
-\section[Unpretty]{Unpretty-printing data type}
-
-\begin{code}
-#include "HsVersions.h"
-
-module Unpretty (
-       SYN_IE(Unpretty),
-
-       uppNil, uppStr, uppPStr, uppChar, uppInt, uppInteger,
-       uppSP, upp'SP, uppLbrack, uppRbrack, uppLparen, uppRparen,
-       uppSemi, uppComma, uppEquals,
-
-       uppBracket, uppParens,
-       uppCat, uppBeside, uppBesides, uppAbove, uppAboves,
-       uppNest, uppSep, uppInterleave, uppIntersperse,
-       uppShow,
-       uppPutStr,
-
-       -- abstract type, to complete the interface...
-       CSeq
-   ) where
-
-CHK_Ubiq() -- debugging consistency check
-IMPORT_1_3(IO)
-
-import CharSeq
-\end{code}
-
-Same interface as @Pretty@, but doesn't do anything.
-
-The pretty type is redefined here:
-\begin{code}
-type Unpretty = CSeq
-\end{code}
-
-%************************************************
-%*                                             *
-       \subsection{The interface}
-%*                                             *
-%************************************************
-
-\begin{code}
-uppNil         :: Unpretty
-uppSP, upp'SP, uppLbrack, uppRbrack, uppLparen, uppRparen, uppSemi, uppComma, uppEquals :: Unpretty
-
-uppStr         :: [Char] -> Unpretty
-uppPStr                :: FAST_STRING -> Unpretty
-uppChar                :: Char -> Unpretty
-uppInt         :: Int -> Unpretty
-uppInteger     :: Integer -> Unpretty
-
-uppBracket     :: Unpretty -> Unpretty -- put brackets around it
-uppParens      :: Unpretty -> Unpretty -- put parens   around it
-
-uppBeside      :: Unpretty -> Unpretty -> Unpretty
-uppBesides     :: [Unpretty] -> Unpretty
-ppBesideSP     :: Unpretty -> Unpretty -> Unpretty
-uppCat         :: [Unpretty] -> Unpretty               -- i.e., ppBesidesSP
-
-uppAbove       :: Unpretty -> Unpretty -> Unpretty
-uppAboves      :: [Unpretty] -> Unpretty
-
-uppInterleave  :: Unpretty -> [Unpretty] -> Unpretty
-uppIntersperse :: Unpretty -> [Unpretty] -> Unpretty   -- no spaces between
-uppSep         :: [Unpretty] -> Unpretty
-uppNest                :: Int -> Unpretty -> Unpretty
-
-uppShow                :: Int -> Unpretty -> [Char]
-
-uppPutStr      :: Handle -> Int -> Unpretty -> IO ()
-\end{code}
-
-%************************************************
-%*                                             *
-       \subsection{The representation}
-%*                                             *
-%************************************************
-
-\begin{code}
-uppShow _ p    = cShow p
-
-uppPutStr f _ p = _scc_ "uppPutStr" (cPutStr f p)
-
-uppNil         = cNil
-uppStr s       = cStr s
-uppPStr s      = cPStr s
-uppChar c      = cCh c
-uppInt n       = cInt n
-
-uppInteger n   = cStr (show n)
-
-uppSP          = cCh ' '
-upp'SP{-'-}    = uppBeside uppComma uppSP
-uppLbrack      = cCh '['
-uppRbrack      = cCh ']'
-uppLparen      = cCh '('
-uppRparen      = cCh ')'
-uppSemi                = cCh ';'
-uppComma       = cCh ','
-uppEquals      = cCh '='
-
-uppBracket p = uppBeside uppLbrack (uppBeside p uppRbrack)
-uppParens  p = uppBeside uppLparen (uppBeside p uppRparen)
-
-uppInterleave sep ps = uppSep (pi ps)
-  where
-   pi []       = []
-   pi [x]      = [x]
-   pi (x:xs)   = (cAppend{-uppBeside-} x sep) : pi xs
-\end{code}
-
-\begin{code}
-uppIntersperse sep ps = uppBesides (pi ps)
-  where
-   pi []       = []
-   pi [x]      = [x]
-   pi (x:xs)   = (cAppend{-uppBeside-} x sep) : pi xs
-\end{code}
-
-\begin{code}
-uppBeside p1 p2  = p1 `cAppend` p2
-
-uppBesides []    = cNil{-uppNil-}
-uppBesides [p]   = p
-uppBesides (p:ps) = p `cAppend`{-uppBeside-} uppBesides ps
-\end{code}
-
-\begin{code}
-ppBesideSP p1 p2 = p1 `cAppend` (cCh ' ') `cAppend` p2
-\end{code}
-
-@uppCat@ is the name I (WDP) happen to have been using for @ppBesidesSP@.
-
-\begin{code}
-uppCat []     = cNil{-uppNil-}
-uppCat [p]    = p
-uppCat (p:ps) = ppBesideSP p (uppCat ps)
-
-uppAbove p1 p2 = p1 `cAppend` (cCh '\n') `cAppend` p2
-
-uppAboves []    = cNil{-uppNil-}
-uppAboves [p]   = p
-uppAboves (p:ps) = p `cAppend` (cCh '\n') `cAppend` (uppAboves ps)
-
-uppNest n p = p
-
-uppSep ps = uppBesides ps
-\end{code}