ghc-lib-parser-9.4.4.20221225: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Data.FastString

Description

There are two principal string types used internally by GHC:

FastString
  • A compact, hash-consed, representation of character strings.
  • Generated by fsLit.
  • You can get a Unique from them.
  • Equality test is O(1) (it uses the Unique).
  • Comparison is O(1) or O(n):
  • O(n) but deterministic with lexical comparison (lexicalCompareFS)
  • O(1) but non-deterministic with Unique comparison (uniqCompareFS)
  • Turn into SDoc with ftext.
PtrString
  • Pointer and size of a Latin-1 encoded string.
  • Practically no operations.
  • Outputting them is fast.
  • Generated by mkPtrString.
  • Length of string literals (mkPtrString "abc") is computed statically
  • Turn into SDoc with ptext
  • Requires manual memory management. Improper use may lead to memory leaks or dangling pointers.
  • It assumes Latin-1 as the encoding, therefore it cannot represent arbitrary Unicode strings.

Use PtrString unless you want the facilities of FastString.

Synopsis

ByteString

bytesFS :: FastString -> ByteString Source #

Gives the Modified UTF-8 encoded bytes corresponding to a FastString

fastStringToByteString :: FastString -> ByteString Source #

Deprecated: Use bytesFS instead

Gives the Modified UTF-8 encoded bytes corresponding to a FastString

ShortByteString

FastZString

data FastZString Source #

Instances

Instances details
NFData FastZString Source # 
Instance details

Defined in GHC.Data.FastString

Methods

rnf :: FastZString -> () #

FastStrings

data FastString Source #

A FastString is a UTF-8 encoded string together with a unique ID. All FastStrings are stored in a global hashtable to support fast O(1) comparison.

It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally.

Constructors

FastString 

Fields

Instances

Instances details
Data FastString Source # 
Instance details

Defined in GHC.Data.FastString

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FastString -> c FastString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FastString #

toConstr :: FastString -> Constr #

dataTypeOf :: FastString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FastString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FastString) #

gmapT :: (forall b. Data b => b -> b) -> FastString -> FastString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FastString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FastString -> r #

gmapQ :: (forall d. Data d => d -> u) -> FastString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FastString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FastString -> m FastString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FastString -> m FastString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FastString -> m FastString #

IsString FastString Source # 
Instance details

Defined in GHC.Data.FastString

Monoid FastString Source # 
Instance details

Defined in GHC.Data.FastString

Semigroup FastString Source # 
Instance details

Defined in GHC.Data.FastString

Show FastString Source # 
Instance details

Defined in GHC.Data.FastString

NFData FastString Source # 
Instance details

Defined in GHC.Data.FastString

Methods

rnf :: FastString -> () #

Uniquable FastString Source # 
Instance details

Defined in GHC.Types.Unique

Binary FastString Source # 
Instance details

Defined in GHC.Utils.Binary

Outputable FastString Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: FastString -> SDoc Source #

Eq FastString Source # 
Instance details

Defined in GHC.Data.FastString

type Anno FieldLabelString Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (SourceText, RuleName) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (SourceText, RuleName) Source # 
Instance details

Defined in GHC.Hs.Decls

newtype NonDetFastString Source #

Non-deterministic FastString

This is a simple FastString wrapper with an Ord instance using uniqCompareFS (i.e. which compares FastStrings on their Uniques). Hence it is not deterministic from one run to the other.

Instances

Instances details
Data NonDetFastString Source # 
Instance details

Defined in GHC.Data.FastString

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonDetFastString -> c NonDetFastString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NonDetFastString #

toConstr :: NonDetFastString -> Constr #

dataTypeOf :: NonDetFastString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NonDetFastString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NonDetFastString) #

gmapT :: (forall b. Data b => b -> b) -> NonDetFastString -> NonDetFastString #

