InternedData-0.0.0.1: Data interning (with compact regions where possible)

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.Interned

Description

An implementation of Int-mapped ByteStrings with internalization. Wrap a ByteString with ibs to receive a IBS. This internalizes the given ByteString, meaning that two bytestring inputs x and y will yield the same IBS if they have the same bytestring representation.

For convenience, conversion from and to text is possible as well and uses UTF8 encoding.

Since internalized ByteString values are never released, be sure to use it sparingly. I.e. to internalize words, not full sentences.

NOTE Currently, we use a ByteString internally and can not compact the structure. The code remains, though as comments in case we switch to another structure.

Synopsis

Documentation

pattern V_IBS :: (Vector Int) -> Vector (IBS k) Source #

pattern MV_IBS :: (MVector s Int) -> MVector s (IBS k) Source #

newtype IBS k Source #

An IBS behaves much like a ByteString, but is represented as an Int internally. Its phantom type is polykinded, since we might want to use type-level strings to name things.

Constructors

IBS 

Fields

Instances
Vector Vector (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (IBS k2) -> m (Vector (IBS k2)) #

basicUnsafeThaw :: PrimMonad m => Vector (IBS k2) -> m (Mutable Vector (PrimState m) (IBS k2)) #

basicLength :: Vector (IBS k2) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (IBS k2) -> Vector (IBS k2) #

basicUnsafeIndexM :: Monad m => Vector (IBS k2) -> Int -> m (IBS k2) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (IBS k2) -> Vector (IBS k2) -> m () #

elemseq :: Vector (IBS k2) -> IBS k2 -> b -> b #

MVector MVector (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

basicLength :: MVector s (IBS k2) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (IBS k2) -> MVector s (IBS k2) #

basicOverlaps :: MVector s (IBS k2) -> MVector s (IBS k2) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (IBS k2)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (IBS k2) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> IBS k2 -> m (MVector (PrimState m) (IBS k2)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (IBS k2) -> Int -> m (IBS k2) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (IBS k2) -> Int -> IBS k2 -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (IBS k2) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (IBS k2) -> IBS k2 -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (IBS k2) -> MVector (PrimState m) (IBS k2) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (IBS k2) -> MVector (PrimState m) (IBS k2) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (IBS k2) -> Int -> m (MVector (PrimState m) (IBS k2)) #

Eq (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

(==) :: IBS k2 -> IBS k2 -> Bool #

(/=) :: IBS k2 -> IBS k2 -> Bool #

Ord (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

compare :: IBS k2 -> IBS k2 -> Ordering #

(<) :: IBS k2 -> IBS k2 -> Bool #

(<=) :: IBS k2 -> IBS k2 -> Bool #

(>) :: IBS k2 -> IBS k2 -> Bool #

(>=) :: IBS k2 -> IBS k2 -> Bool #

max :: IBS k2 -> IBS k2 -> IBS k2 #

min :: IBS k2 -> IBS k2 -> IBS k2 #

Read (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

readsPrec :: Int -> ReadS (IBS k2) #

readList :: ReadS [IBS k2] #

readPrec :: ReadPrec (IBS k2) #

readListPrec :: ReadPrec [IBS k2] #

Show (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

showsPrec :: Int -> IBS k2 -> ShowS #

show :: IBS k2 -> String #

showList :: [IBS k2] -> ShowS #

IsString (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

fromString :: String -> IBS k2 #

Generic (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Associated Types

type Rep (IBS k2) :: Type -> Type #

Methods

from :: IBS k2 -> Rep (IBS k2) x #

to :: Rep (IBS k2) x -> IBS k2 #

Hashable (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

hashWithSalt :: Int -> IBS k2 -> Int #

hash :: IBS k2 -> Int #

ToJSON (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

toJSON :: IBS k2 -> Value #

toEncoding :: IBS k2 -> Encoding #

toJSONList :: [IBS k2] -> Value #

toEncodingList :: [IBS k2] -> Encoding #

FromJSON (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

parseJSON :: Value -> Parser (IBS k2) #

parseJSONList :: Value -> Parser [IBS k2] #

Binary (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

put :: IBS k2 -> Put #

get :: Get (IBS k2) #

putList :: [IBS k2] -> Put #

Serialize (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

put :: Putter (IBS k2) #

get :: Get (IBS k2) #

NFData (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

Methods

rnf :: IBS k2 -> () #

Unbox (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

newtype MVector s (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

newtype MVector s (IBS k2) = MV_IBS (MVector s Int)
type Rep (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

type Rep (IBS k2) = D1 (MetaData "IBS" "Data.ByteString.Interned" "InternedData-0.0.0.1-CxpYoX0we0vKF3Q98H05Nk" True) (C1 (MetaCons "IBS" PrefixI True) (S1 (MetaSel (Just "getIBS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
newtype Vector (IBS k2) Source # 
Instance details

Defined in Data.ByteString.Interned

newtype Vector (IBS k2) = V_IBS (Vector Int)

ibsText :: Text -> IBS k Source #

Handy wrapper to internalize a Text and get a IBS.

ibsFrom :: ConvertibleStrings x Text => x -> IBS k Source #

Convert into an IBS, using a Text intermediate for proper UTF8 conversion.