X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Futils%2FStringBuffer.lhs;h=d7cfdddc2e31c1319aabdc5bd92baaec74acc564;hb=753d8919d892ed0f62fae63241f09610b1eda67e;hp=3119a13c4971d7bad49fe1e85fcc3d8c61d6d6cc;hpb=9dd6e1c216993624a2cd74b62ca0f0569c02c26b;p=ghc-hetmet.git diff --git a/ghc/compiler/utils/StringBuffer.lhs b/ghc/compiler/utils/StringBuffer.lhs index 3119a13..d7cfddd 100644 --- a/ghc/compiler/utils/StringBuffer.lhs +++ b/ghc/compiler/utils/StringBuffer.lhs @@ -1,5 +1,5 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1997 +% (c) The GRASP/AQUA Project, Glasgow University, 1997-1998 % \section{String buffers} @@ -7,19 +7,16 @@ Buffers for scanning string input stored in external arrays. \begin{code} -{-# OPTIONS -fno-prune-tydecls #-} --- Don't really understand this! --- ERROR: Can't see the data constructor(s) for _ccall_/_casm_ argument; --- type: ForeignObj(try compiling with -fno-prune-tydecls ..) - +{-# OPTIONS -optc-DNON_POSIX_SOURCE #-} module StringBuffer ( StringBuffer, - -- creation - hGetStringBuffer, -- :: FilePath -> IO StringBuffer - freeStringBuffer, -- :: StringBuffer -> IO () + -- creation/destruction + hGetStringBuffer, -- :: FilePath -> IO StringBuffer + stringToStringBuffer, -- :: String -> IO StringBuffer + freeStringBuffer, -- :: StringBuffer -> IO () -- Lookup currentChar, -- :: StringBuffer -> Char @@ -30,19 +27,27 @@ module StringBuffer lookAhead, -- :: StringBuffer -> Int -> Char lookAhead#, -- :: StringBuffer -> Int# -> Char# + -- offsets + currentIndex#, -- :: StringBuffer -> Int# + lexemeIndex, -- :: StringBuffer -> Int# + -- moving the end point of the current lexeme. - setCurrentPos#, -- :: StringBuffer -> Int# -> StringBuffer - incLexeme, -- :: StringBuffer -> StringBuffer - decLexeme, -- :: StringBuffer -> StringBuffer + addToCurrentPos, -- :: StringBuffer -> Int# -> StringBuffer + incCurrentPos, -- :: StringBuffer -> StringBuffer + decCurrentPos, -- :: StringBuffer -> StringBuffer -- move the start and end lexeme pointer on by x units. stepOn, -- :: StringBuffer -> StringBuffer stepOnBy#, -- :: StringBuffer -> Int# -> StringBuffer stepOnTo#, -- :: StringBuffer -> Int# -> StringBuffer stepOnUntil, -- :: (Char -> Bool) -> StringBuffer -> StringBuffer + stepOnUntilChar#, -- :: StringBuffer -> Char# -> StringBuffer stepOverLexeme, -- :: StringBuffer -> StringBuffer scanNumLit, -- :: Int -> StringBuffer -> (Int, StringBuffer) - expandWhile, -- :: (Char -> Bool) -> StringBuffer -> StringBuffer + squeezeLexeme, -- :: StringBuffer -> Int# -> StringBuffer + mergeLexemes, -- :: StringBuffer -> StringBuffer -> StringBuffer + expandWhile, -- :: (Char -> Bool) -> StringBuffer -> StringBuffer + expandWhile#, -- :: (Char# -> Bool) -> StringBuffer -> StringBuffer expandUntilMatch, -- :: StrinBuffer -> String -> StringBuffer -- at or beyond end of buffer? bufferExhausted, -- :: StringBuffer -> Bool @@ -51,131 +56,300 @@ module StringBuffer -- matching prefixMatch, -- :: StringBuffer -> String -> Bool untilEndOfString#, -- :: StringBuffer -> Int# - untilEndOfChar#, -- :: StringBuffer -> Int# - untilChar#, -- :: StringBuffer -> Char# -> Int# -- conversion lexemeToString, -- :: StringBuffer -> String - lexemeToByteArray, -- :: StringBuffer -> _ByteArray Int lexemeToFastString, -- :: StringBuffer -> FastString - lexemeToBuffer, -- :: StringBuffer -> StringBuffer - - FastString, - ByteArray ) where #include "HsVersions.h" -import GlaExts -import Addr ( Addr(..) ) -import Foreign -import IOBase -import IOHandle -import ST -import STBase -import Char (isDigit) -import PackBase + +#if __GLASGOW_HASKELL__ < 502 +import Panic ( panic ) +#else +#if __GLASGOW_HASKELL__ < 503 +import Ptr ( Ptr(..) ) +#else +import GHC.Ptr ( Ptr(..) ) +#endif +#endif + +#if __GLASGOW_HASKELL__ < 501 +import Char ( chr ) +#elif __GLASGOW_HASKELL__ < 503 +import PrelIO ( hGetcBuffered ) +#else +import GHC.IO ( hGetcBuffered ) +#endif + import PrimPacked import FastString +import GLAEXTS + +import Foreign + +#if __GLASGOW_HASKELL__ >= 502 +import CString ( newCString ) +#endif + +import IO ( openFile, isEOFError ) +import EXCEPTION ( bracket ) + +#if __GLASGOW_HASKELL__ < 503 +import PrelIOBase +import PrelHandle +#else +import GHC.IOBase +import GHC.Handle +#endif + +import Char ( isDigit ) \end{code} \begin{code} data StringBuffer = StringBuffer Addr# --- ForeignObj# -- the data Int# -- length Int# -- lexeme start Int# -- current pos \end{code} \begin{code} -instance Text StringBuffer where - showsPrec _ s = showString "" +instance Show StringBuffer where + showsPrec _ s = showString "" \end{code} \begin{code} hGetStringBuffer :: FilePath -> IO StringBuffer -hGetStringBuffer fname = --- trace ("Renamer: opening " ++ fname) $ - openFile fname ReadMode >>= \ hndl -> - hFileSize hndl >>= \ len@(J# _ _ d#) -> - let len_i = fromInteger len in - -- Allocate an array for system call to store its bytes into. - -- ToDo: make it robust --- trace (show ((len_i::Int)+1)) $ - _casm_ `` %r=(char *)malloc(sizeof(char)*(int)%0); '' (len_i::Int) >>= \ arr@(A# a#) -> - if addr2Int# a# ==# 0# then - failWith MkIOError(hndl,UserError,("hGetStringBuffer: Could not allocate "++show len_i ++ " bytes")) - else - --- _casm_ `` %r=NULL; '' >>= \ free_p -> --- makeForeignObj arr free_p >>= \ fo@(_ForeignObj fo#) -> - readHandle hndl >>= \ hndl_ -> - writeHandle hndl hndl_ >> - let ptr = _filePtr hndl_ in - _ccall_ fread arr (1::Int) len_i ptr >>= \ (I# read#) -> --- trace ("DEBUG: opened " ++ fname ++ show (I# read#)) $ - hClose hndl >> - if read# ==# 0# then -- EOF or other error - failWith MkIOError(hndl,UserError,"hGetStringBuffer: EOF reached or some other error") - else - -- Add a sentinel NUL - _casm_ `` ((char *)%0)[(int)%1]=(char)0; '' arr (I# (read# -# 1#)) >>= \ () -> - return (StringBuffer a# read# 0# 0#) +hGetStringBuffer fname = do + (a, read) <- slurpFileExpandTabs fname + -- urk! slurpFile gives us a buffer that doesn't have room for + -- the sentinel. Assume it has a final newline for now, and overwrite + -- that with the sentinel. slurpFileExpandTabs (below) leaves room + -- for the sentinel. + let (Ptr a#) = a; + (I# read#) = read; + end# = read# -# 1# + + -- add sentinel '\NUL' + writeCharOffPtr a (I# end#) '\0' + + return (StringBuffer a# end# 0# 0#) +\end{code} + +----------------------------------------------------------------------------- +-- Turn a String into a StringBuffer + +\begin{code} +stringToStringBuffer :: String -> IO StringBuffer freeStringBuffer :: StringBuffer -> IO () -freeStringBuffer (StringBuffer a# _ _ _) = - _casm_ `` free((char *)%0); '' (A# a#) -unsafeWriteBuffer :: StringBuffer -> Int# -> Char# -> StringBuffer -unsafeWriteBuffer s@(StringBuffer a _ _ _) i# ch# = - unsafePerformIO ( - _casm_ `` ((char *)%0)[(int)%1]=(char)%2; '' (A# a) (I# i#) (C# ch#) >>= \ () -> - return s - ) +#if __GLASGOW_HASKELL__ >= 502 +stringToStringBuffer str = do + let sz@(I# sz#) = length str + Ptr a# <- newCString str + return (StringBuffer a# sz# 0# 0#) + +freeStringBuffer (StringBuffer a# _ _ _) = Foreign.free (Ptr a#) +#else +stringToStringBuffer = panic "stringToStringBuffer: not implemented" +freeStringBuffer sb = return () +#endif \end{code} -Lookup +----------------------------------------------------------------------------- +This very disturbing bit of code is used for expanding the tabs in a +file before we start parsing it. Expanding the tabs early makes the +lexer a lot simpler: we only have to record the beginning of the line +in order to be able to calculate the column offset of the current +token. + +We guess the size of the buffer required as 20% extra for +expanded tabs, and enlarge it if necessary. \begin{code} -currentChar# :: StringBuffer -> Char# -currentChar# (StringBuffer fo# _ _ current#) = indexCharOffAddr# fo# current# +#if __GLASGOW_HASKELL__ < 501 +getErrType :: IO Int +getErrType = _ccall_ getErrType__ +#endif + +slurpFileExpandTabs :: FilePath -> IO (Ptr (),Int) +slurpFileExpandTabs fname = do + bracket (openFile fname ReadMode) (hClose) + (\ handle -> + do sz <- hFileSize handle + if sz > toInteger (maxBound::Int) + then ioError (userError "slurpFile: file too big") + else do + let sz_i = fromInteger sz + if sz_i == 0 + -- empty file: just allocate a buffer containing '\0' + then do chunk <- allocMem 1 + writeCharOffPtr chunk 0 '\0' + return (chunk, 0) + else do let sz_i' = (sz_i * 12) `div` 10 -- add 20% for tabs + chunk <- allocMem sz_i' + trySlurp handle sz_i' chunk + ) + +trySlurp :: Handle -> Int -> Ptr () -> IO (Ptr (), Int) +trySlurp handle sz_i chunk = +#if __GLASGOW_HASKELL__ < 501 + wantReadableHandle "hGetChar" handle $ \ handle_ -> + let fo = haFO__ handle_ in +#else + wantReadableHandle "hGetChar" handle $ + \ handle_@Handle__{ haFD=fd, haBuffer=ref, haBufferMode=mode } -> +#endif + let + (I# chunk_sz) = sz_i + + tAB_SIZE = 8# + + slurpFile :: Int# -> Int# -> Ptr () -> Int# -> Int# -> IO (Ptr (), Int) + slurpFile c off chunk chunk_sz max_off = slurp c off + where + + slurp :: Int# -> Int# -> IO (Ptr (), Int) + slurp c off | off >=# max_off = do + let new_sz = chunk_sz *# 2# + chunk' <- reAllocMem chunk (I# new_sz) + slurpFile c off chunk' new_sz (new_sz -# (tAB_SIZE +# 1#)) + slurp c off = do +#if __GLASGOW_HASKELL__ < 501 + intc <- mayBlock fo (_ccall_ fileGetc fo) + if intc == ((-1)::Int) + then do errtype <- getErrType + if errtype == (19{-ERR_EOF-} :: Int) + then return (chunk, I# off) + else constructErrorAndFail "slurpFile" + else case chr intc of +#else + buf <- readIORef ref + ch <- (if not (bufferEmpty buf) + then hGetcBuffered fd ref buf + else do +#if __GLASGOW_HASKELL__ >= 503 + new_buf <- fillReadBuffer fd True False buf +#else + new_buf <- fillReadBuffer fd True buf +#endif + hGetcBuffered fd ref new_buf) + `catch` \e -> if isEOFError e + then return '\xFFFF' + else ioError e + case ch of + '\xFFFF' -> return (chunk, I# off) +#endif + '\t' -> tabIt c off + ch -> do writeCharOffPtr chunk (I# off) ch + let c' | ch == '\n' = 0# + | otherwise = c +# 1# + slurp c' (off +# 1#) + + tabIt :: Int# -> Int# -> IO (Ptr (), Int) + -- can't run out of buffer in here, because we reserved an + -- extra tAB_SIZE bytes at the end earlier. + tabIt c off = do + writeCharOffPtr chunk (I# off) ' ' + let c' = c +# 1# + off' = off +# 1# + if c' `remInt#` tAB_SIZE ==# 0# + then slurp c' off' + else tabIt c' off' + in do + + -- allow space for a full tab at the end of the buffer + -- (that's what the max_off thing is for), + -- and add 1 to allow room for the final sentinel \NUL at + -- the end of the file. + (chunk', rc) <- slurpFile 0# 0# chunk chunk_sz (chunk_sz -# (tAB_SIZE +# 1#)) + return (chunk', rc+1 {- room for sentinel -}) + + +reAllocMem :: Ptr () -> Int -> IO (Ptr ()) +reAllocMem ptr sz = do + chunk <- c_realloc ptr sz + if chunk == nullPtr + then fail "reAllocMem" + else return chunk + +allocMem :: Int -> IO (Ptr ()) +allocMem sz = do + chunk <- c_malloc sz + if chunk == nullPtr +#if __GLASGOW_HASKELL__ < 501 + then constructErrorAndFail "allocMem" +#else + then ioException (IOError Nothing ResourceExhausted "malloc" + "out of memory" Nothing) +#endif + else return chunk + +#if __GLASGOW_HASKELL__ <= 408 +c_malloc sz = do A# a <- c_malloc' sz; return (Ptr a) +foreign import ccall "malloc" unsafe + c_malloc' :: Int -> IO Addr + +c_realloc (Ptr a) sz = do A# a <- c_realloc' (A# a) sz; return (Ptr a) +foreign import ccall "realloc" unsafe + c_realloc' :: Addr -> Int -> IO Addr +#else +foreign import ccall "malloc" unsafe + c_malloc :: Int -> IO (Ptr a) + +foreign import ccall "realloc" unsafe + c_realloc :: Ptr a -> Int -> IO (Ptr a) +#endif +\end{code} + +Lookup +\begin{code} currentChar :: StringBuffer -> Char currentChar sb = case currentChar# sb of c -> C# c -indexSBuffer# :: StringBuffer -> Int# -> Char# -indexSBuffer# (StringBuffer fo# _ _ _) i# = indexCharOffAddr# fo# i# +lookAhead :: StringBuffer -> Int -> Char +lookAhead sb (I# i#) = case lookAhead# sb i# of c -> C# c indexSBuffer :: StringBuffer -> Int -> Char indexSBuffer sb (I# i#) = case indexSBuffer# sb i# of c -> C# c - -- relative lookup, i.e, currentChar = lookAhead 0 +currentChar# :: StringBuffer -> Char# +indexSBuffer# :: StringBuffer -> Int# -> Char# lookAhead# :: StringBuffer -> Int# -> Char# +currentChar# (StringBuffer fo# _ _ current#) = indexCharOffAddr# fo# current# +indexSBuffer# (StringBuffer fo# _ _ _) i# = indexCharOffAddr# fo# i# + + -- relative lookup, i.e, currentChar = lookAhead 0 lookAhead# (StringBuffer fo# _ _ c#) i# = indexCharOffAddr# fo# (c# +# i#) -lookAhead :: StringBuffer -> Int -> Char -lookAhead sb (I# i#) = case lookAhead# sb i# of c -> C# c +currentIndex# :: StringBuffer -> Int# +currentIndex# (StringBuffer fo# _ _ c#) = c# +lexemeIndex :: StringBuffer -> Int# +lexemeIndex (StringBuffer fo# _ c# _) = c# \end{code} moving the start point of the current lexeme. \begin{code} -- moving the end point of the current lexeme. -setCurrentPos# :: StringBuffer -> Int# -> StringBuffer -setCurrentPos# (StringBuffer fo l# s# c#) i# = +addToCurrentPos :: StringBuffer -> Int# -> StringBuffer +addToCurrentPos (StringBuffer fo l# s# c#) i# = StringBuffer fo l# s# (c# +# i#) -- augmenting the current lexeme by one. -incLexeme :: StringBuffer -> StringBuffer -incLexeme (StringBuffer fo l# s# c#) = StringBuffer fo l# s# (c# +# 1#) +incCurrentPos :: StringBuffer -> StringBuffer +incCurrentPos (StringBuffer fo l# s# c#) = StringBuffer fo l# s# (c# +# 1#) -decLexeme :: StringBuffer -> StringBuffer -decLexeme (StringBuffer fo l# s# c#) = StringBuffer fo l# s# (c# -# 1#) +decCurrentPos :: StringBuffer -> StringBuffer +decCurrentPos (StringBuffer fo l# s# c#) = StringBuffer fo l# s# (c# -# 1#) \end{code} @@ -195,7 +369,15 @@ stepOnBy# (StringBuffer fo# l# s# c#) i# = stepOnTo# :: StringBuffer -> Int# -> StringBuffer stepOnTo# (StringBuffer fo l _ _) s# = StringBuffer fo l s# s# +squeezeLexeme :: StringBuffer -> Int# -> StringBuffer +squeezeLexeme (StringBuffer fo l s# c#) i# = StringBuffer fo l (s# +# i#) c# + +mergeLexemes :: StringBuffer -> StringBuffer -> StringBuffer +mergeLexemes (StringBuffer fo l s# _) (StringBuffer _ _ _ c#) + = StringBuffer fo l s# c# + stepOnUntil :: (Char -> Bool) -> StringBuffer -> StringBuffer + stepOnUntil pred (StringBuffer fo l# s# c#) = loop c# where @@ -218,28 +400,38 @@ expandWhile pred (StringBuffer fo l# s# c#) = | ch# `eqChar#` '\NUL'# && c# >=# l# -> StringBuffer fo l# l# l# -- EOB, return immediately. | otherwise -> StringBuffer fo l# s# c# +expandWhile# :: (Char# -> Bool) -> StringBuffer -> StringBuffer +expandWhile# pred (StringBuffer fo l# s# c#) = + loop c# + where + loop c# = + case indexCharOffAddr# fo c# of + ch# | pred ch# -> loop (c# +# 1#) + | ch# `eqChar#` '\NUL'# && c# >=# l# -> StringBuffer fo l# s# c# -- EOB, return immediately. + | otherwise -> StringBuffer fo l# s# c# -scanNumLit :: Int -> StringBuffer -> (Int,StringBuffer) -scanNumLit (I# acc#) (StringBuffer fo l# s# c#) = - loop acc# c# +scanNumLit :: Integer -> StringBuffer -> (Integer,StringBuffer) +scanNumLit acc (StringBuffer fo l# s# c#) = + loop acc c# where - loop acc# c# = + loop acc c# = case indexCharOffAddr# fo c# of - ch# | isDigit (C# ch#) -> loop (acc# *# 10# +# (ord# ch# -# ord# '0'#)) (c# +# 1#) - | ch# `eqChar#` '\NUL'# && c# >=# l# -> (I# acc#, StringBuffer fo l# l# l#) -- EOB, return immediately. - | otherwise -> (I# acc#,StringBuffer fo l# s# c#) + ch# | isDigit (C# ch#) -> loop (acc*10 + (toInteger (I# (ord# ch# -# ord# '0'#)))) (c# +# 1#) + | ch# `eqChar#` '\NUL'# && c# >=# l# -> (acc, StringBuffer fo l# s# c#) -- EOB, return immediately. + | otherwise -> (acc,StringBuffer fo l# s# c#) -expandUntilMatch :: StringBuffer -> String -> StringBuffer +expandUntilMatch :: StringBuffer -> String -> Maybe StringBuffer expandUntilMatch (StringBuffer fo l# s# c#) str = loop c# str where - loop c# [] = StringBuffer fo l# s# c# + loop c# [] = Just (StringBuffer fo l# s# c#) loop c# ((C# x#):xs) = - if indexCharOffAddr# fo c# `eqChar#` x# then - loop (c# +# 1#) xs - else - loop (c# +# 1#) str + case indexCharOffAddr# fo c# of + ch# | ch# `eqChar#` '\NUL'# && c# >=# l# -> Nothing + | ch# `eqChar#` x# -> loop (c# +# 1#) xs + | otherwise -> loop (c# +# 1#) str + \end{code} \begin{code} @@ -256,27 +448,29 @@ prefixMatch (StringBuffer fo l# s# c#) str = loop c# str where loop c# [] = Just (StringBuffer fo l# s# c#) - loop c# ((C# x#):xs) = - if indexCharOffAddr# fo c# `eqChar#` x# then - loop (c# +# 1#) xs - else - Nothing + loop c# ((C# x#):xs) + | indexCharOffAddr# fo c# `eqChar#` x# + = loop (c# +# 1#) xs + | otherwise + = Nothing untilEndOfString# :: StringBuffer -> StringBuffer untilEndOfString# (StringBuffer fo l# s# c#) = loop c# where + getch# i# = indexCharOffAddr# fo i# + loop c# = - case indexCharOffAddr# fo c# of + case getch# c# of '\"'# -> - case indexCharOffAddr# fo (c# -# 1#) of + case getch# (c# -# 1#) of '\\'# -> -- looks like an escaped something or other to me, -- better count the number of "\\"s that are immediately -- preceeding to decide if the " is escaped. let odd_slashes flg i# = - case indexCharOffAddr# fo i# of + case getch# i# of '\\'# -> odd_slashes (not flg) (i# -# 1#) _ -> flg in @@ -294,75 +488,29 @@ untilEndOfString# (StringBuffer fo l# s# c#) = _ -> loop (c# +# 1#) -untilEndOfChar# :: StringBuffer -> StringBuffer -untilEndOfChar# (StringBuffer fo l# s# c#) = - loop c# - where - loop c# = - case indexCharOffAddr# fo c# of - '\''# -> - case indexCharOffAddr# fo (c# -# 1#) of - '\\'# -> - case indexCharOffAddr# fo (c# -# 2#) of - '\\'# -> -- end of char - StringBuffer fo l# s# c# - _ -> loop (c# +# 1#) -- false alarm - _ -> StringBuffer fo l# s# c# - '\NUL'# -> - if c# >=# l# then -- hit sentinel, this doesn't look too good.. - StringBuffer fo l# l# l# - else - loop (c# +# 1#) - _ -> loop (c# +# 1#) - -untilChar# :: StringBuffer -> Char# -> StringBuffer -untilChar# (StringBuffer fo l# s# c#) x# = +stepOnUntilChar# :: StringBuffer -> Char# -> StringBuffer +stepOnUntilChar# (StringBuffer fo l# s# c#) x# = loop c# where - loop c# = - if indexCharOffAddr# fo c# `eqChar#` x# then - StringBuffer fo l# s# c# - else - loop (c# +# 1#) + loop c# + | c# >=# l# || indexCharOffAddr# fo c# `eqChar#` x# + = StringBuffer fo l# c# c# + | otherwise + = loop (c# +# 1#) -- conversion lexemeToString :: StringBuffer -> String -lexemeToString (StringBuffer fo _ start_pos# current#) = +lexemeToString (StringBuffer fo len# start_pos# current#) = if start_pos# ==# current# then "" else -#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 205 - byteArrayToString (copySubStr (A# fo) (I# start_pos#) (I# (current# -# start_pos#))) -#else - unpackCStringBA (copySubStr (A# fo) (I# start_pos#) (I# (current# -# start_pos#))) -#endif - -lexemeToByteArray :: StringBuffer -> _ByteArray Int -lexemeToByteArray (StringBuffer fo _ start_pos# current#) = - if start_pos# ==# current# then - error "lexemeToByteArray" - else - copySubStr (A# fo) (I# start_pos#) (I# (current# -# start_pos#)) + let len = I# (current# -# start_pos#) in + unpackNBytesBA (copySubStr fo (I# start_pos#) len) len lexemeToFastString :: StringBuffer -> FastString lexemeToFastString (StringBuffer fo l# start_pos# current#) = if start_pos# ==# current# then - mkFastCharString2 (A# fo) (I# 0#) + mkFastString "" else - mkFastSubString (A# fo) (I# start_pos#) (I# (current# -# start_pos#)) - -{- - Create a StringBuffer from the current lexeme, and add a sentinel - at the end. Know What You're Doing before taking this function - into use.. --} -lexemeToBuffer :: StringBuffer -> StringBuffer -lexemeToBuffer (StringBuffer fo l# start_pos# current#) = - if start_pos# ==# current# then - StringBuffer fo 0# start_pos# current# -- an error, really. - else - unsafeWriteBuffer (StringBuffer fo (current# -# start_pos#) start_pos# start_pos#) - (current# -# 1#) - '\NUL'# - + mkFastSubString fo (I# start_pos#) (I# (current# -# start_pos#)) \end{code}