diff --git a/ghc/lib/glaExts/ByteArray.lhs b/ghc/lib/glaExts/ByteArray.lhs
new file mode 100644
index 0000000000000000000000000000000000000000..2ea73c21fcca2960387304231edb45c6136196cd
--- /dev/null
+++ b/ghc/lib/glaExts/ByteArray.lhs
@@ -0,0 +1,39 @@
+%
+% (c) The AQUA Project, Glasgow University, 1994-1997
+%
+\section[ByteArray]{The @ByteArray@ interface}
+
+Immutable, read-only chunks of bytes, the @ByteArray@ collects
+together the definitions in @ArrBase@ and exports them as one.
+
+\begin{code}
+module ByteArray
+       (
+        ByteArray(..),  -- not abstract, for now.
+        Ix,
+
+        --Indexing of ordinary @Arrays@ is standard Haskell and isn't defined here.
+        indexCharArray,     --:: Ix ix => ByteArray ix -> ix -> Char 
+        indexIntArray,      --:: Ix ix => ByteArray ix -> ix -> Int
+        indexAddrArray,     --:: Ix ix => ByteArray ix -> ix -> Addr
+        indexFloatArray,    --:: Ix ix => ByteArray ix -> ix -> Float
+        indexDoubleArray,   --:: Ix ix => ByteArray ix -> ix -> Double
+        
+        --Indexing off @Addrs@ is similar, and therefore given here.
+        indexCharOffAddr,   --:: Addr -> Int -> Char
+        indexIntOffAddr,    --:: Addr -> Int -> Int
+        indexAddrOffAddr,   --:: Addr -> Int -> Addr
+        indexFloatOffAddr,  --:: Addr -> Int -> Float
+        indexDoubleOffAddr, --:: Addr -> Int -> Double
+
+        Addr,
+	Word
+
+       ) where
+
+import ArrBase
+import Ix
+import PrelBase (Addr, Word)
+
+\end{code}
+
diff --git a/ghc/lib/glaExts/GlaExts.lhs b/ghc/lib/glaExts/GlaExts.lhs
new file mode 100644
index 0000000000000000000000000000000000000000..1a55b9176ff0989734b114c966be03b171a0dd0d
--- /dev/null
+++ b/ghc/lib/glaExts/GlaExts.lhs
@@ -0,0 +1,60 @@
+%
+% (c) The AQUA Project, Glasgow University, 1994-1996
+%
+\section[GlaExts]{The @GlaExts@ interface}
+
+The @GlaExts@ packages up various Glasgow extensions and
+exports them all through one interface. The Idea being that
+a Haskell program using a Glasgow extension doesn't have to
+selective import of obscure/likely-to-move (believe me, we
+really like to move functions around for the prelude bits!)
+GHC interfaces - instead import the GlaExts rag bag and you should be away!
+
+\begin{code}
+module GlaExts
+
+       (
+        -- From module STBase, the PrimIO monad 
+        -- (an instance of ST):
+	PrimIO,
+        ST, RealWorld,
+        module Monad,   -- ST is an instance
+        fixPrimIO, unsafePerformPrimIO, unsafeInterleavePrimIO,
+        returnPrimIO, thenPrimIO, seqPrimIO,
+        
+        listPrimIO, mapPrimIO, mapAndUnzipPrimIO,
+
+        -- operations for interfacing IO and ST/PrimIO
+        --
+        stToIO,       --:: ST RealWorld a -> IO a
+	primIOToIO,   --:: PrimIO a       -> IO a
+	ioToST,	      --:: IO a -> ST RealWorld a
+	ioToPrimIO,   --:: IO a -> PrimIO       a
+        thenIO_Prim,  -- :: PrimIO a -> (a -> IO b) -> IO b
+
+        -- Everything from module ByteArray:
+	module ByteArray,
+
+        -- Same for Mutable(Byte)Array interface:
+	module MutableArray,
+	
+        -- the representation of some basic types:
+        Int(..),Addr(..),Word(..),Float(..),Double(..),Integer(..),
+
+        -- misc bits
+	trace,
+
+        -- and finally, all the unboxed primops of GHC!
+        module GHC
+
+       ) where
+
+import GHC
+import STBase
+import PrelBase
+import ByteArray
+import MutableArray
+import Monad
+import IOBase
+
+\end{code}
diff --git a/ghc/lib/glaExts/MutVar.lhs b/ghc/lib/glaExts/MutVar.lhs
new file mode 100644
index 0000000000000000000000000000000000000000..e3778e9c6eed9836a6013c72b28a6591b39a00cc
--- /dev/null
+++ b/ghc/lib/glaExts/MutVar.lhs
@@ -0,0 +1,44 @@
+%
+% (c) The AQUA Project, Glasgow University, 1994-1996
+%
+\section[MutVar]{Mutable variables}
+
+Mutable variables, for the @IO@ monad.
+
+\begin{code}
+module MutVar
+
+       (
+        MutVar,      -- abstract
+
+	newVar,      -- :: a -> IO (MutVar a)
+	readVar,     -- :: MutVar a -> IO a
+	writeVar,    -- :: MutVar a -> a -> IO ()
+	sameVar      -- :: MutVar a -> MutVar a -> Bool
+
+       ) where
+
+import qualified ST
+import qualified ArrBase
+import IOBase ( IO , stToIO )
+import GHC (RealWorld)
+
+\end{code}
+
+\begin{code}
+
+newtype MutVar a = MutVar (ArrBase.MutableVar RealWorld a)
+
+newVar :: a -> IO (MutVar a)
+newVar v = stToIO (ST.newVar v) >>= \ var -> return (MutVar var)
+
+readVar :: MutVar a -> IO a
+readVar (MutVar var) = stToIO (ST.readVar var)
+
+writeVar :: MutVar a -> a -> IO ()
+writeVar (MutVar var) v = stToIO (ST.writeVar var v)
+
+sameVar :: MutVar a -> MutVar a -> Bool
+sameVar (MutVar var1) (MutVar var2) = ST.sameVar var1 var2
+
+\end{code}
diff --git a/ghc/lib/glaExts/MutableArray.lhs b/ghc/lib/glaExts/MutableArray.lhs
new file mode 100644
index 0000000000000000000000000000000000000000..eead4b692a9570953da89011ffacf7b5595d1146
--- /dev/null
+++ b/ghc/lib/glaExts/MutableArray.lhs
@@ -0,0 +1,62 @@
+%
+% (c) The AQUA Project, Glasgow University, 1997
+%
+\section[MutableArray]{The @MutableArray@ interface}
+
+Mutable (byte)arrays interface, re-exports type types and operations
+over them from @ArrBase@. Have to be used in conjunction with
+@ST@.
+
+\begin{code}
+module MutableArray 
+   (
+    MutableArray(..),        -- not abstract
+    MutableByteArray(..),
+
+    ST,
+    Ix,
+
+    -- Creators:
+    newArray,           -- :: Ix ix => (ix,ix) -> elt -> ST s (MutableArray s ix elt)
+    newCharArray,
+    newAddrArray,
+    newIntArray,
+    newFloatArray,
+    newDoubleArray,     -- :: Ix ix => (ix,ix) -> ST s (MutableByteArray s ix) 
+
+    boundsOfArray,      -- :: Ix ix => MutableArray s ix elt -> (ix, ix)  
+    boundsOfByteArray,  -- :: Ix ix => MutableByteArray s ix -> (ix, ix)
+
+    readArray,   	-- :: Ix ix => MutableArray s ix elt -> ix -> ST s elt 
+
+    readCharArray,      -- :: Ix ix => MutableByteArray s ix -> ix -> ST s Char 
+    readIntArray,       -- :: Ix ix => MutableByteArray s ix -> ix -> ST s Int
+    readAddrArray,      -- :: Ix ix => MutableByteArray s ix -> ix -> ST s Addr
+    readFloatArray,     -- :: Ix ix => MutableByteArray s ix -> ix -> ST s Float
+    readDoubleArray,    -- :: Ix ix => MutableByteArray s ix -> ix -> ST s Double
+
+    writeArray,  	-- :: Ix ix => MutableArray s ix elt -> ix -> elt -> ST s () 
+    writeCharArray,     -- :: Ix ix => MutableByteArray s ix -> ix -> Char -> ST s () 
+    writeIntArray,      -- :: Ix ix => MutableByteArray s ix -> ix -> Int  -> ST s () 
+    writeAddrArray,     -- :: Ix ix => MutableByteArray s ix -> ix -> Addr -> ST s () 
+    writeFloatArray,    -- :: Ix ix => MutableByteArray s ix -> ix -> Float -> ST s () 
+    writeDoubleArray,   -- :: Ix ix => MutableByteArray s ix -> ix -> Double -> ST s () 
+
+    freezeArray,	-- :: Ix ix => MutableArray s ix elt -> ST s (Array ix elt)
+    freezeCharArray,    -- :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
+    freezeIntArray,     -- :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
+    freezeAddrArray,    -- :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
+    freezeFloatArray,   -- :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
+    freezeDoubleArray,  -- :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
+
+    unsafeFreezeArray,     -- :: Ix ix => MutableArray s ix elt -> ST s (Array ix elt)  
+    unsafeFreezeByteArray, -- :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
+    thawArray              -- :: Ix ix => Array ix elt -> ST s (MutableArray s ix elt)
+
+    ) where
+
+import ArrBase
+import ST
+import Ix
+
+\end{code}