ascii-1.7.0.0: The ASCII character set and encoding
Safe HaskellSafe-Inferred
LanguageHaskell2010

ASCII

Description

The American Standard Code for Information Interchange (ASCII) comprises a set of 128 characters, each represented by 7 bits. 33 of these characters are Control codes; a few of these are still in use, but most are obsolete relics of the early days of computing. The other 95 are Printable characters such as letters and numbers, mostly corresponding to the keys on an American English keyboard.

Nowadays instead of ASCII we typically work with text using an encoding such as UTF-8 that can represent the entire Unicode character set, which includes over a hundred thousand characters and is not limited to the symbols of any particular writing system or culture. However, ASCII is still relevant to network protocols; for example, we can see it in the specification of HTTP.

There is a convenient relationship between ASCII and Unicode: the ASCII characters are the first 128 characters of the much larger Unicode character set. The C0 Controls and Basic Latin section of the Unicode standard contains a list of all the ASCII characters. You may also find this list replicated in the ASCII.Char module; each ASCII character corresponds to a constructor of the Char type.

We do not elaborate on the semantics of the control characters here, because this information is both obsolete and restricted by copyright law. It is described by a document entitled "Coded Character Sets - 7-Bit American National Standard Code for Information Interchange (7-Bit ASCII)", published by American National Standards Institute (ANSI) and available for purchase on their website.

Synopsis

Char

ASCII

See also: ASCII.Char

data Char #

A character in the ASCII character set

Instances

Instances details
DigitSuperset Char 
Instance details

Defined in ASCII.Decimal

HexCharSuperset Char 
Instance details

Defined in ASCII.Hexadecimal

CharIso Char

Char is trivially isomorphic to itself. (This instance is uninteresting.)

Instance details

Defined in ASCII.Isomorphism

Methods

toChar :: Char -> Char #

CharSuperset Char

Char is trivially a superset of itself.

Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Char -> Char #

FromChar Char 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char -> Char #

ToCaselessChar Char 
Instance details

Defined in ASCII.Superset

ToChar Char 
Instance details

Defined in ASCII.Superset

Data Char

The Data instance allows ASCII characters to be used with generic programming in the “SYB” style. (See the syb package and the 2003 paper Scrap Your Boilerplate by Ralf Lämmel and Simon Peyton Jones.)

Instance details

Defined in ASCII.Char

Methods

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

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

toConstr :: Char -> Constr #

dataTypeOf :: Char -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Char

The least character is Null, and the greatest character is Delete. You can write ([minBound .. maxBound] :: [ASCII.Char]) to get a list of all the ASCII characters.

Instance details

Defined in ASCII.Char

Enum Char

The Enum instance allows us to use range syntax, for example [SmallLetterA .. SmallLetterZ] is a list all lower-case letters from a to z. Instead of toEnum and fromEnum, consider using toInt and fromIntMaybe.

Instance details

Defined in ASCII.Char

Methods

succ :: Char -> Char #

pred :: Char -> Char #

toEnum :: Int -> Char #

fromEnum :: Char -> Int #

enumFrom :: Char -> [Char] #

enumFromThen :: Char -> Char -> [Char] #

enumFromTo :: Char -> Char -> [Char] #

enumFromThenTo :: Char -> Char -> Char -> [Char] #

Generic Char 
Instance details

Defined in ASCII.Char

Associated Types

type Rep Char :: Type -> Type #

Methods

from :: Char -> Rep Char x #

to :: Rep Char x -> Char #

Show Char

show produces the name of a constructor. For example, the character e is shown as “SmallLetterE”. See ASCII.Char for the complete list of constructor names.

Instance details

Defined in ASCII.Char

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Eq Char

ASCII characters can be compared for equality using (==). Comparisons are case-sensitive; SmallLetterA /= CapitalLetterA.

Instance details

Defined in ASCII.Char

Methods

(==) :: Char -> Char -> Bool #

(/=) :: Char -> Char -> Bool #

Ord Char

ASCII characters are ordered; for example, the letter A is "less than" (<) the letter B because it appears earlier in the list. The ordering of ASCII characters is the same as the ordering of the corresponding Unicode Chars.

Instance details

Defined in ASCII.Char

Methods

compare :: Char -> Char -> Ordering #

(<) :: Char -> Char -> Bool #

(<=) :: Char -> Char -> Bool #

(>) :: Char -> Char -> Bool #

(>=) :: Char -> Char -> Bool #

max :: Char -> Char -> Char #

min :: Char -> Char -> Char #

Hashable Char

The Hashable instance lets us collect ASCII characters in hash-based sets, and it lets us use ASCII characters as keys in hash-based maps. (See the unordered-containers package.)

Instance details

Defined in ASCII.Char

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

KnownCase letterCase => ToCasefulChar letterCase Char 
Instance details

Defined in ASCII.Superset

DigitStringSuperset [Char] 
Instance details

Defined in ASCII.Decimal

HexStringSuperset [Char] 
Instance details

Defined in ASCII.Hexadecimal

type Rep Char

The Generic instance allows ASCII characters to be used with generic programming in the “generic deriving” style. (See the generic-data package and the 2010 paper A generic deriving mechanism for Haskell by José Pedro Magalhães, Atze Dijkstra, Johan Jeuring, and Andres Löh.)

Instance details

Defined in ASCII.Char

