Cabal-3.2.1.0: A framework for packaging Haskell software
Safe HaskellNone
LanguageHaskell2010

Distribution.Utils.ShortText

Description

Compact representation of short Strings

This module is designed to be import qualifeid

import Distribution.Utils.ShortText (ShortText)
import qualifeid Distribution.Utils.ShortText as ShortText
Synopsis

ShortText type

data ShortText Source #

Compact representation of short Strings

The data is stored internally as UTF8 in an ShortByteString when compiled against bytestring >= 0.10.4, and otherwise the fallback is to use plain old non-compat '[Char]'.

Note: This type is for internal uses (such as e.g. PackageName) and shall not be exposed in Cabal's API

Since: Cabal-2.0.0.2

Instances

Instances details
Eq ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Data ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Methods

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

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

toConstr :: ShortText -> Constr Source #

dataTypeOf :: ShortText -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Read ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Show ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

IsString ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Generic ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Associated Types

type Rep ShortText :: Type -> Type Source #

Semigroup ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Monoid ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Binary ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

NFData ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

Methods

rnf :: ShortText -> () Source #

Structured ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

type Rep ShortText # 
Instance details

Defined in Distribution.Utils.ShortText

type Rep ShortText = D1 ('MetaData "ShortText" "Distribution.Utils.ShortText" "Cabal-3.2.1.0" 'True) (C1 ('MetaCons "ST" 'PrefixI 'True) (S1 ('MetaSel ('Just "unST") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

unsafeFromUTF8BS :: ByteString -> ShortText Source #

Convert from UTF-8 encoded strict ByteString.

Since: Cabal-3.2.0.0

Operations

null :: ShortText -> Bool Source #

Text whether ShortText is empty.

Since: Cabal-3.2.0.0

length :: ShortText -> Int Source #

O(n). Length in characters. Slow as converts to string.

Since: Cabal-3.2.0.0

internal utilities

decodeStringUtf8 :: [Word8] -> String Source #

Decode String from UTF8-encoded octets.

Invalid data in the UTF8 stream (this includes code-points U+D800 through U+DFFF) will be decoded as the replacement character (U+FFFD).

See also encodeStringUtf8

encodeStringUtf8 :: String -> [Word8] Source #

Encode String to a list of UTF8-encoded octets

Code-points in the U+D800-U+DFFF range will be encoded as the replacement character (i.e. U+FFFD).

See also decodeUtf8