{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# OPTIONS_GHC -O2 -funbox-strict-fields #-}
module GHC.Data.FastString
(
bytesFS,
fastStringToByteString,
mkFastStringByteString,
fastZStringToByteString,
unsafeMkByteString,
fastStringToShortByteString,
mkFastStringShortByteString,
FastZString,
hPutFZS,
zString,
lengthFZS,
FastString(..),
NonDetFastString (..),
LexicalFastString (..),
fsLit,
mkFastString,
mkFastStringBytes,
mkFastStringByteList,
mkFastString#,
unpackFS,
unconsFS,
zEncodeFS,
uniqueOfFS,
lengthFS,
nullFS,
appendFS,
headFS,
concatFS,
consFS,
nilFS,
isUnderscoreFS,
lexicalCompareFS,
uniqCompareFS,
hPutFS,
getFastStringTable,
getFastStringZEncCounter,
PtrString (..),
mkPtrString#,
mkPtrString,
unpackPtrString,
lengthPS
) where
import GHC.Prelude as Prelude
import GHC.Utils.Encoding
import GHC.Utils.IO.Unsafe
import GHC.Utils.Panic.Plain
import GHC.Utils.Misc
import GHC.Data.FastMutInt
import Control.Concurrent.MVar
import Control.DeepSeq
import Control.Monad
import Data.ByteString (ByteString)
import Data.ByteString.Short (ShortByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import qualified Data.ByteString.Unsafe as BS
import qualified Data.ByteString.Short as SBS
#if !MIN_VERSION_bytestring(0,11,0)
import qualified Data.ByteString.Short.Internal as SBS
#endif
import Foreign.C
import System.IO
import Data.Data
import Data.IORef
import Data.Char
import Data.Semigroup as Semi
import Foreign
#if MIN_VERSION_GLASGOW_HASKELL(9,3,0,0)
import GHC.Conc.Sync (sharedCAF)
#endif
#if __GLASGOW_HASKELL__ < 811
import GHC.Base (unpackCString#,unpackNBytes#)
#endif
import GHC.Exts
import GHC.IO
bytesFS, fastStringToByteString :: FastString -> ByteString
{-# INLINE[1] bytesFS #-}
bytesFS :: FastString -> ByteString
bytesFS FastString
f = ShortByteString -> ByteString
SBS.fromShort (ShortByteString -> ByteString) -> ShortByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ FastString -> ShortByteString
fs_sbs FastString
f
{-# DEPRECATED fastStringToByteString "Use `bytesFS` instead" #-}
fastStringToByteString :: FastString -> ByteString
fastStringToByteString = FastString -> ByteString
bytesFS
fastStringToShortByteString :: FastString -> ShortByteString
fastStringToShortByteString :: FastString -> ShortByteString
fastStringToShortByteString = FastString -> ShortByteString
fs_sbs
fastZStringToByteString :: FastZString -> ByteString
fastZStringToByteString :: FastZString -> ByteString
fastZStringToByteString (FastZString ByteString
bs) = ByteString
bs
unsafeMkByteString :: String -> ByteString
unsafeMkByteString :: String -> ByteString
unsafeMkByteString = String -> ByteString
BSC.pack
hashFastString :: FastString -> Int
hashFastString :: FastString -> Int
hashFastString FastString
fs = ShortByteString -> Int
hashStr (ShortByteString -> Int) -> ShortByteString -> Int
forall a b. (a -> b) -> a -> b
$ FastString -> ShortByteString
fs_sbs FastString
fs
newtype FastZString = FastZString ByteString
deriving FastZString -> ()
(FastZString -> ()) -> NFData FastZString
forall a. (a -> ()) -> NFData a
$crnf :: FastZString -> ()
rnf :: FastZString -> ()
NFData
hPutFZS :: Handle -> FastZString -> IO ()
hPutFZS :: Handle -> FastZString -> IO ()
hPutFZS Handle
handle (FastZString ByteString
bs) = Handle -> ByteString -> IO ()
BS.hPut Handle
handle ByteString
bs
zString :: FastZString -> String
zString :: FastZString -> String
zString (FastZString ByteString
bs) =
IO String -> String
forall a. IO a -> a
inlinePerformIO (IO String -> String) -> IO String -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> (CStringLen -> IO String) -> IO String
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
bs CStringLen -> IO String
peekCAStringLen
lengthFZS :: FastZString -> Int
lengthFZS :: FastZString -> Int
lengthFZS (FastZString ByteString
bs) = ByteString -> Int
BS.length ByteString
bs
mkFastZStringString :: String -> FastZString
mkFastZStringString :: String -> FastZString
mkFastZStringString String
str = ByteString -> FastZString
FastZString (String -> ByteString
BSC.pack String
str)
data FastString = FastString {
FastString -> Int
uniq :: {-# UNPACK #-} !Int,
FastString -> Int
n_chars :: {-# UNPACK #-} !Int,
FastString -> ShortByteString
fs_sbs :: {-# UNPACK #-} !ShortByteString,
FastString -> FastZString
fs_zenc :: FastZString
}
instance Eq FastString where
FastString
f1 == :: FastString -> FastString -> Bool
== FastString
f2 = FastString -> Int
uniq FastString
f1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== FastString -> Int
uniq FastString
f2
instance IsString FastString where
fromString :: String -> FastString
fromString = String -> FastString
fsLit
instance Semi.Semigroup FastString where
<> :: FastString -> FastString -> FastString
(<>) = FastString -> FastString -> FastString
appendFS
instance Monoid FastString where
mempty :: FastString
mempty = FastString
nilFS
mappend :: FastString -> FastString -> FastString
mappend = FastString -> FastString -> FastString
forall a. Semigroup a => a -> a -> a
(Semi.<>)
mconcat :: [FastString] -> FastString
mconcat = [FastString] -> FastString
concatFS
instance Show FastString where
show :: FastString -> String
show FastString
fs = ShowS
forall a. Show a => a -> String
show (FastString -> String
unpackFS FastString
fs)
instance Data FastString where
toConstr :: FastString -> Constr
toConstr FastString
_ = String -> Constr
abstractConstr String
"FastString"
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FastString
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_ = String -> Constr -> c FastString
forall a. HasCallStack => String -> a
error String
"gunfold"
dataTypeOf :: FastString -> DataType
dataTypeOf FastString
_ = String -> DataType
mkNoRepType String
"FastString"
instance NFData FastString where
rnf :: FastString -> ()
rnf FastString
fs = FastString -> () -> ()
forall a b. a -> b -> b
seq FastString
fs ()
lexicalCompareFS :: FastString -> FastString -> Ordering
lexicalCompareFS :: FastString -> FastString -> Ordering
lexicalCompareFS FastString
fs1 FastString
fs2 =
if FastString -> Int
uniq FastString
fs1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== FastString -> Int
uniq FastString
fs2 then Ordering
EQ else
ShortByteString -> ShortByteString -> Ordering
utf8CompareShortByteString (FastString -> ShortByteString
fs_sbs FastString
fs1) (FastString -> ShortByteString
fs_sbs FastString
fs2)
uniqCompareFS :: FastString -> FastString -> Ordering
uniqCompareFS :: FastString -> FastString -> Ordering
uniqCompareFS FastString
fs1 FastString
fs2 = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (FastString -> Int
uniq FastString
fs1) (FastString -> Int
uniq FastString
fs2)
newtype NonDetFastString
= NonDetFastString FastString
deriving newtype (NonDetFastString -> NonDetFastString -> Bool
(NonDetFastString -> NonDetFastString -> Bool)
-> (NonDetFastString -> NonDetFastString -> Bool)
-> Eq NonDetFastString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NonDetFastString -> NonDetFastString -> Bool
== :: NonDetFastString -> NonDetFastString -> Bool
$c/= :: NonDetFastString -> NonDetFastString -> Bool
/= :: NonDetFastString -> NonDetFastString -> Bool
Eq, Int -> NonDetFastString -> ShowS
[NonDetFastString] -> ShowS
NonDetFastString -> String
(Int -> NonDetFastString -> ShowS)
-> (NonDetFastString -> String)
-> ([NonDetFastString] -> ShowS)
-> Show NonDetFastString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NonDetFastString -> ShowS
showsPrec :: Int -> NonDetFastString -> ShowS
$cshow :: NonDetFastString -> String
show :: NonDetFastString -> String
$cshowList :: [NonDetFastString] -> ShowS
showList :: [NonDetFastString] -> ShowS
Show)
deriving stock Typeable NonDetFastString
Typeable NonDetFastString
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonDetFastString -> c NonDetFastString)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonDetFastString)
-> (NonDetFastString -> Constr)
-> (NonDetFastString -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonDetFastString))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonDetFastString))
-> ((forall b. Data b => b -> b)
-> NonDetFastString -> NonDetFastString)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r)
-> (forall u.
(forall d. Data d => d -> u) -> NonDetFastString -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> NonDetFastString -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString)
-> Data NonDetFastString
NonDetFastString -> Constr
NonDetFastString -> DataType
(forall b. Data b => b -> b)
-> NonDetFastString -> NonDetFastString
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> NonDetFastString -> u
forall u. (forall d. Data d => d -> u) -> NonDetFastString -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonDetFastString
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonDetFastString -> c NonDetFastString
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonDetFastString)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonDetFastString)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonDetFastString -> c NonDetFastString
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonDetFastString -> c NonDetFastString
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonDetFastString
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonDetFastString
$ctoConstr :: NonDetFastString -> Constr
toConstr :: NonDetFastString -> Constr
$cdataTypeOf :: NonDetFastString -> DataType
dataTypeOf :: NonDetFastString -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonDetFastString)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonDetFastString)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonDetFastString)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonDetFastString)
$cgmapT :: (forall b. Data b => b -> b)
-> NonDetFastString -> NonDetFastString
gmapT :: (forall b. Data b => b -> b)
-> NonDetFastString -> NonDetFastString
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonDetFastString -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NonDetFastString -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NonDetFastString -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NonDetFastString -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NonDetFastString -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonDetFastString -> m NonDetFastString
Data
instance Ord NonDetFastString where
compare :: NonDetFastString -> NonDetFastString -> Ordering
compare (NonDetFastString FastString
fs1) (NonDetFastString FastString
fs2) = FastString -> FastString -> Ordering
uniqCompareFS FastString
fs1 FastString
fs2
newtype LexicalFastString
= LexicalFastString FastString
deriving newtype (LexicalFastString -> LexicalFastString -> Bool
(LexicalFastString -> LexicalFastString -> Bool)
-> (LexicalFastString -> LexicalFastString -> Bool)
-> Eq LexicalFastString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LexicalFastString -> LexicalFastString -> Bool
== :: LexicalFastString -> LexicalFastString -> Bool
$c/= :: LexicalFastString -> LexicalFastString -> Bool
/= :: LexicalFastString -> LexicalFastString -> Bool
Eq, Int -> LexicalFastString -> ShowS
[LexicalFastString] -> ShowS
LexicalFastString -> String
(Int -> LexicalFastString -> ShowS)
-> (LexicalFastString -> String)
-> ([LexicalFastString] -> ShowS)
-> Show LexicalFastString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LexicalFastString -> ShowS
showsPrec :: Int -> LexicalFastString -> ShowS
$cshow :: LexicalFastString -> String
show :: LexicalFastString -> String
$cshowList :: [LexicalFastString] -> ShowS
showList :: [LexicalFastString] -> ShowS
Show)
deriving stock Typeable LexicalFastString
Typeable LexicalFastString
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> LexicalFastString
-> c LexicalFastString)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFastString)
-> (LexicalFastString -> Constr)
-> (LexicalFastString -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LexicalFastString))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFastString))
-> ((forall b. Data b => b -> b)
-> LexicalFastString -> LexicalFastString)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r)
-> (forall u.
(forall d. Data d => d -> u) -> LexicalFastString -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> LexicalFastString -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString)
-> Data LexicalFastString
LexicalFastString -> Constr
LexicalFastString -> DataType
(forall b. Data b => b -> b)
-> LexicalFastString -> LexicalFastString
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> LexicalFastString -> u
forall u. (forall d. Data d => d -> u) -> LexicalFastString -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFastString
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFastString -> c LexicalFastString
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LexicalFastString)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFastString)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFastString -> c LexicalFastString
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFastString -> c LexicalFastString
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFastString
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFastString
$ctoConstr :: LexicalFastString -> Constr
toConstr :: LexicalFastString -> Constr
$cdataTypeOf :: LexicalFastString -> DataType
dataTypeOf :: LexicalFastString -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LexicalFastString)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LexicalFastString)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFastString)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFastString)
$cgmapT :: (forall b. Data b => b -> b)
-> LexicalFastString -> LexicalFastString
gmapT :: (forall b. Data b => b -> b)
-> LexicalFastString -> LexicalFastString
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFastString -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LexicalFastString -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> LexicalFastString -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> LexicalFastString -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> LexicalFastString -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LexicalFastString -> m LexicalFastString
Data
instance Ord LexicalFastString where
compare :: LexicalFastString -> LexicalFastString -> Ordering
compare (LexicalFastString FastString
fs1) (LexicalFastString FastString
fs2) = FastString -> FastString -> Ordering
lexicalCompareFS FastString
fs1 FastString
fs2
data FastStringTable = FastStringTable
{-# UNPACK #-} !FastMutInt
{-# UNPACK #-} !FastMutInt
(Array# (IORef FastStringTableSegment))
data FastStringTableSegment = FastStringTableSegment
{-# UNPACK #-} !(MVar ())
{-# UNPACK #-} !FastMutInt
(MutableArray# RealWorld [FastString])
segmentBits, numSegments, segmentMask, initialNumBuckets :: Int
segmentBits :: Int
segmentBits = Int
8
numSegments :: Int
numSegments = Int
256
segmentMask :: Int
segmentMask = Int
0xff
initialNumBuckets :: Int
initialNumBuckets = Int
64
hashToSegment# :: Int# -> Int#
hashToSegment# :: Int# -> Int#
hashToSegment# Int#
hash# = Int#
hash# Int# -> Int# -> Int#
`andI#` Int#
segmentMask#
where
!(I# Int#
segmentMask#) = Int
segmentMask
hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int#
hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int#
hashToIndex# MutableArray# RealWorld [FastString]
buckets# Int#
hash# =
(Int#
hash# Int# -> Int# -> Int#
`uncheckedIShiftRL#` Int#
segmentBits#) Int# -> Int# -> Int#
`remInt#` Int#
size#
where
!(I# Int#
segmentBits#) = Int
segmentBits
size# :: Int#
size# = MutableArray# RealWorld [FastString] -> Int#
forall d a. MutableArray# d a -> Int#
sizeofMutableArray# MutableArray# RealWorld [FastString]
buckets#
maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment
maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment
maybeResizeSegment IORef FastStringTableSegment
segmentRef = do
segment :: FastStringTableSegment
segment@(FastStringTableSegment MVar ()
lock FastMutInt
counter MutableArray# RealWorld [FastString]
old#) <- IORef FastStringTableSegment -> IO FastStringTableSegment
forall a. IORef a -> IO a
readIORef IORef FastStringTableSegment
segmentRef
let oldSize# :: Int#
oldSize# = MutableArray# RealWorld [FastString] -> Int#
forall d a. MutableArray# d a -> Int#
sizeofMutableArray# MutableArray# RealWorld [FastString]
old#
newSize# :: Int#
newSize# = Int#
oldSize# Int# -> Int# -> Int#
*# Int#
2#
(I# Int#
n#) <- FastMutInt -> IO Int
readFastMutInt FastMutInt
counter
if Int# -> Bool
isTrue# (Int#
n# Int# -> Int# -> Int#
<# Int#
newSize#)
then FastStringTableSegment -> IO FastStringTableSegment
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FastStringTableSegment
segment
else do
resizedSegment :: FastStringTableSegment
resizedSegment@(FastStringTableSegment MVar ()
_ FastMutInt
_ MutableArray# RealWorld [FastString]
new#) <- (State# RealWorld
-> (# State# RealWorld, FastStringTableSegment #))
-> IO FastStringTableSegment
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld
-> (# State# RealWorld, FastStringTableSegment #))
-> IO FastStringTableSegment)
-> (State# RealWorld
-> (# State# RealWorld, FastStringTableSegment #))
-> IO FastStringTableSegment
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s1# ->
case Int#
-> [FastString]
-> State# RealWorld
-> (# State# RealWorld, MutableArray# RealWorld [FastString] #)
forall a d.
Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
newArray# Int#
newSize# [] State# RealWorld
s1# of
(# State# RealWorld
s2#, MutableArray# RealWorld [FastString]
arr# #) -> (# State# RealWorld
s2#, MVar ()
-> FastMutInt
-> MutableArray# RealWorld [FastString]
-> FastStringTableSegment
FastStringTableSegment MVar ()
lock FastMutInt
counter MutableArray# RealWorld [FastString]
arr# #)
[Int] -> (Int -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
0 .. (Int# -> Int
I# Int#
oldSize#) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> IO ()) -> IO ()) -> (Int -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(I# Int#
i#) -> do
[FastString]
fsList <- (State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString])
-> (State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a b. (a -> b) -> a -> b
$ MutableArray# RealWorld [FastString]
-> Int# -> State# RealWorld -> (# State# RealWorld, [FastString] #)
forall d a.
MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
readArray# MutableArray# RealWorld [FastString]
old# Int#
i#
[FastString] -> (FastString -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [FastString]
fsList ((FastString -> IO ()) -> IO ()) -> (FastString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FastString
fs -> do
let
!(I# Int#
hash#) = FastString -> Int
hashFastString FastString
fs
idx# :: Int#
idx# = MutableArray# RealWorld [FastString] -> Int# -> Int#
hashToIndex# MutableArray# RealWorld [FastString]
new# Int#
hash#
(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s1# ->
case MutableArray# RealWorld [FastString]
-> Int# -> State# RealWorld -> (# State# RealWorld, [FastString] #)
forall d a.
MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
readArray# MutableArray# RealWorld [FastString]
new# Int#
idx# State# RealWorld
s1# of
(# State# RealWorld
s2#, [FastString]
bucket #) -> case MutableArray# RealWorld [FastString]
-> Int# -> [FastString] -> State# RealWorld -> State# RealWorld
forall d a. MutableArray# d a -> Int# -> a -> State# d -> State# d
writeArray# MutableArray# RealWorld [FastString]
new# Int#
idx# (FastString
fsFastString -> [FastString] -> [FastString]
forall a. a -> [a] -> [a]
: [FastString]
bucket) State# RealWorld
s2# of
State# RealWorld
s3# -> (# State# RealWorld
s3#, () #)
IORef FastStringTableSegment -> FastStringTableSegment -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef FastStringTableSegment
segmentRef FastStringTableSegment
resizedSegment
FastStringTableSegment -> IO FastStringTableSegment
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FastStringTableSegment
resizedSegment
{-# NOINLINE stringTable #-}
stringTable :: FastStringTable
stringTable :: FastStringTable
stringTable = IO FastStringTable -> FastStringTable
forall a. IO a -> a
unsafePerformIO (IO FastStringTable -> FastStringTable)
-> IO FastStringTable -> FastStringTable
forall a b. (a -> b) -> a -> b
$ do
let !(I# Int#
numSegments#) = Int
numSegments
!(I# Int#
initialNumBuckets#) = Int
initialNumBuckets
loop :: MutableArray# RealWorld (IORef FastStringTableSegment)
-> Int# -> State# RealWorld -> State# RealWorld
loop MutableArray# RealWorld (IORef FastStringTableSegment)
a# Int#
i# State# RealWorld
s1#
| Int# -> Bool
isTrue# (Int#
i# Int# -> Int# -> Int#
==# Int#
numSegments#) = State# RealWorld
s1#
| Bool
otherwise = case () -> IO (MVar ())
forall a. a -> IO (MVar a)
newMVar () IO (MVar ()) -> State# RealWorld -> (# State# RealWorld, MVar () #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
`unIO` State# RealWorld
s1# of
(# State# RealWorld
s2#, MVar ()
lock #) -> case Int -> IO FastMutInt
newFastMutInt Int
0 IO FastMutInt
-> State# RealWorld -> (# State# RealWorld, FastMutInt #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
`unIO` State# RealWorld
s2# of
(# State# RealWorld
s3#, FastMutInt
counter #) -> case Int#
-> [FastString]
-> State# RealWorld
-> (# State# RealWorld, MutableArray# RealWorld [FastString] #)
forall a d.
Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
newArray# Int#
initialNumBuckets# [] State# RealWorld
s3# of
(# State# RealWorld
s4#, MutableArray# RealWorld [FastString]
buckets# #) -> case FastStringTableSegment -> IO (IORef FastStringTableSegment)
forall a. a -> IO (IORef a)
newIORef
(MVar ()
-> FastMutInt
-> MutableArray# RealWorld [FastString]
-> FastStringTableSegment
FastStringTableSegment MVar ()
lock FastMutInt
counter MutableArray# RealWorld [FastString]
buckets#) IO (IORef FastStringTableSegment)
-> State# RealWorld
-> (# State# RealWorld, IORef FastStringTableSegment #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
`unIO` State# RealWorld
s4# of
(# State# RealWorld
s5#, IORef FastStringTableSegment
segment #) -> case MutableArray# RealWorld (IORef FastStringTableSegment)
-> Int#
-> IORef FastStringTableSegment
-> State# RealWorld
-> State# RealWorld
forall d a. MutableArray# d a -> Int# -> a -> State# d -> State# d
writeArray# MutableArray# RealWorld (IORef FastStringTableSegment)
a# Int#
i# IORef FastStringTableSegment
segment State# RealWorld
s5# of
State# RealWorld
s6# -> MutableArray# RealWorld (IORef FastStringTableSegment)
-> Int# -> State# RealWorld -> State# RealWorld
loop MutableArray# RealWorld (IORef FastStringTableSegment)
a# (Int#
i# Int# -> Int# -> Int#
+# Int#
1#) State# RealWorld
s6#
FastMutInt
uid <- Int -> IO FastMutInt
newFastMutInt Int
603979776
FastMutInt
n_zencs <- Int -> IO FastMutInt
newFastMutInt Int
0
FastStringTable
tab <- (State# RealWorld -> (# State# RealWorld, FastStringTable #))
-> IO FastStringTable
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, FastStringTable #))
-> IO FastStringTable)
-> (State# RealWorld -> (# State# RealWorld, FastStringTable #))
-> IO FastStringTable
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s1# ->
case Int#
-> IORef FastStringTableSegment
-> State# RealWorld
-> (# State# RealWorld,
MutableArray# RealWorld (IORef FastStringTableSegment) #)
forall a d.
Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
newArray# Int#
numSegments# (String -> IORef FastStringTableSegment
forall a. String -> a
panic String
"string_table") State# RealWorld
s1# of
(# State# RealWorld
s2#, MutableArray# RealWorld (IORef FastStringTableSegment)
arr# #) -> case MutableArray# RealWorld (IORef FastStringTableSegment)
-> Int# -> State# RealWorld -> State# RealWorld
loop MutableArray# RealWorld (IORef FastStringTableSegment)
arr# Int#
0# State# RealWorld
s2# of
State# RealWorld
s3# -> case MutableArray# RealWorld (IORef FastStringTableSegment)
-> State# RealWorld
-> (# State# RealWorld, Array# (IORef FastStringTableSegment) #)
forall d a.
MutableArray# d a -> State# d -> (# State# d, Array# a #)
unsafeFreezeArray# MutableArray# RealWorld (IORef FastStringTableSegment)
arr# State# RealWorld
s3# of
(# State# RealWorld
s4#, Array# (IORef FastStringTableSegment)
segments# #) ->
(# State# RealWorld
s4#, FastMutInt
-> FastMutInt
-> Array# (IORef FastStringTableSegment)
-> FastStringTable
FastStringTable FastMutInt
uid FastMutInt
n_zencs Array# (IORef FastStringTableSegment)
segments# #)
#if !MIN_VERSION_GLASGOW_HASKELL(9,3,0,0)
return tab
#else
FastStringTable
-> (Ptr FastStringTable -> IO (Ptr FastStringTable))
-> IO FastStringTable
forall a. a -> (Ptr a -> IO (Ptr a)) -> IO a
sharedCAF FastStringTable
tab Ptr FastStringTable -> IO (Ptr FastStringTable)
forall a. Ptr a -> IO (Ptr a)
getOrSetLibHSghcFastStringTable
foreign import ccall unsafe "getOrSetLibHSghcFastStringTable"
getOrSetLibHSghcFastStringTable :: Ptr a -> IO (Ptr a)
#endif
mkFastString# :: Addr# -> FastString
{-# INLINE mkFastString# #-}
mkFastString# :: Addr# -> FastString
mkFastString# Addr#
a# = Ptr Word8 -> Int -> FastString
mkFastStringBytes Ptr Word8
ptr (Ptr Word8 -> Int
ptrStrLength Ptr Word8
ptr)
where ptr :: Ptr Word8
ptr = Addr# -> Ptr Word8
forall a. Addr# -> Ptr a
Ptr Addr#
a#
mkFastStringWith
:: (Int -> FastMutInt-> IO FastString) -> ShortByteString -> IO FastString
mkFastStringWith :: (Int -> FastMutInt -> IO FastString)
-> ShortByteString -> IO FastString
mkFastStringWith Int -> FastMutInt -> IO FastString
mk_fs ShortByteString
sbs = do
FastStringTableSegment MVar ()
lock FastMutInt
_ MutableArray# RealWorld [FastString]
buckets# <- IORef FastStringTableSegment -> IO FastStringTableSegment
forall a. IORef a -> IO a
readIORef IORef FastStringTableSegment
segmentRef
let idx# :: Int#
idx# = MutableArray# RealWorld [FastString] -> Int# -> Int#
hashToIndex# MutableArray# RealWorld [FastString]
buckets# Int#
hash#
[FastString]
bucket <- (State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString])
-> (State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a b. (a -> b) -> a -> b
$ MutableArray# RealWorld [FastString]
-> Int# -> State# RealWorld -> (# State# RealWorld, [FastString] #)
forall d a.
MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
readArray# MutableArray# RealWorld [FastString]
buckets# Int#
idx#
Maybe FastString
res <- [FastString] -> ShortByteString -> IO (Maybe FastString)
bucket_match [FastString]
bucket ShortByteString
sbs
case Maybe FastString
res of
Just FastString
found -> FastString -> IO FastString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FastString
found
Maybe FastString
Nothing -> do
IO ()
noDuplicate
Int
n <- IO Int
get_uid
FastString
new_fs <- Int -> FastMutInt -> IO FastString
mk_fs Int
n FastMutInt
n_zencs
MVar () -> (() -> IO FastString) -> IO FastString
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar ()
lock ((() -> IO FastString) -> IO FastString)
-> (() -> IO FastString) -> IO FastString
forall a b. (a -> b) -> a -> b
$ \()
_ -> FastString -> IO FastString
insert FastString
new_fs
where
!(FastStringTable FastMutInt
uid FastMutInt
n_zencs Array# (IORef FastStringTableSegment)
segments#) = FastStringTable
stringTable
get_uid :: IO Int
get_uid = FastMutInt -> Int -> IO Int
atomicFetchAddFastMut FastMutInt
uid Int
1
!(I# Int#
hash#) = ShortByteString -> Int
hashStr ShortByteString
sbs
(# IORef FastStringTableSegment
segmentRef #) = Array# (IORef FastStringTableSegment)
-> Int# -> (# IORef FastStringTableSegment #)
forall a. Array# a -> Int# -> (# a #)
indexArray# Array# (IORef FastStringTableSegment)
segments# (Int# -> Int#
hashToSegment# Int#
hash#)
insert :: FastString -> IO FastString
insert FastString
fs = do
FastStringTableSegment MVar ()
_ FastMutInt
counter MutableArray# RealWorld [FastString]
buckets# <- IORef FastStringTableSegment -> IO FastStringTableSegment
maybeResizeSegment IORef FastStringTableSegment
segmentRef
let idx# :: Int#
idx# = MutableArray# RealWorld [FastString] -> Int# -> Int#
hashToIndex# MutableArray# RealWorld [FastString]
buckets# Int#
hash#
[FastString]
bucket <- (State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString])
-> (State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a b. (a -> b) -> a -> b
$ MutableArray# RealWorld [FastString]
-> Int# -> State# RealWorld -> (# State# RealWorld, [FastString] #)
forall d a.
MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
readArray# MutableArray# RealWorld [FastString]
buckets# Int#
idx#
Maybe FastString
res <- [FastString] -> ShortByteString -> IO (Maybe FastString)
bucket_match [FastString]
bucket ShortByteString
sbs
case Maybe FastString
res of
Just FastString
found -> FastString -> IO FastString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FastString
found
Maybe FastString
Nothing -> do
(State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s1# ->
case MutableArray# RealWorld [FastString]
-> Int# -> [FastString] -> State# RealWorld -> State# RealWorld
forall d a. MutableArray# d a -> Int# -> a -> State# d -> State# d
writeArray# MutableArray# RealWorld [FastString]
buckets# Int#
idx# (FastString
fs FastString -> [FastString] -> [FastString]
forall a. a -> [a] -> [a]
: [FastString]
bucket) State# RealWorld
s1# of
State# RealWorld
s2# -> (# State# RealWorld
s2#, () #)
Int
_ <- FastMutInt -> Int -> IO Int
atomicFetchAddFastMut FastMutInt
counter Int
1
FastString -> IO FastString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FastString
fs
bucket_match :: [FastString] -> ShortByteString -> IO (Maybe FastString)
bucket_match :: [FastString] -> ShortByteString -> IO (Maybe FastString)
bucket_match [] ShortByteString
_ = Maybe FastString -> IO (Maybe FastString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FastString
forall a. Maybe a
Nothing
bucket_match (fs :: FastString
fs@(FastString {fs_sbs :: FastString -> ShortByteString
fs_sbs=ShortByteString
fs_sbs}) : [FastString]
ls) ShortByteString
sbs
| ShortByteString
fs_sbs ShortByteString -> ShortByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ShortByteString
sbs = Maybe FastString -> IO (Maybe FastString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FastString -> Maybe FastString
forall a. a -> Maybe a
Just FastString
fs)
| Bool
otherwise = [FastString] -> ShortByteString -> IO (Maybe FastString)
bucket_match [FastString]
ls ShortByteString
sbs
mkFastStringBytes :: Ptr Word8 -> Int -> FastString
mkFastStringBytes :: Ptr Word8 -> Int -> FastString
mkFastStringBytes !Ptr Word8
ptr !Int
len =
IO FastString -> FastString
forall a. IO a -> a
unsafeDupablePerformIO (IO FastString -> FastString) -> IO FastString -> FastString
forall a b. (a -> b) -> a -> b
$ do
ShortByteString
sbs <- Ptr Word8 -> Int -> IO ShortByteString
forall a. Ptr a -> Int -> IO ShortByteString
newSBSFromPtr Ptr Word8
ptr Int
len
(Int -> FastMutInt -> IO FastString)
-> ShortByteString -> IO FastString
mkFastStringWith (ShortByteString -> Int -> FastMutInt -> IO FastString
mkNewFastStringShortByteString ShortByteString
sbs) ShortByteString
sbs
newSBSFromPtr :: Ptr a -> Int -> IO ShortByteString
newSBSFromPtr :: forall a. Ptr a -> Int -> IO ShortByteString
newSBSFromPtr (Ptr Addr#
src#) (I# Int#
len#) =
(State# RealWorld -> (# State# RealWorld, ShortByteString #))
-> IO ShortByteString
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, ShortByteString #))
-> IO ShortByteString)
-> (State# RealWorld -> (# State# RealWorld, ShortByteString #))
-> IO ShortByteString
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
case Int#
-> State# RealWorld
-> (# State# RealWorld, MutableByteArray# RealWorld #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
len# State# RealWorld
s of { (# State# RealWorld
s, MutableByteArray# RealWorld
dst# #) ->
case Addr#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
forall d.
Addr#
-> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
copyAddrToByteArray# Addr#
src# MutableByteArray# RealWorld
dst# Int#
0# Int#
len# State# RealWorld
s of { State# RealWorld
s ->
case MutableByteArray# RealWorld
-> State# RealWorld -> (# State# RealWorld, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# RealWorld
dst# State# RealWorld
s of { (# State# RealWorld
s, ByteArray#
ba# #) ->
(# State# RealWorld
s, ByteArray# -> ShortByteString
SBS.SBS ByteArray#
ba# #) }}}
mkFastStringByteString :: ByteString -> FastString
mkFastStringByteString :: ByteString -> FastString
mkFastStringByteString ByteString
bs =
let sbs :: ShortByteString
sbs = ByteString -> ShortByteString
SBS.toShort ByteString
bs in
IO FastString -> FastString
forall a. IO a -> a
inlinePerformIO (IO FastString -> FastString) -> IO FastString -> FastString
forall a b. (a -> b) -> a -> b
$
(Int -> FastMutInt -> IO FastString)
-> ShortByteString -> IO FastString
mkFastStringWith (ShortByteString -> Int -> FastMutInt -> IO FastString
mkNewFastStringShortByteString ShortByteString
sbs) ShortByteString
sbs
mkFastStringShortByteString :: ShortByteString -> FastString
mkFastStringShortByteString :: ShortByteString -> FastString
mkFastStringShortByteString ShortByteString
sbs =
IO FastString -> FastString
forall a. IO a -> a
inlinePerformIO (IO FastString -> FastString) -> IO FastString -> FastString
forall a b. (a -> b) -> a -> b
$ (Int -> FastMutInt -> IO FastString)
-> ShortByteString -> IO FastString
mkFastStringWith (ShortByteString -> Int -> FastMutInt -> IO FastString
mkNewFastStringShortByteString ShortByteString
sbs) ShortByteString
sbs
mkFastString :: String -> FastString
{-# NOINLINE[1] mkFastString #-}
mkFastString :: String -> FastString
mkFastString String
str =
IO FastString -> FastString
forall a. IO a -> a
inlinePerformIO (IO FastString -> FastString) -> IO FastString -> FastString
forall a b. (a -> b) -> a -> b
$ do
ShortByteString
sbs <- String -> IO ShortByteString
utf8EncodeShortByteString String
str
(Int -> FastMutInt -> IO FastString)
-> ShortByteString -> IO FastString
mkFastStringWith (ShortByteString -> Int -> FastMutInt -> IO FastString
mkNewFastStringShortByteString ShortByteString
sbs) ShortByteString
sbs
{-# RULES
"bytesFS/mkFastString" forall x. bytesFS (mkFastString x) = utf8EncodeString x #-}
mkFastStringByteList :: [Word8] -> FastString
mkFastStringByteList :: [Word8] -> FastString
mkFastStringByteList [Word8]
str = ShortByteString -> FastString
mkFastStringShortByteString ([Word8] -> ShortByteString
SBS.pack [Word8]
str)
mkZFastString :: FastMutInt -> ShortByteString -> FastZString
mkZFastString :: FastMutInt -> ShortByteString -> FastZString
mkZFastString FastMutInt
n_zencs ShortByteString
sbs = IO FastZString -> FastZString
forall a. IO a -> a
unsafePerformIO (IO FastZString -> FastZString) -> IO FastZString -> FastZString
forall a b. (a -> b) -> a -> b
$ do
Int
_ <- FastMutInt -> Int -> IO Int
atomicFetchAddFastMut FastMutInt
n_zencs Int
1
FastZString -> IO FastZString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FastZString -> IO FastZString) -> FastZString -> IO FastZString
forall a b. (a -> b) -> a -> b
$ String -> FastZString
mkFastZStringString (ShowS
zEncodeString (ShortByteString -> String
utf8DecodeShortByteString ShortByteString
sbs))
mkNewFastStringShortByteString :: ShortByteString -> Int
-> FastMutInt -> IO FastString
mkNewFastStringShortByteString :: ShortByteString -> Int -> FastMutInt -> IO FastString
mkNewFastStringShortByteString ShortByteString
sbs Int
uid FastMutInt
n_zencs = do
let zstr :: FastZString
zstr = FastMutInt -> ShortByteString -> FastZString
mkZFastString FastMutInt
n_zencs ShortByteString
sbs
Int
chars <- ShortByteString -> IO Int
countUTF8Chars ShortByteString
sbs
FastString -> IO FastString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Int -> ShortByteString -> FastZString -> FastString
FastString Int
uid Int
chars ShortByteString
sbs FastZString
zstr)
hashStr :: ShortByteString -> Int
hashStr :: ShortByteString -> Int
hashStr sbs :: ShortByteString
sbs@(SBS.SBS ByteArray#
ba#) = Int# -> Int# -> Int
loop Int#
0# Int#
0#
where
!(I# Int#
len#) = ShortByteString -> Int
SBS.length ShortByteString
sbs
loop :: Int# -> Int# -> Int
loop Int#
h Int#
n =
if Int# -> Bool
isTrue# (Int#
n Int# -> Int# -> Int#
==# Int#
len#) then
Int# -> Int
I# Int#
h
else
let
#if __GLASGOW_HASKELL__ >= 901
!c :: Int#
c = Int8# -> Int#
int8ToInt# (ByteArray# -> Int# -> Int8#
indexInt8Array# ByteArray#
ba# Int#
n)
#else
!c = indexInt8Array# ba# n
#endif
!h2 :: Int#
h2 = (Int#
h Int# -> Int# -> Int#
*# Int#
16777619#) Int# -> Int# -> Int#
`xorI#` Int#
c
in
Int# -> Int# -> Int
loop Int#
h2 (Int#
n Int# -> Int# -> Int#
+# Int#
1#)
lengthFS :: FastString -> Int
lengthFS :: FastString -> Int
lengthFS FastString
fs = FastString -> Int
n_chars FastString
fs
nullFS :: FastString -> Bool
nullFS :: FastString -> Bool
nullFS FastString
fs = ShortByteString -> Bool
SBS.null (ShortByteString -> Bool) -> ShortByteString -> Bool
forall a b. (a -> b) -> a -> b
$ FastString -> ShortByteString
fs_sbs FastString
fs
unpackFS :: FastString -> String
unpackFS :: FastString -> String
unpackFS FastString
fs = ShortByteString -> String
utf8DecodeShortByteString (ShortByteString -> String) -> ShortByteString -> String
forall a b. (a -> b) -> a -> b
$ FastString -> ShortByteString
fs_sbs FastString
fs
zEncodeFS :: FastString -> FastZString
zEncodeFS :: FastString -> FastZString
zEncodeFS FastString
fs = FastString -> FastZString
fs_zenc FastString
fs
appendFS :: FastString -> FastString -> FastString
appendFS :: FastString -> FastString -> FastString
appendFS FastString
fs1 FastString
fs2 = ShortByteString -> FastString
mkFastStringShortByteString
(ShortByteString -> FastString) -> ShortByteString -> FastString
forall a b. (a -> b) -> a -> b
$ ShortByteString -> ShortByteString -> ShortByteString
forall a. Semigroup a => a -> a -> a
(Semi.<>) (FastString -> ShortByteString
fs_sbs FastString
fs1) (FastString -> ShortByteString
fs_sbs FastString
fs2)
concatFS :: [FastString] -> FastString
concatFS :: [FastString] -> FastString
concatFS = ShortByteString -> FastString
mkFastStringShortByteString (ShortByteString -> FastString)
-> ([FastString] -> ShortByteString) -> [FastString] -> FastString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ShortByteString] -> ShortByteString
forall a. Monoid a => [a] -> a
mconcat ([ShortByteString] -> ShortByteString)
-> ([FastString] -> [ShortByteString])
-> [FastString]
-> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FastString -> ShortByteString)
-> [FastString] -> [ShortByteString]
forall a b. (a -> b) -> [a] -> [b]
map FastString -> ShortByteString
fs_sbs
headFS :: FastString -> Char
headFS :: FastString -> Char
headFS FastString
fs
| ShortByteString -> Bool
SBS.null (ShortByteString -> Bool) -> ShortByteString -> Bool
forall a b. (a -> b) -> a -> b
$ FastString -> ShortByteString
fs_sbs FastString
fs = String -> Char
forall a. String -> a
panic String
"headFS: Empty FastString"
headFS FastString
fs = String -> Char
forall a. HasCallStack => [a] -> a
head (String -> Char) -> String -> Char
forall a b. (a -> b) -> a -> b
$ FastString -> String
unpackFS FastString
fs
consFS :: Char -> FastString -> FastString
consFS :: Char -> FastString -> FastString
consFS Char
c FastString
fs = String -> FastString
mkFastString (Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: FastString -> String
unpackFS FastString
fs)
unconsFS :: FastString -> Maybe (Char, FastString)
unconsFS :: FastString -> Maybe (Char, FastString)
unconsFS FastString
fs =
case FastString -> String
unpackFS FastString
fs of
[] -> Maybe (Char, FastString)
forall a. Maybe a
Nothing
(Char
chr : String
str) -> (Char, FastString) -> Maybe (Char, FastString)
forall a. a -> Maybe a
Just (Char
chr, String -> FastString
mkFastString String
str)
uniqueOfFS :: FastString -> Int
uniqueOfFS :: FastString -> Int
uniqueOfFS FastString
fs = FastString -> Int
uniq FastString
fs
nilFS :: FastString
nilFS :: FastString
nilFS = String -> FastString
mkFastString String
""
isUnderscoreFS :: FastString -> Bool
isUnderscoreFS :: FastString -> Bool
isUnderscoreFS FastString
fs = FastString
fs FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== String -> FastString
fsLit String
"_"
getFastStringTable :: IO [[[FastString]]]
getFastStringTable :: IO [[[FastString]]]
getFastStringTable =
[Int] -> (Int -> IO [[FastString]]) -> IO [[[FastString]]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0 .. Int
numSegments Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> IO [[FastString]]) -> IO [[[FastString]]])
-> (Int -> IO [[FastString]]) -> IO [[[FastString]]]
forall a b. (a -> b) -> a -> b
$ \(I# Int#
i#) -> do
let (# IORef FastStringTableSegment
segmentRef #) = Array# (IORef FastStringTableSegment)
-> Int# -> (# IORef FastStringTableSegment #)
forall a. Array# a -> Int# -> (# a #)
indexArray# Array# (IORef FastStringTableSegment)
segments# Int#
i#
FastStringTableSegment MVar ()
_ FastMutInt
_ MutableArray# RealWorld [FastString]
buckets# <- IORef FastStringTableSegment -> IO FastStringTableSegment
forall a. IORef a -> IO a
readIORef IORef FastStringTableSegment
segmentRef
let bucketSize :: Int
bucketSize = Int# -> Int
I# (MutableArray# RealWorld [FastString] -> Int#
forall d a. MutableArray# d a -> Int#
sizeofMutableArray# MutableArray# RealWorld [FastString]
buckets#)
[Int] -> (Int -> IO [FastString]) -> IO [[FastString]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0 .. Int
bucketSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> IO [FastString]) -> IO [[FastString]])
-> (Int -> IO [FastString]) -> IO [[FastString]]
forall a b. (a -> b) -> a -> b
$ \(I# Int#
j#) ->
(State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString])
-> (State# RealWorld -> (# State# RealWorld, [FastString] #))
-> IO [FastString]
forall a b. (a -> b) -> a -> b
$ MutableArray# RealWorld [FastString]
-> Int# -> State# RealWorld -> (# State# RealWorld, [FastString] #)
forall d a.
MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
readArray# MutableArray# RealWorld [FastString]
buckets# Int#
j#
where
!(FastStringTable FastMutInt
_ FastMutInt
_ Array# (IORef FastStringTableSegment)
segments#) = FastStringTable
stringTable
getFastStringZEncCounter :: IO Int
getFastStringZEncCounter :: IO Int
getFastStringZEncCounter = FastMutInt -> IO Int
readFastMutInt FastMutInt
n_zencs
where
!(FastStringTable FastMutInt
_ FastMutInt
n_zencs Array# (IORef FastStringTableSegment)
_) = FastStringTable
stringTable
hPutFS :: Handle -> FastString -> IO ()
hPutFS :: Handle -> FastString -> IO ()
hPutFS Handle
handle FastString
fs = Handle -> ByteString -> IO ()
BS.hPut Handle
handle (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ FastString -> ByteString
bytesFS FastString
fs
data PtrString = PtrString !(Ptr Word8) !Int
mkPtrString# :: Addr# -> PtrString
{-# INLINE mkPtrString# #-}
mkPtrString# :: Addr# -> PtrString
mkPtrString# Addr#
a# = Ptr Word8 -> Int -> PtrString
PtrString (Addr# -> Ptr Word8
forall a. Addr# -> Ptr a
Ptr Addr#
a#) (Ptr Word8 -> Int
ptrStrLength (Addr# -> Ptr Word8
forall a. Addr# -> Ptr a
Ptr Addr#
a#))
{-# NOINLINE[0] mkPtrString #-}
mkPtrString :: String -> PtrString
mkPtrString :: String -> PtrString
mkPtrString String
s =
IO PtrString -> PtrString
forall a. IO a -> a
unsafePerformIO (do
let len :: Int
len = String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s
Ptr Word8
p <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
len
let
loop :: Int -> String -> IO ()
loop :: Int -> String -> IO ()
loop !Int
_ [] = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
loop Int
n (Char
c:String
cs) = do
Ptr Word8 -> Int -> Word8 -> IO ()
forall b. Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
p Int
n (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c) :: Word8)
Int -> String -> IO ()
loop (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) String
cs
Int -> String -> IO ()
loop Int
0 String
s
PtrString -> IO PtrString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Word8 -> Int -> PtrString
PtrString Ptr Word8
p Int
len)
)
{-# RULES "mkPtrString"
forall x . mkPtrString (unpackCString# x) = mkPtrString# x #-}
unpackPtrString :: PtrString -> String
unpackPtrString :: PtrString -> String
unpackPtrString (PtrString (Ptr Addr#
p#) (I# Int#
n#)) = Addr# -> Int# -> String
unpackNBytes# Addr#
p# Int#
n#
lengthPS :: PtrString -> Int
lengthPS :: PtrString -> Int
lengthPS (PtrString Ptr Word8
_ Int
n) = Int
n
#if !MIN_VERSION_GLASGOW_HASKELL(9,0,0,0)
foreign import ccall unsafe "strlen"
cstringLength# :: Addr# -> Int#
#endif
ptrStrLength :: Ptr Word8 -> Int
{-# INLINE ptrStrLength #-}
ptrStrLength :: Ptr Word8 -> Int
ptrStrLength (Ptr Addr#
a) = Int# -> Int
I# (Addr# -> Int#
cstringLength# Addr#
a)
{-# NOINLINE fsLit #-}
fsLit :: String -> FastString
fsLit :: String -> FastString
fsLit String
x = String -> FastString
mkFastString String
x
{-# RULES "fslit"
forall x . fsLit (unpackCString# x) = mkFastString# x #-}