Skip to content

Commit

Permalink
Use CPP rather than cabal conditionals
Browse files Browse the repository at this point in the history
  • Loading branch information
ozkutuk authored and sergv committed Apr 17, 2022
1 parent 2a347e6 commit 72e2f54
Show file tree
Hide file tree
Showing 4 changed files with 32 additions and 96 deletions.
7 changes: 0 additions & 7 deletions fast-tags.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -80,14 +80,7 @@ library
transformers,
vector,
void
if impl(ghc >= 9.2)
hs-source-dirs: src-9.2
else
if impl(ghc >= 8.10)
hs-source-dirs: src-8.10
build-tools: alex
other-modules:
Compat
exposed-modules:
FastTags.Cabal
FastTags.Emacs
Expand Down
53 changes: 0 additions & 53 deletions src-8.10/Compat.hs

This file was deleted.

15 changes: 0 additions & 15 deletions src-9.2/Compat.hs

This file was deleted.

53 changes: 32 additions & 21 deletions src/FastTags/LexerM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,8 +76,6 @@ module FastTags.LexerM
, alexGetByte
) where

import qualified Compat as C

import Control.Applicative as A
import Control.DeepSeq
import Control.Exception
Expand Down Expand Up @@ -108,6 +106,19 @@ import FastTags.LensBlaze
import FastTags.LexerTypes
import FastTags.Token

