[project @ 2000-04-13 19:31:05 by panne]
[ghc-hetmet.git] / ghc / compiler / utils / FastString.lhs
index d5d4997..3d63e7f 100644 (file)
@@ -1,5 +1,5 @@
 %
-% (c) The GRASP/AQUA Project, Glasgow University, 1997
+% (c) The GRASP/AQUA Project, Glasgow University, 1997-1998
 %
 \section{Fast strings}
 
@@ -39,6 +39,7 @@ module FastString
         tailFS,                    -- :: FastString -> FastString
        concatFS,           -- :: [FastString] -> FastString
         consFS,             -- :: Char -> FastString -> FastString
+       indexFS,            -- :: FastString -> Int -> Char
 
         hPutFS             -- :: Handle -> FastString -> IO ()
        ) where
@@ -58,15 +59,24 @@ import IOBase               ( Handle__(..), IOError(..), IOErrorType(..),
                        )
 #else
 import PrelPack
+#if __GLASGOW_HASKELL__ < 400
 import PrelST          ( StateAndPtr#(..) )
+#endif
+
+#if __GLASGOW_HASKELL__ <= 303
 import PrelHandle      ( readHandle, 
-#if __GLASGOW_HASKELL__ < 303
+# if __GLASGOW_HASKELL__ < 303
                          filePtr,
-#endif
+# endif
                          writeHandle
                        )
+#endif
+
 import PrelIOBase      ( Handle__(..), IOError(..), IOErrorType(..),
-                         IOResult(..), IO(..),
+#if __GLASGOW_HASKELL__ < 400
+                         IOResult(..), 
+#endif
+                         IO(..),
 #if __GLASGOW_HASKELL__ >= 303
                          Handle__Type(..),
 #endif
@@ -76,8 +86,13 @@ import PrelIOBase    ( Handle__(..), IOError(..), IOErrorType(..),
 
 import PrimPacked
 import GlaExts
-import Addr            ( Addr(..) )
+import PrelAddr                ( Addr(..) )
+#if __GLASGOW_HASKELL__ < 407
 import MutableArray    ( MutableArray(..) )
+#else
+import PrelArr         ( STArray(..), newSTArray )
+import IOExts          ( hPutBuf, hPutBufBA )
+#endif
 
 -- ForeignObj is now exported abstractly.
 #if __GLASGOW_HASKELL__ >= 303
@@ -90,6 +105,10 @@ import IOExts               ( IORef, newIORef, readIORef, writeIORef )
 import IO
 
 #define hASH_TBL_SIZE 993
+
+#if __GLASGOW_HASKELL__ >= 400
+#define IOok STret
+#endif
 \end{code} 
 
 @FastString@s are packed representations of strings
@@ -126,15 +145,15 @@ instance Ord FastString where
             | otherwise        =  y
     compare a b = cmpFS a b
 
-instance Text FastString  where
-    showsPrec p ps@(FastString u# _ _) r = showsPrec p (unpackFS ps) r
-    showsPrec p ps r = showsPrec p (unpackFS ps) r
-
 getByteArray# :: FastString -> ByteArray#
 getByteArray# (FastString _ _ ba#) = ba#
 
 getByteArray :: FastString -> ByteArray Int
+#if __GLASGOW_HASKELL__ < 405
 getByteArray (FastString _ l# ba#) = ByteArray (0,I# l#) ba#
+#else
+getByteArray (FastString _ l# ba#) = ByteArray 0 (I# l#) ba#
+#endif
 
 lengthFS :: FastString -> Int
 lengthFS (FastString _ l# _) = I# l#
@@ -145,7 +164,7 @@ nullFastString (FastString _ l# _) = l# ==# 0#
 nullFastString (CharStr _ l#) = l# ==# 0#
 
 unpackFS :: FastString -> String
-unpackFS (FastString _ l# ba#) = unpackCStringBA# ba# l#
+unpackFS (FastString _ l# ba#) = unpackNBytesBA# ba# l#
 unpackFS (CharStr addr len#) =
  unpack 0#
  where
@@ -167,6 +186,18 @@ headFS f@(FastString _ l# ba#) =
 headFS f@(CharStr a# l#) = 
  if l# ># 0# then C# (indexCharOffAddr# a# 0#) else error ("headFS: empty FS: " ++ unpackFS f)
 
+indexFS :: FastString -> Int -> Char
+indexFS f i@(I# i#) =
+ case f of
+   FastString _ l# ba#
+     | l# ># 0# && l# ># i#  -> C# (indexCharArray# ba# i#)
+     | otherwise            -> error (msg (I# l#))
+   CharStr a# l#
+     | l# ># 0# && l# ># i#  -> C# (indexCharOffAddr# a# i#)
+     | otherwise            -> error (msg (I# l#))
+ where
+  msg l =  "indexFS: out of range: " ++ show (l,i)
+
 tailFS :: FastString -> FastString
 tailFS (FastString _ l# ba#) = mkFastSubStringBA# ba# 1# (l# -# 1#)
 
@@ -206,18 +237,36 @@ type FastStringTableVar = IORef FastStringTable
 string_table :: FastStringTableVar
 string_table = 
  unsafePerformIO (
-   stToIO (newArray (0::Int,hASH_TBL_SIZE) [])         >>= \ (MutableArray _ arr#) ->
+#if __GLASGOW_HASKELL__ < 405
+   stToIO (newArray (0::Int,hASH_TBL_SIZE) [])
+       >>= \ (MutableArray _ arr#) ->
+#elif __GLASGOW_HASKELL__ < 407
+   stToIO (newArray (0::Int,hASH_TBL_SIZE) [])
+       >>= \ (MutableArray _ _ arr#) ->
+#else
+   stToIO (newSTArray (0::Int,hASH_TBL_SIZE) [])
+       >>= \ (STArray _ _ arr#) ->
+#endif
    newIORef (FastStringTable 0# arr#))
 
 lookupTbl :: FastStringTable -> Int# -> IO [FastString]
 lookupTbl (FastStringTable _ arr#) i# =
   IO ( \ s# ->
+#if __GLASGOW_HASKELL__ < 400
   case readArray# arr# i# s# of { StateAndPtr# s2# r ->
   IOok s2# r })
+#else
+  readArray# arr# i# s#)
+#endif
 
 updTbl :: FastStringTableVar -> FastStringTable -> Int# -> [FastString] -> IO ()
 updTbl fs_table_var (FastStringTable uid# arr#) i# ls =
- IO (\ s# -> case writeArray# arr# i# ls s# of { s2# -> IOok s2# () }) >>
+ IO (\ s# -> case writeArray# arr# i# ls s# of { s2# -> 
+#if __GLASGOW_HASKELL__ < 400
+       IOok s2# () })  >>
+#else
+       (# s2#, () #) }) >>
+#endif
  writeIORef fs_table_var (FastStringTable (uid# +# 1#) arr#)
 
 mkFastString# :: Addr# -> Int# -> FastString
@@ -235,7 +284,11 @@ mkFastString# a# len# =
        -- the string into a ByteArray
        -- _trace "empty bucket" $
        case copyPrefixStr (A# a#) (I# len#) of
+#if __GLASGOW_HASKELL__ < 405
         (ByteArray _ barr#) ->  
+#else
+        (ByteArray _ _ barr#) ->  
+#endif
           let f_str = FastString uid# len# barr# in
            updTbl string_table ft h [f_str] >>
            ({- _trace ("new: " ++ show f_str)   $ -} return f_str)
@@ -246,7 +299,11 @@ mkFastString# a# len# =
        case bucket_match ls len# a# of
         Nothing -> 
            case copyPrefixStr (A# a#) (I# len#) of
-           (ByteArray _ barr#) ->  
+#if __GLASGOW_HASKELL__ < 405
+            (ByteArray _ barr#) ->  
+#else
+            (ByteArray _ _ barr#) ->  
+#endif
               let f_str = FastString uid# len# barr# in
               updTbl string_table ft h (f_str:ls) >>
              ( {- _trace ("new: " ++ show f_str)  $ -} return f_str)
@@ -275,7 +332,11 @@ mkFastSubStringFO# fo# start# len# =
        -- no match, add it to table by copying out the
        -- the string into a ByteArray
        case copySubStrFO (_ForeignObj fo#) (I# start#) (I# len#) of
+#if __GLASGOW_HASKELL__ < 405
         (ByteArray _ barr#) ->  
+#else
+        (ByteArray _ _ barr#) ->  
+#endif
           let f_str = FastString uid# len# barr# in
            updTbl string_table ft h [f_str]       >>
           return f_str
@@ -285,7 +346,11 @@ mkFastSubStringFO# fo# start# len# =
        case bucket_match ls start# len# fo# of
         Nothing -> 
            case copySubStrFO (_ForeignObj fo#) (I# start#) (I# len#) of
-            (ByteArray _ barr#) ->  
+#if __GLASGOW_HASKELL__ < 405
+            (ByteArray _ barr#) ->  
+#else
+            (ByteArray _ _ barr#) ->  
+#endif
               let f_str = FastString uid# len# barr# in
               updTbl string_table ft  h (f_str:ls) >>
              ( {- _trace ("new: " ++ show f_str) $ -} return f_str)
@@ -313,8 +378,13 @@ mkFastSubStringBA# barr# start# len# =
        -- no match, add it to table by copying out the
        -- the string into a ByteArray
        -- _trace "empty bucket(b)" $
+#if __GLASGOW_HASKELL__ < 405
        case copySubStrBA (ByteArray btm barr#) (I# start#) (I# len#) of
          (ByteArray _ ba#) ->  
+#else
+       case copySubStrBA (ByteArray btm btm barr#) (I# start#) (I# len#) of
+         (ByteArray _ _ ba#) ->  
+#endif
           let f_str = FastString uid# len# ba# in
           updTbl string_table ft h [f_str]     >>
           -- _trace ("new(b): " ++ show f_str)   $
@@ -325,8 +395,13 @@ mkFastSubStringBA# barr# start# len# =
        -- _trace ("non-empty bucket(b)"++show ls) $
        case bucket_match ls start# len# barr# of
         Nothing -> 
-          case copySubStrBA (ByteArray (error "") barr#) (I# start#) (I# len#) of
+#if __GLASGOW_HASKELL__ < 405
+          case copySubStrBA (ByteArray btm barr#) (I# start#) (I# len#) of
             (ByteArray _ ba#) ->  
+#else
+          case copySubStrBA (ByteArray btm btm barr#) (I# start#) (I# len#) of
+            (ByteArray _ _ ba#) ->  
+#endif
               let f_str = FastString uid# len# ba# in
               updTbl string_table ft h (f_str:ls) >>
              -- _trace ("new(b): " ++ show f_str)   $
@@ -361,7 +436,11 @@ mkFastCharString2 a@(A# a#) (I# len#) = CharStr a# len#
 mkFastString :: String -> FastString
 mkFastString str = 
  case packString str of
+#if __GLASGOW_HASKELL__ < 405
   (ByteArray (_,I# len#) frozen#) -> 
+#else
+  (ByteArray _ (I# len#) frozen#) -> 
+#endif
     mkFastSubStringBA# frozen# 0# len#
     {- 0-indexed array, len# == index to one beyond end of string,
        i.e., (0,1) => empty string.    -}
@@ -435,15 +514,23 @@ cmpFS (FastString u1# _ b1#) (FastString u2# _ b2#) = -- assume non-null chars
      EQ
   else
    unsafePerformIO (
-    _ccall_ strcmp (ByteArray bottom b1#) (ByteArray bottom b2#)       >>= \ (I# res) ->
+#if __GLASGOW_HASKELL__ < 405
+    _ccall_ strcmp (ByteArray bot b1#) (ByteArray bot b2#)     >>= \ (I# res) ->
+#else
+    _ccall_ strcmp (ByteArray bot bot b1#) (ByteArray bot bot b2#) >>= \ (I# res) ->
+#endif
     return (
     if      res <#  0# then LT
     else if res ==# 0# then EQ
     else                   GT
     ))
   where
-   bottom :: (Int,Int)
-   bottom = error "tagCmp"
+#if __GLASGOW_HASKELL__ < 405
+   bot :: (Int,Int)
+#else
+   bot :: Int
+#endif
+   bot = error "tagCmp"
 cmpFS (CharStr bs1 len1) (CharStr bs2 len2)
   = unsafePerformIO (
     _ccall_ strcmp ba1 ba2     >>= \ (I# res) ->
@@ -464,7 +551,11 @@ cmpFS (FastString _ len1 bs1) (CharStr bs2 len2)
      else                   GT
     ))
   where
+#if __GLASGOW_HASKELL__ < 405
     ba1 = ByteArray ((error "")::(Int,Int)) bs1
+#else
+    ba1 = ByteArray (error "") ((error "")::Int) bs1
+#endif
     ba2 = A# bs2
 
 cmpFS a@(CharStr _ _) b@(FastString _ _ _)
@@ -500,7 +591,11 @@ hPutFS handle (FastString _ l# ba#) =
       other -> 
           let fp = filePtr htype in
           -- here we go..
+#if __GLASGOW_HASKELL__ < 405
           _ccall_ writeFile (ByteArray ((error "")::(Int,Int)) ba#) fp (I# l#) >>= \rc ->
+#else
+          _ccall_ writeFile (ByteArray ((error "")::Int) ((error "")::Int) ba#) fp (I# l#) >>= \rc ->
+#endif
           if rc==0 then
               return ()
           else
@@ -533,16 +628,29 @@ hPutFS handle (CharStr a# l#) =
           else
               constructError "hPutFS"          >>= \ err ->
              fail err
+
+
 #else
 hPutFS handle (FastString _ l# ba#)
   | l# ==# 0#  = return ()
-  | otherwise  = hPutBufBA handle (ByteArray bottom ba#) (I# l#)
+#if __GLASGOW_HASKELL__ < 405
+  | otherwise  = hPutBufBA handle (ByteArray bot ba#) (I# l#)
+#elif __GLASGOW_HASKELL__ < 407
+  | otherwise  = hPutBufBA handle (ByteArray bot bot ba#) (I# l#)
+#else
+  | otherwise  = do mba <- stToIO $ unsafeThawByteArray (ByteArray (bot::Int) bot ba#)
+                    hPutBufBA  handle mba (I# l#)
+                    return ()
+#endif
  where
-  bottom = error "hPutFS.ba"
+  bot = error "hPutFS.ba"
+
+--ToDo: avoid silly code duplic.
 
 hPutFS handle (CharStr a# l#)
   | l# ==# 0#  = return ()
-  | otherwise  = hPutBuf handle (A# a#) (I# l#)
+  | otherwise  = do hPutBuf handle (A# a#) (I# l#) ; return ()
+
 
 #endif
 \end{code}