gmapQl :: (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 #

gmapQ :: (forall d. Data d => d -> u) -> NonDetFastString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonDetFastString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonDetFastString -> m NonDetFastString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonDetFastString -> m NonDetFastString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonDetFastString -> m NonDetFastString #

Show NonDetFastString Source # 
Instance details

Defined in GHC.Data.FastString

Binary NonDetFastString Source # 
Instance details

Defined in GHC.Utils.Binary

Outputable NonDetFastString Source # 
Instance details

Defined in GHC.Utils.Outputable

Eq NonDetFastString Source # 
Instance details

Defined in GHC.Data.FastString

Ord NonDetFastString Source # 
Instance details

Defined in GHC.Data.FastString

newtype LexicalFastString Source #

Lexical FastString

This is a simple FastString wrapper with an Ord instance using lexicalCompareFS (i.e. which compares FastStrings on their String representation). Hence it is deterministic from one run to the other.

Instances

Instances details
Data LexicalFastString Source # 
Instance details

Defined in GHC.Data.FastString

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFastString -> c LexicalFastString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFastString #

toConstr :: LexicalFastString -> Constr #

dataTypeOf :: LexicalFastString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFastString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFastString) #

gmapT :: (forall b. Data b => b -> b) -> LexicalFastString -> LexicalFastString #

gmapQl :: (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 #

gmapQ :: (forall d. Data d => d -> u) -> LexicalFastString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFastString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFastString -> m LexicalFastString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFastString -> m LexicalFastString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFastString -> m LexicalFastString #

Show LexicalFastString Source # 
Instance details

Defined in GHC.Data.FastString

Binary LexicalFastString Source # 
Instance details

Defined in GHC.Utils.Binary

Outputable LexicalFastString Source # 
Instance details

Defined in GHC.Utils.Outputable

Eq LexicalFastString Source # 
Instance details

Defined in GHC.Data.FastString

Ord LexicalFastString Source # 
Instance details

Defined in GHC.Data.FastString

Construction

mkFastString :: String -> FastString Source #

Creates a UTF-8 encoded FastString from a String

mkFastStringByteList :: [Word8] -> FastString Source #

Creates a FastString from a UTF-8 encoded [Word8]

Deconstruction

unpackFS :: FastString -> String Source #

Unpacks and decodes the FastString

Encoding

zEncodeFS :: FastString -> FastZString Source #

Returns a Z-encoded version of a FastString. This might be the original, if it was already Z-encoded. The first time this function is applied to a particular FastString, the results are memoized.

Operations

lengthFS :: FastString -> Int Source #

Returns the length of the FastString in characters

nullFS :: FastString -> Bool Source #

Returns True if the FastString is empty

lexicalCompareFS :: FastString -> FastString -> Ordering Source #

Compare FastString lexically

If you don't care about the lexical ordering, use uniqCompareFS instead.

uniqCompareFS :: FastString -> FastString -> Ordering Source #

Compare FastString by their Unique (not lexically).

Much cheaper than lexicalCompareFS but non-deterministic!

Outputting

hPutFS :: Handle -> FastString -> IO () Source #

Outputs a FastString with no decoding at all, that is, you get the actual bytes in the FastString written to the Handle.

Internal

PtrStrings

data PtrString Source #

A PtrString is a pointer to some array of Latin-1 encoded chars.

Constructors

PtrString !(Ptr Word8) !Int 

Construction

mkPtrString# :: Addr# -> PtrString Source #

Wrap an unboxed address into a PtrString.

mkPtrString :: String -> PtrString Source #

Encode a String into a newly allocated PtrString using Latin-1 encoding. The original string must not contain non-Latin-1 characters (above codepoint 0xff).

Deconstruction

unpackPtrString :: PtrString -> String Source #

Decode a PtrString back into a String using Latin-1 encoding. This does not free the memory associated with PtrString.

Operations

lengthPS :: PtrString -> Int Source #

Return the length of a PtrString