{-# LANGUAGE CPP, MagicHash, UnboxedTuples, NumericUnderscores #-}
{-# OPTIONS_GHC -Wno-overflowed-literals #-}
module Parsley.Internal.Backend.Machine.PosOps (
initPos, tabWidth,
extractLine, extractCol,
liftPos,
updatePos, updatePosQ,
updatePosNewlineOnly, updatePosNewlineOnlyQ,
shiftLineAndSetCol, shiftCol, shiftAlignAndShiftCol,
shiftLineAndSetColQ, shiftColQ, shiftAlignAndShiftColQ,
toNextTab
) where
#include "MachDeps.h"
#if WORD_SIZE_IN_BITS < 64
#define FULL_WIDTH_POSITIONS
#endif
import Data.Bits ( (.&.), (.|.)
#ifndef FULL_WIDTH_POSITIONS
, unsafeShiftL
#endif
)
import Parsley.Internal.Backend.Machine.Types.Base (Pos)
import Parsley.Internal.Common (Code)
import GHC.Exts (Int(..), Word(W#))
import GHC.Prim ( plusWord#, and#, or#, word2Int#
#ifdef FULL_WIDTH_POSITIONS
, minusWord#
#else
, uncheckedShiftRL#
#endif
)
toNextTab :: Word -> Word
toNextTab :: Word -> Word
toNextTab Word
x = (Word
x Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
forall a. Num a => a
tabWidth Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
1) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word -> Word
forall a. Num a => a -> a
negate Word
forall a. Num a => a
tabWidth Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
1
updatePos :: Code Char -> Word -> Word -> Code Pos
updatePos :: Code Char -> Word -> Word -> Code Pos
updatePos Code Char
c Word
line Word
col = [||updatePos# $$(liftPos line col) $$c||]
updatePosNewlineOnly :: Code Char -> Word -> Code Pos
updatePosNewlineOnly :: Code Char -> Word -> Code Pos
updatePosNewlineOnly Code Char
c Word
line = [||updatePos0ColNewlineOnly# $$(liftPos line 0) $$c||]
updatePosQ :: Code Char -> Code Pos -> Code Pos
updatePosQ :: Code Char -> Code Pos -> Code Pos
updatePosQ Code Char
c Code Pos
pos = [||updatePos# $$pos $$c||]
updatePosNewlineOnlyQ :: Code Char -> Code Pos -> Code Pos
updatePosNewlineOnlyQ :: Code Char -> Code Pos -> Code Pos
updatePosNewlineOnlyQ Code Char
c Code Pos
pos = [||updatePosNewlineOnly# $$pos $$c||]
shiftCol :: Word
-> Word
-> Word
-> (Word, Word)
shiftCol :: Word -> Word -> Word -> (Word, Word)
shiftCol Word
n Word
line Word
col = (Word
line, Word
col Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
n)
shiftLineAndSetCol :: Word
-> Word
-> Word
-> (Word, Word)
shiftLineAndSetCol :: Word -> Word -> Word -> (Word, Word)
shiftLineAndSetCol Word
n Word
col Word
line = (Word
line Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
n, Word
col)
shiftAlignAndShiftCol :: Word
-> Word
-> Word
-> Word
-> (Word, Word)
shiftAlignAndShiftCol :: Word -> Word -> Word -> Word -> (Word, Word)
shiftAlignAndShiftCol Word
firstBy Word
thenBy Word
line Word
col = (Word
line, Word -> Word
toNextTab (Word
col Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
firstBy) Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
thenBy)
initPos :: (Word, Word)
initPos :: (Word, Word)
initPos = (Word
1, Word
1)
tabWidth :: Num a => a
tabWidth :: a
tabWidth = a
4
{-# INLINEABLE updatePos# #-}
updatePos# :: Pos -> Char -> Pos
{-# INLINE updatePosNewlineOnly# #-}
updatePosNewlineOnly# :: Pos -> Char -> Pos
{-# INLINEABLE updatePos0ColNewlineOnly# #-}
updatePos0ColNewlineOnly# :: Pos -> Char -> Pos
shiftColQ :: Word
-> Code Pos
-> Code Pos
shiftLineAndSetColQ :: Word
-> Word
-> Code Pos
-> Code Pos
shiftAlignAndShiftColQ :: Word
-> Word
-> Code Pos
-> Code Pos
extractLine :: Code Pos -> Code Int
extractCol :: Code Pos -> Code Int
liftPos :: Word -> Word -> Code Pos
#ifndef FULL_WIDTH_POSITIONS
updatePos# :: Pos -> Char -> Pos
updatePos# Pos
pos Char
'\n' = (Pos
pos Pos -> Pos -> Pos
`and#` Pos
0xffffffff_00000000##) Pos -> Pos -> Pos
`plusWord#` Pos
0x00000001_00000001##
updatePos# Pos
pos Char
'\t' = ((Pos
pos Pos -> Pos -> Pos
`plusWord#` Pos
0x00000000_00000003##) Pos -> Pos -> Pos
`and#` Pos
0xffffffff_fffffffc##) Pos -> Pos -> Pos
`or#` Pos
0x00000000_00000001##
updatePos# Pos
pos Char
_ = Pos
pos Pos -> Pos -> Pos
`plusWord#` Pos
0x00000000_00000001##
updatePosNewlineOnly# :: Pos -> Char -> Pos
updatePosNewlineOnly# Pos
pos = Pos -> Char -> Pos
updatePos0ColNewlineOnly# (Pos
pos Pos -> Pos -> Pos
`and#` Pos
0xffffffff_00000000##)
updatePos0ColNewlineOnly# :: Pos -> Char -> Pos
updatePos0ColNewlineOnly# Pos
pos0Col Char
'\n' = Pos
pos0Col Pos -> Pos -> Pos
`plusWord#` Pos
0x00000001_00000000##
updatePos0ColNewlineOnly# Pos
pos0Col Char
_ = Pos
pos0Col
shiftLineAndSetColQ :: Word -> Word -> Code Pos -> Code Pos
shiftLineAndSetColQ Word
n Word
col Code Pos
qpos = [|| ($$qpos `and#` 0xffffffff_00000000##) `plusWord#` $$(liftPos n col) ||]
shiftColQ :: Word -> Code Pos -> Code Pos
shiftColQ (W# Pos
n) Code Pos
qpos = [|| $$qpos `plusWord#` n ||]
shiftAlignAndShiftColQ :: Word -> Word -> Code Pos -> Code Pos
shiftAlignAndShiftColQ Word
firstBy Word
thenBy Code Pos
qpos =
let !(W# Pos
pre) = Word
firstBy Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
3
!(W# Pos
mask) = -Word
4
!(W# Pos
post) = Word
thenBy Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
1
in if Word
thenBy Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
0 then [|| (($$qpos `plusWord#` pre) `and#` mask) `or#` 0x00000000_00000001## ||]
else [|| (($$qpos `plusWord#` pre) `and#` mask) `plusWord#` post ||]
Code Pos
qpos = [||I# (word2Int# ($$qpos `uncheckedShiftRL#` 32#))||]
Code Pos
qpos = [||I# (word2Int# ($$qpos `and#` 0x00000000_ffffffff##))||]
liftPos :: Word -> Word -> Code Pos
liftPos Word
line Word
col = let !(W# Pos
p) = (Word
line Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
32) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
col in [||p||]
#else
updatePos# (# line, _ #) '\n' = (# line `plusWord#` 1##, 1## #)
updatePos# (# line, col #) '\t' = (# line, ((col `plusWord#` 3##) `and#` (0## `minusWord#` 4##)) `or#` 1## #)
updatePos# (# line, col #) _ = (# line, col `plusWord#` 1## #)
updatePosNewlineOnly# = updatePos0ColNewlineOnly#
updatePos0ColNewlineOnly# (# line, _ #) '\n' = (# line `plusWord#` 1##, 0## #)
updatePos0ColNewlineOnly# pos _ = pos
shiftLineAndSetColQ (W# n) (W# col) qpos = [|| case $$qpos of (# line, _ #) -> (# line `plusWord#` n, col #) ||]
shiftColQ (W# n) qpos = [|| case $$qpos of (# line, col #) -> (# line, col `plusWord#` n #) ||]
shiftAlignAndShiftColQ firstBy thenBy qpos =
let !(W# pre) = firstBy + 3
!(W# mask) = -4
!(W# post) = thenBy + 1
in [|| case $$qpos of
(# line, col #) -> (# line,
$$(if thenBy == 0 then [|| ((col `plusWord#` pre) `and#` mask) `or#` 1## ||]
else [|| ((col `plusWord#` pre) `and#` mask) `plusWord#` post ||]) #) ||]
extractLine qpos = [|| case $$qpos of (# line, _ #) -> I# (word2Int# line) ||]
extractCol qpos = [|| case $$qpos of (# _, col #) -> I# (word2Int# col) ||]
liftPos (W# line) (W# col) = [||(# line, col #)||]
#endif