#if __GLASGOW_HASKELL__ >= 902
import GHC.Exts (word8ToWord#, wordToWord8#)
#else
{-# INLINE word8ToWord# #-}
word8ToWord# :: Word# -> Word#
word8ToWord# x = x

{-# INLINE wordToWord8# #-}
wordToWord8# :: Word# -> Word#
wordToWord8# x = x
#endif


data AlexState = AlexState
{ asInput :: {-# UNPACK #-} !AlexInput
, asIntStore :: {-# UNPACK #-} !Word64
Expand Down Expand Up @@ -437,7 +448,7 @@ extractDefineOrLetName AlexInput{aiPtr} n =
start# = (goBack# (end# `plusAddr#` -1#)) `plusAddr#` 1#

goBack# :: Addr# -> Addr#
goBack# ptr# = case C.word8ToWord# (indexWord8OffAddr# ptr# 0#) of
goBack# ptr# = case word8ToWord# (indexWord8OffAddr# ptr# 0#) of
0## -> ptr#
9## -> ptr# -- '\n'
10## -> ptr# -- '\n'
Expand Down Expand Up @@ -483,7 +494,7 @@ alexInputPrevChar AlexInput{ aiPtr = Ptr ptr# } =
_ -> '\0' -- Invalid!
where
ch0 :: Int#
!ch0 = word2Int# (C.word8ToWord# (indexWord8OffAddr# start# 0#))
!ch0 = word2Int# (word8ToWord# (indexWord8OffAddr# start# 0#))

base# = findCharStart ptr# `plusAddr#` -1#

Expand All @@ -496,7 +507,7 @@ alexInputPrevChar AlexInput{ aiPtr = Ptr ptr# } =
| otherwise
= p#
where
w# = word2Int# (C.word8ToWord# (indexWord8OffAddr# p# 0#))
w# = word2Int# (word8ToWord# (indexWord8OffAddr# p# 0#))

{-# INLINE alexGetByte #-}
alexGetByte :: AlexInput -> Maybe (Word8, AlexInput)
Expand All @@ -514,7 +525,7 @@ alexGetByte input@AlexInput{aiPtr} =
input { aiPtr = cs }
c -> Just (b, input')
where
!b = W8# (C.wordToWord8# c)
!b = W8# (wordToWord8# c)
!input' =
over aiLineLengthL (+ I# n) $
input { aiPtr = cs }
Expand Down Expand Up @@ -615,7 +626,7 @@ dropUntilNL# :: Ptr Word8 -> Ptr Word8
dropUntilNL# (Ptr start#) = Ptr (go start#)
where
go :: Addr# -> Addr#
go ptr# = case C.word8ToWord# (indexWord8OffAddr# ptr# 0#) of
go ptr# = case word8ToWord# (indexWord8OffAddr# ptr# 0#) of
0## -> ptr#
10## -> ptr# -- '\n'
_ -> go (ptr# `plusAddr#` 1#)
Expand All @@ -625,13 +636,13 @@ dropUntilUnescapedNL# :: Ptr Word8 -> (# Int, Ptr Word8 #)
dropUntilUnescapedNL# (Ptr start#) = go 0 start#
where
go :: Int -> Addr# -> (# Int, Ptr Word8 #)
go !n ptr# = case C.word8ToWord# (indexWord8OffAddr# ptr# 0#) of
go !n ptr# = case word8ToWord# (indexWord8OffAddr# ptr# 0#) of
0## -> (# n, Ptr ptr# #)
-- '\n'
10## -> (# n, Ptr ptr# #)
-- '\\'
92## ->
case C.word8ToWord# (indexWord8OffAddr# ptr# 1#) of
case word8ToWord# (indexWord8OffAddr# ptr# 1#) of
0## -> (# n, Ptr (ptr# `plusAddr#` 1#) #)
-- '\n'
10## -> go (n + 1) (ptr# `plusAddr#` 2#)
Expand All @@ -643,23 +654,23 @@ dropUntilNLOr# :: Word8 -> Ptr Word8 -> Ptr Word8
dropUntilNLOr# (W8# w#) (Ptr start#) = Ptr (go start#)
where
go :: Addr# -> Addr#
go ptr# = case C.word8ToWord# (indexWord8OffAddr# ptr# 0#) of
go ptr# = case word8ToWord# (indexWord8OffAddr# ptr# 0#) of
0## -> ptr#
-- '\n'
10## -> ptr#
c# | isTrue# (c# `eqWord#` C.word8ToWord# w#) -> ptr#
c# | isTrue# (c# `eqWord#` word8ToWord# w#) -> ptr#
| otherwise -> go (ptr# `plusAddr#` 1#)

{-# INLINE dropUntilNLOrEither# #-}
dropUntilNLOrEither# :: Word8 -> Word8 -> Ptr Word8 -> Ptr Word8
dropUntilNLOrEither# (W8# w1#) (W8# w2#) (Ptr start#) = Ptr (go start#)
where
go :: Addr# -> Addr#
go ptr# = case C.word8ToWord# (indexWord8OffAddr# ptr# 0#) of
go ptr# = case word8ToWord# (indexWord8OffAddr# ptr# 0#) of
0## -> ptr#
-- '\n'
10## -> ptr#
c# | isTrue# ((c# `eqWord#` C.word8ToWord# w1#) `orI#` (c# `eqWord#` C.word8ToWord# w2#))
c# | isTrue# ((c# `eqWord#` word8ToWord# w1#) `orI#` (c# `eqWord#` word8ToWord# w2#))
-> ptr#
| otherwise
-> go (ptr# `plusAddr#` 1#)
Expand Down Expand Up @@ -713,7 +724,7 @@ regionToUtf8BS start end =
{-# INLINE utf8DecodeChar# #-}
utf8DecodeChar# :: Addr# -> (# Char#, Int# #)
utf8DecodeChar# a# =
case C.word8ToWord# (indexWord8OffAddr# a# 0#) of
case word8ToWord# (indexWord8OffAddr# a# 0#) of
0## -> (# '\0'#, 0# #)
!x# ->
let !ch0 = word2Int# x# in
Expand All @@ -736,7 +747,7 @@ invalid# nBytes# = (# '\8'#, nBytes# #)
{-# INLINE readChar1# #-}
readChar1# :: Addr# -> Int# -> (# Char#, Int# #)
readChar1# a# ch0 =
let !ch1 = word2Int# (C.word8ToWord# (indexWord8OffAddr# a# 1#)) in
let !ch1 = word2Int# (word8ToWord# (indexWord8OffAddr# a# 1#)) in
if noValidUtf8Cont# ch1 then invalid# 1# else
(# chr# (((ch0 `andI#` 0x3F#) `uncheckedIShiftL#` 6#) `orI#`
(ch1 `andI#` 0x7F#)),
Expand All @@ -745,9 +756,9 @@ readChar1# a# ch0 =
{-# INLINE readChar2# #-}
readChar2# :: Addr# -> Int# -> (# Char#, Int# #)
readChar2# a# ch0 =
let !ch1 = word2Int# (C.word8ToWord# (indexWord8OffAddr# a# 1#)) in
let !ch1 = word2Int# (word8ToWord# (indexWord8OffAddr# a# 1#)) in
if noValidUtf8Cont# ch1 then invalid# 1# else
let !ch2 = word2Int# (C.word8ToWord# (indexWord8OffAddr# a# 2#)) in
let !ch2 = word2Int# (word8ToWord# (indexWord8OffAddr# a# 2#)) in
if noValidUtf8Cont# ch2 then invalid# 2# else
(# chr# (((ch0 `andI#` 0x1F#) `uncheckedIShiftL#` 12#) `orI#`
((ch1 `andI#` 0x7F#) `uncheckedIShiftL#` 6#) `orI#`
Expand All @@ -757,11 +768,11 @@ readChar2# a# ch0 =
{-# INLINE readChar3# #-}
readChar3# :: Addr# -> Int# -> (# Char#, Int# #)
readChar3# a# ch0 =
let !ch1 = word2Int# (C.word8ToWord# (indexWord8OffAddr# a# 1#)) in
let !ch1 = word2Int# (word8ToWord# (indexWord8OffAddr# a# 1#)) in
if noValidUtf8Cont# ch1 then invalid# 1# else
let !ch2 = word2Int# (C.word8ToWord# (indexWord8OffAddr# a# 2#)) in
let !ch2 = word2Int# (word8ToWord# (indexWord8OffAddr# a# 2#)) in
if noValidUtf8Cont# ch2 then invalid# 2# else
let !ch3 = word2Int# (C.word8ToWord# (indexWord8OffAddr# a# 3#)) in
let !ch3 = word2Int# (word8ToWord# (indexWord8OffAddr# a# 3#)) in
if noValidUtf8Cont# ch3 then invalid# 3# else
(# chr# (((ch0 `andI#` 0x0F#) `uncheckedIShiftL#` 18#) `orI#`
((ch1 `andI#` 0x7F#) `uncheckedIShiftL#` 12#) `orI#`
Expand Down Expand Up @@ -796,7 +807,7 @@ startsWith11110# x = isTrue# ((x `andI#` 0xF8#) ==# 0xF0#)
{-# INLINE utf8SizeChar# #-}
utf8SizeChar# :: Addr# -> Int#
utf8SizeChar# a# =
case C.word8ToWord# (indexWord8OffAddr# a# 0#) of
case word8ToWord# (indexWord8OffAddr# a# 0#) of
0## -> 0#
!x# ->
let !ch0 = word2Int# x# in
Expand Down

0 comments on commit 72e2f54

Please sign in to comment.