type Rep Char = D1 ('MetaData "Char" "ASCII.Char" "ascii-char-1.0.1.0-LiVxY0eZCce7UgRuMTOed" 'False) (((((((C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StartOfHeading" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StartOfText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndOfText" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EndOfTransmission" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Enquiry" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Acknowledgement" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bell" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Backspace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HorizontalTab" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LineFeed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerticalTab" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FormFeed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CarriageReturn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ShiftOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ShiftIn" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "DataLinkEscape" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeviceControl1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeviceControl2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeviceControl3" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DeviceControl4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NegativeAcknowledgement" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SynchronousIdle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndOfTransmissionBlock" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Cancel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndOfMedium" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Substitute" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Escape" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FileSeparator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GroupSeparator" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RecordSeparator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnitSeparator" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: (((((C1 ('MetaCons "Space" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExclamationMark" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QuotationMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NumberSign" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DollarSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PercentSign" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Ampersand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Apostrophe" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "LeftParenthesis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightParenthesis" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asterisk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlusSign" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Comma" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HyphenMinus" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FullStop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Slash" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "Digit0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Digit2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit3" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Digit4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit5" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Digit6" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit7" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Digit8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit9" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Colon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Semicolon" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LessThanSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualsSign" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GreaterThanSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuestionMark" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: ((((((C1 ('MetaCons "AtSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterA" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CapitalLetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterG" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CapitalLetterH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterJ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterK" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CapitalLetterL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterM" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterO" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "CapitalLetterP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterQ" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CapitalLetterT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterU" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterW" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CapitalLetterX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterY" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftSquareBracket" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Backslash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightSquareBracket" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Caret" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Underscore" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: (((((C1 ('MetaCons "GraveAccent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterA" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallLetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SmallLetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallLetterF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterG" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "SmallLetterH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallLetterJ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterK" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SmallLetterL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterM" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallLetterN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterO" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "SmallLetterP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterQ" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallLetterR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SmallLetterT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterU" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallLetterV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterW" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "SmallLetterX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterY" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallLetterZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftCurlyBracket" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "VerticalLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightCurlyBracket" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Tilde" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Delete" 'PrefixI 'False) (U1 :: Type -> Type))))))))

Unicode

type UnicodeChar = Char Source #

A character in the full range of Unicode

ASCII Char is a subset of this type. Convert using charToUnicode and unicodeToCharMaybe.

Case-insensitive

See also: ASCII.Caseless

data CaselessChar #

A character in the ASCII character set, without an upper/lower case distinction for letters

Instances

Instances details
FromChar CaselessChar 
Instance details

Defined in ASCII.Superset

ToCaselessChar CaselessChar

CaselessChar is trivially convertible to itself.

Instance details

Defined in ASCII.Superset

Data CaselessChar

The Data instance allows caseless ASCII characters to be used with generic programming in the “SYB” style. (See the syb package and the 2003 paper Scrap Your Boilerplate by Ralf Lämmel and Simon Peyton Jones.)

Instance details

Defined in ASCII.Caseless

Methods

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

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

toConstr :: CaselessChar -> Constr #

dataTypeOf :: CaselessChar -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded CaselessChar

You can write ([minBound .. maxBound] :: [CaselessChar]) to get a list of all the caseless ASCII characters.

Instance details

Defined in ASCII.Caseless

Enum CaselessChar

The Enum instance allows us to use range syntax, for example [LetterA .. LetterZ] is a list all letters from a to z.

Instance details

Defined in ASCII.Caseless

Generic CaselessChar 
Instance details

Defined in ASCII.Caseless

Associated Types

type Rep CaselessChar :: Type -> Type #

Show CaselessChar

show produces the name of a constructor. For example, the character e is shown as “LetterE”. See ASCII.Caseless for the complete list of constructor names.

Instance details

Defined in ASCII.Caseless

Eq CaselessChar

ASCII characters can be compared for equality using (==).

Instance details

Defined in ASCII.Caseless

Ord CaselessChar

Caseless ASCII characters are ordered; for example, the letter A is "less than" (<) the letter B because it appears earlier in the list. The ordering of caseless ASCII characters is roughly the same as the ordering of the corresponding Unicode Chars, with caseless letters appearing in the place of case-sensitive capital letters.

Instance details

Defined in ASCII.Caseless

Hashable CaselessChar

The Hashable instance lets us collect caseless ASCII characters in hash-based sets, and it lets us use caseless ASCII characters as keys in hash-based maps. (See the unordered-containers package.)

Instance details

Defined in ASCII.Caseless

type Rep CaselessChar

The Generic instance allows caseless ASCII characters to be used with generic programming in the “generic deriving” style. (See the generic-data package and the 2010 paper A generic deriving mechanism for Haskell by José Pedro Magalhães, Atze Dijkstra, Johan Jeuring, and Andres Löh.)

Instance details

Defined in ASCII.Caseless

type Rep CaselessChar = D1 ('MetaData "CaselessChar" "ASCII.Caseless" "ascii-caseless-0.0.0.0-Jq67qosUQtb5xooXL2rV2R" 'False) ((((((C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StartOfHeading" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StartOfText" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "EndOfText" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EndOfTransmission" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Enquiry" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Acknowledgement" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Bell" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Backspace" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "HorizontalTab" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LineFeed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerticalTab" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "FormFeed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CarriageReturn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ShiftOut" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ShiftIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataLinkEscape" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeviceControl1" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DeviceControl2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DeviceControl3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeviceControl4" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NegativeAcknowledgement" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SynchronousIdle" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EndOfTransmissionBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cancel" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "EndOfMedium" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Substitute" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Escape" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "FileSeparator" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GroupSeparator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecordSeparator" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "UnitSeparator" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Space" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExclamationMark" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QuotationMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NumberSign" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DollarSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PercentSign" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Ampersand" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Apostrophe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftParenthesis" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "RightParenthesis" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Asterisk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlusSign" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Comma" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HyphenMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullStop" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Slash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Digit1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit2" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Digit3" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit5" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Digit6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit8" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Digit9" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Colon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Semicolon" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LessThanSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EqualsSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GreaterThanSign" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "QuestionMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AtSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterA" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterD" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LetterE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterF" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterG" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LetterH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LetterJ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterK" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "LetterL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterN" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LetterO" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterQ" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LetterR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LetterU" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterV" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LetterW" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterX" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "LetterY" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftSquareBracket" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Backslash" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RightSquareBracket" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Caret" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Underscore" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GraveAccent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftCurlyBracket" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "VerticalLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightCurlyBracket" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Tilde" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Delete" 'PrefixI 'False) (U1 :: Type -> Type))))))))

Character classifications

Print/control groups

ASCII characters are broadly categorized into two groups: control codes and printable characters.

See also: ASCII.Group

data Group #

Constructors

Control

33 of the ASCII characters are control codes. A few of these are still in use, but most are obsolete relics of the early days of computing.

Printable

95 of the ASCII characters are printable characters such as letters and numbers, mostly corresponding to the keys on an American English keyboard.

Instances

Instances details
Data Group 
Instance details

Defined in ASCII.Group

Methods

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

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

toConstr :: Group -> Constr #

dataTypeOf :: Group -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Group 
Instance details

Defined in ASCII.Group

Enum Group 
Instance details

Defined in ASCII.Group

Generic Group 
Instance details

Defined in ASCII.Group

Associated Types

type Rep Group :: Type -> Type #

Methods

from :: Group -> Rep Group x #

to :: Rep Group x -> Group #

Show Group 
Instance details

Defined in ASCII.Group

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

Eq Group 
Instance details

Defined in ASCII.Group

Methods

(==) :: Group -> Group -> Bool #

(/=) :: Group -> Group -> Bool #

Ord Group 
Instance details

Defined in ASCII.Group

Methods

compare :: Group -> Group -> Ordering #

(<) :: Group -> Group -> Bool #

(<=) :: Group -> Group -> Bool #

(>) :: Group -> Group -> Bool #

(>=) :: Group -> Group -> Bool #

max :: Group -> Group -> Group #

min :: Group -> Group -> Group #

Hashable Group 
Instance details

Defined in ASCII.Group

Methods

hashWithSalt :: Int -> Group -> Int #

hash :: Group -> Int #

type Rep Group 
Instance details

Defined in ASCII.Group

type Rep Group = D1 ('MetaData "Group" "ASCII.Group" "ascii-group-1.0.0.15-6EfWL0KTxx86fPEHPEfri8" 'False) (C1 ('MetaCons "Control" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Printable" 'PrefixI 'False) (U1 :: Type -> Type))

charGroup :: CharIso char => char -> Group Source #

Determine which group a particular character belongs to

charGroup CapitalLetterA == Printable

charGroup EndOfTransmission == Control

inGroup :: CharSuperset char => Group -> char -> Bool Source #

Test whether a character belongs to a particular ASCII group

not (inGroup Printable EndOfTransmission)

inGroup Control EndOfTransmission

map (inGroup Printable) ([-1, 5, 65, 97, 127, 130] :: [Int])
    == [False, False, True, True, False, False]

Upper/lower case

Case is a property of letters. A-Z are upper case letters, and a-z are lower case letters. No other ASCII characters have case.

See also: ASCII.Case

data Case #

Constructors

UpperCase

The letters from CapitalLetterA to CapitalLetterZ.

LowerCase

The letters from SmallLetterA to SmallLetterZ.

Instances

Instances details
Data Case 
Instance details

Defined in ASCII.Case

Methods

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

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

toConstr :: Case -> Constr #

dataTypeOf :: Case -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Case 
Instance details

Defined in ASCII.Case

Enum Case 
Instance details

Defined in ASCII.Case

Methods

succ :: Case -> Case #

pred :: Case -> Case #

toEnum :: Int -> Case #

fromEnum :: Case -> Int #

enumFrom :: Case -> [Case] #

enumFromThen :: Case -> Case -> [Case] #

enumFromTo :: Case -> Case -> [Case] #

enumFromThenTo :: Case -> Case -> Case -> [Case] #

Generic Case 
Instance details

Defined in ASCII.Case

Associated Types

type Rep Case :: Type -> Type #

Methods

from :: Case -> Rep Case x #

to :: Rep Case x -> Case #

Show Case 
Instance details

Defined in ASCII.Case

Methods

showsPrec :: Int -> Case -> ShowS #

show :: Case -> String #

showList :: [Case] -> ShowS #

Eq Case 
Instance details

Defined in ASCII.Case

Methods

(==) :: Case -> Case -> Bool #

(/=) :: Case -> Case -> Bool #

Ord Case 
Instance details

Defined in ASCII.Case

Methods

compare :: Case -> Case -> Ordering #

(<) :: Case -> Case -> Bool #

(<=) :: Case -> Case -> Bool #

(>) :: Case -> Case -> Bool #

(>=) :: Case -> Case -> Bool #

max :: Case -> Case -> Case #

min :: Case -> Case -> Case #

Hashable Case 
Instance details

Defined in ASCII.Case

Methods

hashWithSalt :: Int -> Case -> Int #

hash :: Case -> Int #

type Rep Case 
Instance details

Defined in ASCII.Case

type Rep Case = D1 ('MetaData "Case" "ASCII.Case" "ascii-case-1.0.1.2-APWqY3lVZYhBCvJZhxx0DP" 'False) (C1 ('MetaCons "UpperCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LowerCase" 'PrefixI 'False) (U1 :: Type -> Type))

letterCase :: CharSuperset char => char -> Maybe Case Source #

Determines whether a character is an ASCII letter, and if so, whether it is upper or lower case

map letterCase [SmallLetterA, CapitalLetterA, ExclamationMark]
    == [Just LowerCase, Just UpperCase, Nothing]

map letterCase ([string|Hey!|] :: [ASCII Word8])
    == [Just UpperCase, Just LowerCase, Just LowerCase, Nothing]

isCase :: CharSuperset char => Case -> char -> Bool Source #

Determines whether a character is an ASCII letter of a particular case

map (isCase UpperCase) [SmallLetterA, CapitalLetterA, ExclamationMark]
    == [False, True, False]

map (isCase UpperCase) ([string|Hey!|] :: [ASCII Word8])
    == [True, False, False, False]

map (isCase UpperCase) ([-1, 65, 97, 150] :: [Int])
    == [False, True, False, False]

toCaseChar :: CharSuperset char => Case -> char -> char Source #

Maps a letter character to its upper/lower case equivalent

toCaseChar UpperCase SmallLetterA == CapitalLetterA

(                     [char|a|] :: ASCII Word8) == asciiUnsafe 97
(toCaseChar UpperCase [char|a|] :: ASCII Word8) == asciiUnsafe 65

toCaseString :: StringSuperset string => Case -> string -> string Source #

Maps each of the characters in a string to its upper/lower case equivalent

toCaseString UpperCase [CapitalLetterH, SmallLetterE, SmallLetterY, ExclamationMark]
    == [CapitalLetterH, CapitalLetterE, CapitalLetterY, ExclamationMark]

(toCaseString UpperCase [string|Hey!|] :: ASCII Text) == asciiUnsafe "HEY!"

disregardCase :: Char -> CaselessChar Source #

Convert from ASCII character to caseless ASCII character, discarding the case if the character is a letter

refineCharToCase :: forall (letterCase :: Case) char. (KnownCase letterCase, CharSuperset char) => ASCII char -> ASCII'case letterCase char #

Given an ASCII superset character that is known to be valid ASCII, refine it further by converting it to a particular letter case

refineStringToCase :: forall (letterCase :: Case) char. (KnownCase letterCase, StringSuperset char) => ASCII char -> ASCII'case letterCase char #

Given an ASCII superset string that is known to be valid ASCII, refine it further by converting it to a particular letter case

Letters

isLetter :: CharSuperset char => char -> Bool Source #

Returns True for ASCII letters:

Letters and numbers

isAlphaNum :: CharSuperset char => char -> Bool Source #

Returns True if the character is either an ASCII letter (isLetter) or an ASCII digit (isDigit).

Decimal digits

See also: ASCII.Decimal

isDigit :: CharSuperset char => char -> Bool Source #

Returns True for the characters from Digit0 to Digit9.

data Digit #

The subset of ASCII used to represent unsigned decimal numbers:

Instances

Instances details
DigitSuperset Digit 
Instance details

Defined in ASCII.Decimal

Data Digit 
Instance details

Defined in ASCII.Decimal

Methods

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

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

toConstr :: Digit -> Constr #

dataTypeOf :: Digit -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Digit 
Instance details

Defined in ASCII.Decimal

Enum Digit 
Instance details

Defined in ASCII.Decimal

Generic Digit 
Instance details

Defined in ASCII.Decimal

Associated Types

type Rep Digit :: Type -> Type #

Methods

from :: Digit -> Rep Digit x #

to :: Rep Digit x -> Digit #

Show Digit 
Instance details

Defined in ASCII.Decimal

Methods

showsPrec :: Int -> Digit -> ShowS #

show :: Digit -> String #

showList :: [Digit] -> ShowS #

Eq Digit 
Instance details

Defined in ASCII.Decimal

Methods

(==) :: Digit -> Digit -> Bool #

(/=) :: Digit -> Digit -> Bool #

Ord Digit 
Instance details

Defined in ASCII.Decimal

Methods

compare :: Digit -> Digit -> Ordering #

(<) :: Digit -> Digit -> Bool #

(<=) :: Digit -> Digit -> Bool #

(>) :: Digit -> Digit -> Bool #

(>=) :: Digit -> Digit -> Bool #

max :: Digit -> Digit -> Digit #

min :: Digit -> Digit -> Digit #

Hashable Digit 
Instance details

Defined in ASCII.Decimal

Methods

hashWithSalt :: Int -> Digit -> Int #

hash :: Digit -> Int #

DigitStringSuperset [Digit] 
Instance details

Defined in ASCII.Decimal

type Rep Digit 
Instance details

Defined in ASCII.Decimal

type Rep Digit = D1 ('MetaData "Digit" "ASCII.Decimal" "ascii-numbers-1.2.0.0-EgPb9BKveBi2bByYv4gh7X" 'False) (((C1 ('MetaCons "Digit0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Digit2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit4" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Digit5" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit6" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Digit7" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit9" 'PrefixI 'False) (U1 :: Type -> Type)))))

Hexadecimal digits

isHexDigit :: CharSuperset char => char -> Bool Source #

Returns True for characters in any of the following ranges:

data HexChar #

The subset of ASCII used to represent hexadecimal numbers:

Instances

Instances details
HexCharSuperset HexChar 
Instance details

Defined in ASCII.Hexadecimal

Data HexChar 
Instance details

Defined in ASCII.Hexadecimal

Methods

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

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

toConstr :: HexChar -> Constr #

dataTypeOf :: HexChar -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded HexChar 
Instance details

Defined in ASCII.Hexadecimal

Enum HexChar 
Instance details

Defined in ASCII.Hexadecimal

Generic HexChar 
Instance details

Defined in ASCII.Hexadecimal

Associated Types

type Rep HexChar :: Type -> Type #

Methods

from :: HexChar -> Rep HexChar x #

to :: Rep HexChar x -> HexChar #

Show HexChar 
Instance details

Defined in ASCII.Hexadecimal

Eq HexChar 
Instance details

Defined in ASCII.Hexadecimal

Methods

(==) :: HexChar -> HexChar -> Bool #

(/=) :: HexChar -> HexChar -> Bool #

Ord HexChar 
Instance details

Defined in ASCII.Hexadecimal

Hashable HexChar 
Instance details

Defined in ASCII.Hexadecimal

Methods

hashWithSalt :: Int -> HexChar -> Int #

hash :: HexChar -> Int #

HexStringSuperset [HexChar] 
Instance details

Defined in ASCII.Hexadecimal

type Rep HexChar 
Instance details

Defined in ASCII.Hexadecimal

type Rep HexChar = D1 ('MetaData "HexChar" "ASCII.Hexadecimal" "ascii-numbers-1.2.0.0-EgPb9BKveBi2bByYv4gh7X" 'False) ((((C1 ('MetaCons "Digit0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Digit2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit4" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Digit5" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit6" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit7" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Digit8" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterA" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CapitalLetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CapitalLetterE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SmallLetterA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SmallLetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SmallLetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SmallLetterE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterF" 'PrefixI 'False) (U1 :: Type -> Type))))))

Octal digits

isOctDigit :: CharSuperset char => char -> Bool Source #

Returns True for the characters from Digit0 to Digit7.

Spaces and symbols

isSpace :: CharSuperset char => char -> Bool Source #

Returns True for the following characters:

isVisible :: CharSuperset char => char -> Bool Source #

Returns True for visible characters

This includes all print characters except Space.

Monomorphic character conversions

These are a few simple monomorphic functions to convert between ASCII and types representing some other character set.

This is not intended to be an exhaustive list of all possible conversions. For more options, see ASCII.Superset.

ASCII.CharInt

These functions convert between the ASCII Char type and Int.

charToInt :: Char -> Int Source #

map charToInt [Null, CapitalLetterA, SmallLetterA, Delete] == [0, 65, 97, 127]

ASCII.CharWord8

These functions convert between the ASCII Char type and Word8.

charToWord8 :: Char -> Word8 Source #

map charToWord8 [Null, CapitalLetterA, SmallLetterA, Delete] == [0, 65, 97, 127]

ASCII.CharUnicodeChar

These functions convert between the ASCII Char type and the UnicodeChar type.

Monomorphic digit conversions

DigitWord8

These functions convert between the ASCII Digit type and ASCII digits in their byte encoding.

These conversions do not correspond to the numeric interpretations of Digit and Word8. For example, digitToWord8 Digit0 is 48, not 0.

DigitASCII.Char

These functions convert between the ASCII Digit type and the ASCII Char type.

DigitUnicodeChar

These functions convert between the ASCII Digit type and the UnicodeChar type.

HexCharWord8

These functions convert between the ASCII HexChar type and ASCII characters in their byte encoding.

These conversions do not correspond to the numeric interpretations of HexChar and Word8. For example, hexCharToWord8 CapitalLetterA is 65, not 10.

HexCharASCII.Char

These functions convert between the ASCII HexChar type and the ASCII Char type.

HexCharUnicodeChar

These functions convert between the ASCII HexChar type and the UnicodeChar type.

Monomorphic string conversions

ASCII.CharString

These functions convert between [Char] (a list of ASCII characters) and String (a list of Unicode characters).

ASCII.CharText

These functions convert between [Char] and Text.

charListToText :: [Char] -> Text Source #

charListToText [CapitalLetterH, SmallLetterI, ExclamationMark] == "Hi!"

ASCII.CharByteString

These functions convert between [Char] and ByteString.

ASCII ByteString -> Text

Monomorphic conversions between ASCII supersets

These functions are all specializations of convertStringMaybe. They convert a string from one ASCII-superset type to another.

ASCII.byteListToUnicodeStringMaybe [0x48, 0x54, 0x54, 0x50] == Just HTTP

If any of the characters in the input is outside the ASCII character set, the result is Nothing.

ASCII.byteListToUnicodeStringMaybe [0x48, 0x54, 0x54, 0x80] == Nothing

ByteStringString

[Word8]String

Monomorphic numeric string conversions

Natural[Digit]

Natural[HexChar]

Refinement types

data ASCII superset #

This type constructor indicates that a value from some ASCII superset is valid ASCII

The type parameter is the ASCII superset, which should be a type with an instance of either CharSuperset or StringSuperset.

For example, whereas a Text value may contain a combination of ASCII and non-ASCII characters, a value of type ASCII Text may contain only ASCII characters.

Instances

Instances details
DigitStringSuperset char => DigitStringSuperset (ASCII char) 
Instance details

Defined in ASCII.Decimal

DigitSuperset char => DigitSuperset (ASCII char) 
Instance details

Defined in ASCII.Decimal

Methods

fromDigit :: Digit -> ASCII char #

isDigit :: ASCII char -> Bool #

toDigitUnsafe :: ASCII char -> Digit #

toDigitMaybe :: ASCII char -> Maybe Digit #

HexCharSuperset char => HexCharSuperset (ASCII char) 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset char => HexStringSuperset (ASCII char) 
Instance details

Defined in ASCII.Hexadecimal

CharSuperset char => CharIso (ASCII char) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

toChar :: ASCII char -> Char #

StringSuperset string => StringIso (ASCII string) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

toCharList :: ASCII string -> [Char] #

mapChars :: (Char -> Char) -> ASCII string -> ASCII string #

CharSuperset char => CharSuperset (ASCII char) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

toCaseChar :: Case -> ASCII char -> ASCII char #

CharSuperset char => FromChar (ASCII char) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

fromChar :: Char -> ASCII char #

FromString string => FromString (ASCII string) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

fromCharList :: [Char] -> ASCII string #

StringSuperset string => StringSuperset (ASCII string) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

substituteString :: ASCII string -> ASCII string #

mapCharsUnsafe :: (Char -> Char) -> ASCII string -> ASCII string #

toCaseString :: Case -> ASCII string -> ASCII string #

ToCaselessChar char => ToCaselessChar (ASCII char) 
Instance details

Defined in ASCII.Refinement.Internal

ToCaselessString string => ToCaselessString (ASCII string) 
Instance details

Defined in ASCII.Refinement.Internal

CharSuperset char => ToChar (ASCII char) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

isAsciiChar :: ASCII char -> Bool #

toCharUnsafe :: ASCII char -> Char #

ToString string => ToString (ASCII string) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

isAsciiString :: ASCII string -> Bool #

toCharListUnsafe :: ASCII string -> [Char] #

toCharListSub :: ASCII string -> [Char] #

ToText (ASCII ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII Text) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII Text) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII [Char]) 
Instance details

Defined in ASCII.Superset.Text

Data superset => Data (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

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

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

toConstr :: ASCII superset -> Constr #

dataTypeOf :: ASCII superset -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid superset => Monoid (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

mempty :: ASCII superset #

mappend :: ASCII superset -> ASCII superset -> ASCII superset #

mconcat :: [ASCII superset] -> ASCII superset #

Semigroup superset => Semigroup (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

(<>) :: ASCII superset -> ASCII superset -> ASCII superset #

sconcat :: NonEmpty (ASCII superset) -> ASCII superset #

stimes :: Integral b => b -> ASCII superset -> ASCII superset #

Generic (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Associated Types

type Rep (ASCII superset) :: Type -> Type #

Methods

from :: ASCII superset -> Rep (ASCII superset) x #

to :: Rep (ASCII superset) x -> ASCII superset #

Show superset => Show (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

showsPrec :: Int -> ASCII superset -> ShowS #

show :: ASCII superset -> String #

showList :: [ASCII superset] -> ShowS #

Eq superset => Eq (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

(==) :: ASCII superset -> ASCII superset -> Bool #

(/=) :: ASCII superset -> ASCII superset -> Bool #

Ord superset => Ord (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

compare :: ASCII superset -> ASCII superset -> Ordering #

(<) :: ASCII superset -> ASCII superset -> Bool #

(<=) :: ASCII superset -> ASCII superset -> Bool #

(>) :: ASCII superset -> ASCII superset -> Bool #

(>=) :: ASCII superset -> ASCII superset -> Bool #

max :: ASCII superset -> ASCII superset -> ASCII superset #

min :: ASCII superset -> ASCII superset -> ASCII superset #

Hashable superset => Hashable (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

hashWithSalt :: Int -> ASCII superset -> Int #

hash :: ASCII superset -> Int #

type Rep (ASCII superset) 
Instance details

Defined in ASCII.Refinement.Internal

type Rep (ASCII superset) = D1 ('MetaData "ASCII" "ASCII.Refinement.Internal" "ascii-superset-1.3.0.0-JHm4MzW2iKu8X5vcFtH7vf" 'True) (C1 ('MetaCons "ASCII_Unsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "lift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 superset)))

data ASCII'case (letterCase :: Case) superset #

Indicates that a value from some ASCII superset is valid ASCII, and also that any letters belong to a particular Case indicated by the letterCase type parameter

The superset type parameter is the ASCII superset, which should be a type with an instance of either CharSuperset or StringSuperset.

For example, whereas a Text value may contain a combination of ASCII and non-ASCII characters, a value of type ASCII'case 'UpperCase Text may contain only uppercase ASCII letters and ASCII non-letters.

Instances

Instances details
(FromChar superset, KnownCase letterCase) => ToCasefulChar letterCase (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

toCasefulChar :: CaselessChar -> ASCII'case letterCase superset #

(FromString superset, KnownCase letterCase) => ToCasefulString letterCase (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

toCasefulString :: [CaselessChar] -> ASCII'case letterCase superset #

ToCaselessChar char => ToCaselessChar (ASCII'case letterCase char) 
Instance details

Defined in ASCII.CaseRefinement

Methods

isAsciiCaselessChar :: ASCII'case letterCase char -> Bool #

toCaselessCharUnsafe :: ASCII'case letterCase char -> CaselessChar #

ToCaselessString string => ToCaselessString (ASCII'case letterCase string) 
Instance details

Defined in ASCII.CaseRefinement

Methods

isAsciiCaselessString :: ASCII'case letterCase string -> Bool #

toCaselessCharListUnsafe :: ASCII'case letterCase string -> [CaselessChar] #

toCaselessCharListSub :: ASCII'case letterCase string -> [CaselessChar] #

CharSuperset char => ToChar (ASCII'case letterCase char) 
Instance details

Defined in ASCII.CaseRefinement

Methods

isAsciiChar :: ASCII'case letterCase char -> Bool #

toCharUnsafe :: ASCII'case letterCase char -> Char #

ToString string => ToString (ASCII'case letterCase string) 
Instance details

Defined in ASCII.CaseRefinement

Methods

isAsciiString :: ASCII'case letterCase string -> Bool #

toCharListUnsafe :: ASCII'case letterCase string -> [Char] #

toCharListSub :: ASCII'case letterCase string -> [Char] #

ToText (ASCII'case letterCase ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII'case letterCase ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII'case letterCase Text) 
Instance details

Defined in ASCII.Superset.Text

Methods

toStrictText :: ASCII'case letterCase Text -> Text #

toLazyText :: ASCII'case letterCase Text -> Text0 #

toUnicodeCharList :: ASCII'case letterCase Text -> [Char] #

ToText (ASCII'case letterCase Text) 
Instance details

Defined in ASCII.Superset.Text

Methods

toStrictText :: ASCII'case letterCase Text -> Text0 #

toLazyText :: ASCII'case letterCase Text -> Text #

toUnicodeCharList :: ASCII'case letterCase Text -> [Char] #

ToText (ASCII'case letterCase [Char]) 
Instance details

Defined in ASCII.Superset.Text

Methods

toStrictText :: ASCII'case letterCase [Char] -> Text #

toLazyText :: ASCII'case letterCase [Char] -> Text #

toUnicodeCharList :: ASCII'case letterCase [Char] -> [Char] #

(Data superset, Typeable letterCase) => Data (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ASCII'case letterCase superset -> c (ASCII'case letterCase superset) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ASCII'case letterCase superset) #

toConstr :: ASCII'case letterCase superset -> Constr #

dataTypeOf :: ASCII'case letterCase superset -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ASCII'case letterCase superset)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ASCII'case letterCase superset)) #

gmapT :: (forall b. Data b => b -> b) -> ASCII'case letterCase superset -> ASCII'case letterCase superset #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ASCII'case letterCase superset -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ASCII'case letterCase superset -> r #

gmapQ :: (forall d. Data d => d -> u) -> ASCII'case letterCase superset -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ASCII'case letterCase superset -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ASCII'case letterCase superset -> m (ASCII'case letterCase superset) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ASCII'case letterCase superset -> m (ASCII'case letterCase superset) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ASCII'case letterCase superset -> m (ASCII'case letterCase superset) #

Monoid superset => Monoid (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

mempty :: ASCII'case letterCase superset #

mappend :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> ASCII'case letterCase superset #

mconcat :: [ASCII'case letterCase superset] -> ASCII'case letterCase superset #

Semigroup superset => Semigroup (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

(<>) :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> ASCII'case letterCase superset #

sconcat :: NonEmpty (ASCII'case letterCase superset) -> ASCII'case letterCase superset #

stimes :: Integral b => b -> ASCII'case letterCase superset -> ASCII'case letterCase superset #

Generic (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Associated Types

type Rep (ASCII'case letterCase superset) :: Type -> Type #

Methods

from :: ASCII'case letterCase superset -> Rep (ASCII'case letterCase superset) x #

to :: Rep (ASCII'case letterCase superset) x -> ASCII'case letterCase superset #

Show superset => Show (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

showsPrec :: Int -> ASCII'case letterCase superset -> ShowS #

show :: ASCII'case letterCase superset -> String #

showList :: [ASCII'case letterCase superset] -> ShowS #

Eq superset => Eq (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

(==) :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> Bool #

(/=) :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> Bool #

Ord superset => Ord (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

compare :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> Ordering #

(<) :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> Bool #

(<=) :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> Bool #

(>) :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> Bool #

(>=) :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> Bool #

max :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> ASCII'case letterCase superset #

min :: ASCII'case letterCase superset -> ASCII'case letterCase superset -> ASCII'case letterCase superset #

Hashable superset => Hashable (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

Methods

hashWithSalt :: Int -> ASCII'case letterCase superset -> Int #

hash :: ASCII'case letterCase superset -> Int #

type Rep (ASCII'case letterCase superset) 
Instance details

Defined in ASCII.CaseRefinement

type Rep (ASCII'case letterCase superset) = D1 ('MetaData "ASCII'case" "ASCII.CaseRefinement" "ascii-superset-1.3.0.0-JHm4MzW2iKu8X5vcFtH7vf" 'True) (C1 ('MetaCons "ASCII'case_Unsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "lift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 superset)))

type ASCII'upper superset = ASCII'case 'UpperCase superset #

type ASCII'lower superset = ASCII'case 'LowerCase superset #

class KnownCase (letterCase :: Case) where #

Methods

theCase :: Case #

Instances

Instances details
KnownCase 'LowerCase 
Instance details

Defined in ASCII.CaseRefinement

Methods

theCase :: Case #

KnownCase 'UpperCase 
Instance details

Defined in ASCII.CaseRefinement

Methods

theCase :: Case #

Polymorphic conversions

Narrowing

toCharMaybe :: ToChar char => char -> Maybe Char #

toCharListMaybe :: ToString string => string -> Maybe [Char] #

Validate

validateChar :: CharSuperset superset => superset -> Maybe (ASCII superset) #

(map validateChar [-1, 65, 97, 128] :: [Maybe (ASCII Int)])
    == [Nothing, Just (asciiUnsafe 65), Just (asciiUnsafe 97), Nothing]

validateString :: StringSuperset superset => superset -> Maybe (ASCII superset) #

(map validateString ["Hello", "Cristóbal"] :: [Maybe (ASCII Text)])
    == [Just (asciiUnsafe "Hello"), Nothing]

(map validateString ["Hello", "Cristóbal"] :: [Maybe (ASCII String)])
    == [Just (asciiUnsafe "Hello"), Nothing]

Widening

See also: ASCII.Refinement

lift :: ASCII superset -> superset #

toStrictText :: ToText a => a -> Text #

toLazyText :: ToText a => a -> Text #

See also: ASCII.Superset

fromChar :: FromChar char => Char -> char #

Conversion from Char

fromCharList :: FromString string => [Char] -> string #

Conversion from [Char]

See also: ASCII.Decimal

fromDigit :: DigitSuperset char => Digit -> char #

fromDigitList :: DigitStringSuperset string => [Digit] -> string #

fromHexCharList :: HexStringSuperset string => [HexChar] -> string #

forgetCase :: forall (letterCase :: Case) superset. ASCII'case letterCase superset -> ASCII superset #

Convert

These functions all convert from one ASCII-superset type to another, failing if any of the characters in the input is outside the ASCII character set.

convertCharMaybe :: (CharSuperset char1, CharSuperset char2) => char1 -> Maybe char2 Source #

convertCharOrFail :: (CharSuperset char1, CharSuperset char2, MonadFail context) => char1 -> context char2 Source #

convertStringMaybe :: (StringSuperset string1, StringSuperset string2) => string1 -> Maybe string2 Source #

convertStringOrFail :: (StringSuperset string1, StringSuperset string2, MonadFail context) => string1 -> context string2 Source #

convertRefinedString :: StringSupersetConversion a b => ASCII a -> ASCII b Source #

For example, this function can convert ASCII ByteString to ASCII Text and vice versa

Integral strings

showIntegralDecimal :: (Integral n, StringSuperset string) => n -> string Source #

Gives the ASCII string representation of an integer in decimal (base 10) notation, using digits Digit0 through Digit9, leading with HyphenMinus for negative numbers

For example, showIntegralDecimal (-512 :: Integer) = "-512".

showIntegralHexadecimal :: (Integral n, StringSuperset string) => Case -> n -> string Source #

Gives the ASCII string representation of an integer in hexadecimal (base 16) notation

The characters Digit0 through Digit9 represent digits 0 though 9. The representation of digits 10 to 15 is determined by the value of Case parameter: UpperCase means CapitalLetterA to CapitalLetterF, and LowerCase means SmallLetterA to SmallLetterF. For negative numbers, the resulting string begins with HyphenMinus.

showIntegralHexadecimal UpperCase (negate (256 + 12) :: Integer) == "-10C"

readIntegralDecimal :: (StringSuperset string, Integral number, Bits number) => string -> Maybe number Source #

Roughly the inverse of showIntegralDecimal

  • Leading zeroes are accepted, as in "0074" and "-0074"

Conditions where the result is Nothing:

  • If the input is empty
  • If the input contains any other extraneous characters
  • If the resulting number would be outside the range supported by the Integral (determined by its Bits instance)

readIntegralHexadecimal :: (StringSuperset string, Integral number, Bits number) => string -> Maybe number Source #

Roughly the inverse of showIntegralHexadecimal

  • Upper and lower case letters are treated equally
  • Leading zeroes are accepted, as in "006a" and "-006a"

Conditions where the result is Nothing:

  • If the input is empty
  • If the input contains any other extraneous characters
  • If the resulting number would be outside the range supported by the Integral (determined by its Bits instance)

Natural strings

showNaturalDecimal :: DigitStringSuperset string => Natural -> string Source #

Gives the ASCII string representation of an natural number in decimal (base 10) notation, using digits Digit0 through Digit9

showNaturalDecimal 512 == @"512"

showNaturalHexadecimal :: HexStringSuperset string => Case -> Natural -> string Source #

Gives the ASCII string representation of an integer in hexadecimal (base 16) notation

Characters Digit0 through Digit9 represent digits 0 though 9. The representation of digits 10 to 15 is determined by the value of Case parameter: UpperCase means CapitalLetterA to CapitalLetterF, and LowerCase means SmallLetterA to SmallLetterF.

showNaturalHexadecimal UpperCase (256 + 12) == "10C"

readNaturalDecimal :: DigitStringSuperset string => string -> Maybe Natural Source #

Roughly the inverse of showNaturalDecimal

  • Leading zeroes are accepted, as in "0074"

Conditions where the result is Nothing:

  • If the input is empty
  • If the input contains any other extraneous characters

readNaturalHexadecimal :: HexStringSuperset string => string -> Maybe Natural Source #

Roughly the inverse of showNaturalHexadecimal

  • Upper and lower case letters are treated equally
  • Leading zeroes are accepted, as in "006a"

Conditions where the result is Nothing:

  • If the input is empty
  • If the input contains any other extraneous characters

Single-digit strings

digitString :: DigitStringSuperset string => Digit -> string Source #

A string containing a single digit character 0-9

hexCharString :: HexStringSuperset string => HexChar -> string Source #

A string containing a single hexadecimal digit character 0-9, A-F, or a-f

Classes

Supersets of ASCII

class (ToChar char, FromChar char) => CharSuperset char #

Character type with:

  • a total conversion from ASCII; and
  • a partial conversion to ASCII

Minimal complete definition

toCaseChar

Instances

Instances details
CharSuperset Char

Char is trivially a superset of itself.

Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Char -> Char #

CharSuperset Word8 
Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Word8 -> Word8 #

CharSuperset Natural 
Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Natural -> Natural #

CharSuperset Char 
Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Char -> Char #

CharSuperset Int 
Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Int -> Int #

CharSuperset char => CharSuperset (ASCII char) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

toCaseChar :: Case -> ASCII char -> ASCII char #

class (ToString string, FromString string) => StringSuperset string #

String type with:

  • a total conversion from ASCII; and
  • a partial conversion to ASCII

Minimal complete definition

substituteString, toCaseString

Instances

Instances details
StringSuperset Builder 
Instance details

Defined in ASCII.Superset

StringSuperset ByteString 
Instance details

Defined in ASCII.Superset

StringSuperset ByteString 
Instance details

Defined in ASCII.Superset

StringSuperset Text 
Instance details

Defined in ASCII.Superset

StringSuperset Builder 
Instance details

Defined in ASCII.Superset

StringSuperset Text 
Instance details

Defined in ASCII.Superset

StringSuperset string => StringSuperset (ASCII string) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

substituteString :: ASCII string -> ASCII string #

mapCharsUnsafe :: (Char -> Char) -> ASCII string -> ASCII string #

toCaseString :: Case -> ASCII string -> ASCII string #

CharSuperset char => StringSuperset [char] 
Instance details

Defined in ASCII.Superset

Methods

substituteString :: [char] -> [char] #

mapCharsUnsafe :: (Char -> Char) -> [char] -> [char] #

toCaseString :: Case -> [char] -> [char] #

class (StringSuperset a, StringSuperset b) => StringSupersetConversion a b #

Minimal complete definition

convertStringUnsafe

Instances

Instances details
StringSupersetConversion ByteString ByteString 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion ByteString Text 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion ByteString ByteString 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion ByteString Text 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion Text ByteString 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion Text Text 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion Text ByteString 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion Text Text 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion ByteString [Char] 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion ByteString [Char] 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion Text [Char] 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion Text [Char] 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion [Char] ByteString 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion [Char] ByteString 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion [Char] Text 
Instance details

Defined in ASCII.SupersetConversion

StringSupersetConversion [Char] Text 
Instance details

Defined in ASCII.SupersetConversion

class ToText a #

Minimal complete definition

toStrictText | toLazyText

Instances

Instances details
ToText Text 
Instance details

Defined in ASCII.Superset.Text

ToText Text 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII Text) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII Text) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII [Char]) 
Instance details

Defined in ASCII.Superset.Text

ToText [Char] 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII'case letterCase ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII'case letterCase ByteString) 
Instance details

Defined in ASCII.Superset.Text

ToText (ASCII'case letterCase Text) 
Instance details

Defined in ASCII.Superset.Text

Methods

toStrictText :: ASCII'case letterCase Text -> Text #

toLazyText :: ASCII'case letterCase Text -> Text0 #

toUnicodeCharList :: ASCII'case letterCase Text -> [Char] #

ToText (ASCII'case letterCase Text) 
Instance details

Defined in ASCII.Superset.Text

Methods

toStrictText :: ASCII'case letterCase Text -> Text0 #

toLazyText :: ASCII'case letterCase Text -> Text #

toUnicodeCharList :: ASCII'case letterCase Text -> [Char] #

ToText (ASCII'case letterCase [Char]) 
Instance details

Defined in ASCII.Superset.Text

Methods

toStrictText :: ASCII'case letterCase [Char] -> Text #

toLazyText :: ASCII'case letterCase [Char] -> Text #

toUnicodeCharList :: ASCII'case letterCase [Char] -> [Char] #

Equivalents to ASCII

class CharSuperset char => CharIso char #

Minimal complete definition

toChar

Instances

Instances details
CharIso Char

Char is trivially isomorphic to itself. (This instance is uninteresting.)

Instance details

Defined in ASCII.Isomorphism

Methods

toChar :: Char -> Char #

CharSuperset char => CharIso (ASCII char) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

toChar :: ASCII char -> Char #

class StringSuperset string => StringIso string #

Minimal complete definition

toCharList, mapChars

Instances

Instances details
StringSuperset string => StringIso (ASCII string) 
Instance details

Defined in ASCII.Refinement.Internal

Methods

toCharList :: ASCII string -> [Char] #

mapChars :: (Char -> Char) -> ASCII string -> ASCII string #

CharIso char => StringIso [char] 
Instance details

Defined in ASCII.Isomorphism

Methods

toCharList :: [char] -> [Char] #

mapChars :: (Char -> Char) -> [char] -> [char] #

Supersets of numeric characters

class DigitSuperset char #

Minimal complete definition

fromDigit, (isDigit, toDigitUnsafe | toDigitMaybe)

Instances

Instances details
DigitSuperset Char 
Instance details

Defined in ASCII.Decimal

DigitSuperset Digit 
Instance details

Defined in ASCII.Decimal

DigitSuperset Word8 
Instance details

Defined in ASCII.Decimal

DigitSuperset Char 
Instance details

Defined in ASCII.Decimal

DigitSuperset char => DigitSuperset (ASCII char) 
Instance details

Defined in ASCII.Decimal

Methods

fromDigit :: Digit -> ASCII char #

isDigit :: ASCII char -> Bool #

toDigitUnsafe :: ASCII char -> Digit #

toDigitMaybe :: ASCII char -> Maybe Digit #

class DigitStringSuperset string #

Instances

Instances details
DigitStringSuperset Builder 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset ByteString 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset ByteString 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset Text 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset Builder 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset Text 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset char => DigitStringSuperset (ASCII char) 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [Char] 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [Digit] 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [Char] 
Instance details

Defined in ASCII.Decimal

class HexStringSuperset string #

Instances

Instances details
HexStringSuperset Builder 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset ByteString 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset ByteString 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset Text 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset Builder 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset Text 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset char => HexStringSuperset (ASCII char) 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset [Char] 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset [HexChar] 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset [Char] 
Instance details

Defined in ASCII.Hexadecimal

Quasi-quoters

char :: QuasiQuoter #

An expression pattern corresponding to an ASCII character

In an expression context

The result will have a FromChar constraint.

The quasi-quoted string must consist of a single character that is within the ASCII character set.

[char|e|] == SmallLetterE

[char|e|] == (101 :: Word8)

Since this is polymorphic, a type signature is recommended.

In a pattern context

The pattern matches a value of a type satisfying the ToChar constraint.

let
    x = case Tilde of
          [char|@|] -> 1
          [char|~|] -> 2
          _ -> 3
in
    x == 2

string :: QuasiQuoter #

An expression or pattern corresponding to an ASCII string

In an expression context

The result will have a FromString constraint.

The quasi-quoted string must consist only of characters are within the ASCII character set.

[string|Hello!|] ==
    [CapitalLetterH,SmallLetterE,SmallLetterL,SmallLetterL,SmallLetterO,ExclamationMark]

[string|Hello!|] == ("Hello!" :: String)

[string|Hello!|] == ("Hello!" :: Text)

toLazyByteString [string|Hello!|] == "Hello!"

Since this is polymorphic, a type signature is recommended.

In a pattern context

The pattern matches a value of a type satisfying the ToString constraint.

let
    x = case [CapitalLetterH, SmallLetterI] of
          [string|Bye|] -> 1
          [string|Hi|] -> 2
          _ -> 3
in
    x == 2

caseless :: QuasiQuoter #

An expression or pattern corresponding to a case-insensitive ASCII string

In an expression context

A monomorphic expression of type [CaselessChar].

[caseless|Hello!|] ==
    [LetterH, LetterE, LetterL, LetterL, LetterO, ExclamationMark]

In a pattern context

A case-insensitive match of any type belonging to the ToCaselessString class.

let
    x = case "Hello!" :: Text of
          [caseless|Bye!|] -> 1
          [caseless|hEllo!|] -> 2
          _ -> 3
in
    x == 2

lower :: QuasiQuoter #

An expression or pattern corresponding to an ASCII string where all the letters are of lower case

The letters in the body of the quasi-quotation may be written in any case you like; they will be converted to lower case automatically.

In an expression context

The expression can become any type satisfying the (ToCasefulString 'LowerCase) constraint. Any letters in the quoted content will be converted to lower case.

[lower|Hello!|] == ("hello!" :: Text)

[lower|Hello!|] == ("hello!" :: ASCII'lower ByteString)

In a pattern context

The pattern matches a value of a type satisfying the ToString constraint. A value matches this pattern if:

  • All of the letters in the tested value are in lower case
  • The tested value satisfies a case-insensitive comparison with the quasi-quoted content
let
    x = case "hi!" :: Text of
          [lower|wow|] -> 1
          [lower|Hi!|] -> 2
          _ -> 3
in
    x == 2

upper :: QuasiQuoter #

An expression or pattern corresponding to an ASCII string where all the letters are of upper case

The letters in the body of the quasi-quotation may be written in any case you like; they will be converted to upper case automatically.

In an expression context

The expression can become any type satisfying the (ToCasefulString 'UpperCase) constraint. Any letters in the quoted content will be converted to upper case.

[upper|Hello!|] == ("HELLO!" :: Text)

[upper|Hello!|] == ("HELLO!" :: ASCII'upper ByteString)

In a pattern context

The pattern matches a value of a type satisfying the ToString constraint. A value matches this pattern if:

  • All of the letters in the tested value are in upper case
  • The tested value satisfies a case-insensitive comparison with the quasi-quoted content
let
    x = case "HI!" :: Text of
          [QQ.upper|wow|] -> 1
          [QQ.upper|Hi!|] -> 2
          _ -> 3
in
    x == 2