summaryrefslogtreecommitdiff
path: root/compiler/utils/StringBuffer.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/utils/StringBuffer.hs')
-rw-r--r--compiler/utils/StringBuffer.hs40
1 files changed, 39 insertions, 1 deletions
diff --git a/compiler/utils/StringBuffer.hs b/compiler/utils/StringBuffer.hs
index fcc344554b..d75e537fca 100644
--- a/compiler/utils/StringBuffer.hs
+++ b/compiler/utils/StringBuffer.hs
@@ -6,7 +6,7 @@
Buffers for scanning string input stored in external arrays.
-}
-{-# LANGUAGE CPP, MagicHash, UnboxedTuples #-}
+{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-}
{-# OPTIONS_GHC -O #-}
-- We always optimise this, otherwise performance of a non-optimised
-- compiler is severely affected
@@ -32,6 +32,7 @@ module StringBuffer
stepOn,
offsetBytes,
byteDiff,
+ atLine,
-- * Conversion
lexemeToString,
@@ -240,6 +241,43 @@ byteDiff s1 s2 = cur s2 - cur s1
atEnd :: StringBuffer -> Bool
atEnd (StringBuffer _ l c) = l == c
+-- | Computes a 'StringBuffer' which points to the first character of the
+-- wanted line. Lines begin at 1.
+atLine :: Int -> StringBuffer -> Maybe StringBuffer
+atLine line sb@(StringBuffer buf len _) =
+ inlinePerformIO $
+ withForeignPtr buf $ \p -> do
+ p' <- skipToLine line len p
+ if p' == nullPtr
+ then return Nothing
+ else
+ let
+ delta = p' `minusPtr` p
+ in return $ Just (sb { cur = delta
+ , len = len - delta
+ })
+
+skipToLine :: Int -> Int -> Ptr Word8 -> IO (Ptr Word8)
+skipToLine !line !len !op0 = go 1 op0
+ where
+ !opend = op0 `plusPtr` len
+
+ go !i_line !op
+ | op >= opend = pure nullPtr
+ | i_line == line = pure op
+ | otherwise = do
+ w <- peek op :: IO Word8
+ case w of
+ 10 -> go (i_line + 1) (plusPtr op 1)
+ 13 -> do
+ -- this is safe because a 'StringBuffer' is
+ -- guaranteed to have 3 bytes sentinel values.
+ w' <- peek (plusPtr op 1) :: IO Word8
+ case w' of
+ 10 -> go (i_line + 1) (plusPtr op 2)
+ _ -> go (i_line + 1) (plusPtr op 1)
+ _ -> go i_line (plusPtr op 1)
+
-- -----------------------------------------------------------------------------
-- Conversion