ascii-1.0.0.2: The ASCII character set and encoding
Safe HaskellNone
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 message headers.

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

See also: ASCII.Char

data Char #

Instances

Instances details
Bounded Char 
Instance details

Defined in ASCII.Char

Enum Char 
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] #

Eq Char 
Instance details

Defined in ASCII.Char

Methods

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

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

Data Char 
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 #

Ord Char 
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 #

Show Char 
Instance details

Defined in ASCII.Char

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

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 #

Hashable Char 
Instance details

Defined in ASCII.Char

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

CharIso Char 
Instance details

Defined in ASCII.Isomorphism

Methods

toChar :: Char -> Char

CharSuperset Char 
Instance details

Defined in ASCII.Superset

CharSuperset superset => Lift Char superset 
Instance details

Defined in ASCII.Lift

Methods

lift :: Char -> superset

StringSuperset superset => Lift [Char] superset 
Instance details

Defined in ASCII.Lift

Methods

lift :: [Char] -> superset

type Rep Char 
Instance details

Defined in ASCII.Char

type Rep Char = D1 ('MetaData "Char" "ASCII.Char" "ascii-char-1.0.0.4-inplace" '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))))))))

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
Bounded Group 
Instance details

Defined in ASCII.Group

Enum Group 
Instance details

Defined in ASCII.Group

Eq Group 
Instance details

Defined in ASCII.Group

Methods

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

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

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 #

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 #

Show Group 
Instance details

Defined in ASCII.Group

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

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 #

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.2-inplace" '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.

>>> map charGroup [CapitalLetterA,EndOfTransmission]
[Printable,Control]

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

Test whether a character belongs to a particular ASCII group.

>>> inGroup Printable EndOfTransmission
False
>>> inGroup Control EndOfTransmission
True
>>> 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
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] #

Eq Case 
Instance details

Defined in ASCII.Case

Methods

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

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

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 #

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 #

Show Case 
Instance details

Defined in ASCII.Case

Methods

showsPrec :: Int -> Case -> ShowS #

show :: Case -> String #

showList :: [Case] -> ShowS #

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 #

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.0.2-inplace" '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 :: CharIso char => Case -> char -> char Source #

Maps a letter character to its upper/lower case equivalent.

>>> toCaseChar UpperCase SmallLetterA
CapitalLetterA
>>> ([char|a|] :: ASCII Word8, toCaseChar UpperCase [char|a|] :: ASCII Word8)
(asciiUnsafe 97,asciiUnsafe 65)

toCaseString :: StringIso 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!"

Monomorphic 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.

Int

These functions convert between the ASCII Char type and Int.

charToInt :: Char -> Int Source #

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

Word8

These functions convert between the ASCII Char type and Word8.

charToWord8 :: Char -> Word8 Source #

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

Char

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

String

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

Text

These functions convert between [Char] and Text.

charListToText :: [Char] -> Text Source #

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

ByteString

These functions convert between [Char] and ByteString.

Refinement type

ASCII

data ASCII superset #

Instances

Instances details
Eq superset => Eq (ASCII superset) 
Instance details

Defined in ASCII.Refinement

Methods

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

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

Data superset => Data (ASCII superset) 
Instance details

Defined in ASCII.Refinement

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) #

Ord superset => Ord (ASCII superset) 
Instance details

Defined in ASCII.Refinement

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 #

Show superset => Show (ASCII superset) 
Instance details

Defined in ASCII.Refinement

Methods

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

show :: ASCII superset -> String #

showList :: [ASCII superset] -> ShowS #

Generic (ASCII superset) 
Instance details

Defined in ASCII.Refinement

Associated Types

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

Methods

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

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

Semigroup superset => Semigroup (ASCII superset) 
Instance details

Defined in ASCII.Refinement

Methods

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

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

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

Monoid superset => Monoid (ASCII superset) 
Instance details

Defined in ASCII.Refinement

Methods

mempty :: ASCII superset #

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

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

Hashable superset => Hashable (ASCII superset) 
Instance details

Defined in ASCII.Refinement

Methods

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

hash :: ASCII superset -> Int #

CharSuperset char => CharIso (ASCII char) 
Instance details

Defined in ASCII.Refinement

Methods

toChar :: ASCII char -> Char

StringSuperset string => StringIso (ASCII string) 
Instance details

Defined in ASCII.Refinement

Methods

toCharList :: ASCII string -> [Char]

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

StringSuperset string => StringSuperset (ASCII string) 
Instance details

Defined in ASCII.Refinement

Methods

isAsciiString :: ASCII string -> Bool

fromCharList :: [Char] -> ASCII string

toCharListUnsafe :: ASCII string -> [Char]

toCharListSub :: ASCII string -> [Char]

substituteString :: ASCII string -> ASCII string

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

CharSuperset char => CharSuperset (ASCII char) 
Instance details

Defined in ASCII.Refinement

Methods

isAsciiChar :: ASCII char -> Bool

fromChar :: Char -> ASCII char

toCharUnsafe :: ASCII char -> Char

Lift (ASCII superset) superset 
Instance details

Defined in ASCII.Lift

Methods

lift :: ASCII superset -> superset

type Rep (ASCII superset) 
Instance details

Defined in ASCII.Refinement

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

Polymorphic conversions

Validate

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

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

Lift

See also: ASCII.Lift

lift :: Lift ascii superset => ascii -> superset Source #

Converts from ASCII to any larger type.

For example, (lift @ASCII.Char @Word8) is the same function as charToWord8.

>>> lift CapitalLetterA :: Word8
65

And (lift @[ASCII.Char] @Text) is equivalent to charListToText.

>>> lift [CapitalLetterH,SmallLetterI,ExclamationMark] :: Text
"Hi!"

Due to the highly polymorphic nature of the lift function, often it must used with an explicit type signature or type application to avoid any type ambiguity.

Classes

CharSuperset

class CharSuperset char #

Minimal complete definition

isAsciiChar, fromChar, toCharUnsafe

Instances

Instances details
CharSuperset Char 
Instance details

Defined in ASCII.Superset

CharSuperset Int 
Instance details

Defined in ASCII.Superset

CharSuperset Natural 
Instance details

Defined in ASCII.Superset

CharSuperset Word8 
Instance details

Defined in ASCII.Superset

CharSuperset Char 
Instance details

Defined in ASCII.Superset

CharSuperset char => CharSuperset (ASCII char) 
Instance details

Defined in ASCII.Refinement

Methods

isAsciiChar :: ASCII char -> Bool

fromChar :: Char -> ASCII char

toCharUnsafe :: ASCII char -> Char

StringSuperset

class StringSuperset string #

Minimal complete definition

isAsciiString, fromCharList, toCharListUnsafe, toCharListSub, substituteString

Instances

Instances details
StringSuperset ByteString 
Instance details

Defined in ASCII.Superset

StringSuperset ByteString 
Instance details

Defined in ASCII.Superset

StringSuperset Builder 
Instance details

Defined in ASCII.Superset

StringSuperset Text 
Instance details

Defined in ASCII.Superset

StringSuperset Text 
Instance details

Defined in ASCII.Superset

StringSuperset Builder 
Instance details

Defined in ASCII.Superset

CharSuperset char => StringSuperset [char] 
Instance details

Defined in ASCII.Superset

Methods

isAsciiString :: [char] -> Bool

fromCharList :: [Char] -> [char]

toCharListUnsafe :: [char] -> [Char]

toCharListSub :: [char] -> [Char]

substituteString :: [char] -> [char]

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

StringSuperset string => StringSuperset (ASCII string) 
Instance details

Defined in ASCII.Refinement

Methods

isAsciiString :: ASCII string -> Bool

fromCharList :: [Char] -> ASCII string

toCharListUnsafe :: ASCII string -> [Char]

toCharListSub :: ASCII string -> [Char]

substituteString :: ASCII string -> ASCII string

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

Lift

class Lift ascii superset #

Minimal complete definition

lift

Instances

Instances details
CharSuperset superset => Lift Char superset 
Instance details

Defined in ASCII.Lift

Methods

lift :: Char -> superset

StringSuperset superset => Lift [Char] superset 
Instance details

Defined in ASCII.Lift

Methods

lift :: [Char] -> superset

Lift (ASCII superset) superset 
Instance details

Defined in ASCII.Lift

Methods

lift :: ASCII superset -> superset

CharIso

class CharSuperset char => CharIso char #

Minimal complete definition

toChar

Instances

Instances details
CharIso Char 
Instance details

Defined in ASCII.Isomorphism

Methods

toChar :: Char -> Char

CharSuperset char => CharIso (ASCII char) 
Instance details

Defined in ASCII.Refinement

Methods

toChar :: ASCII char -> Char

StringIso

class StringSuperset string => StringIso string #

Minimal complete definition

toCharList, mapChars

Instances

Instances details
CharIso char => StringIso [char] 
Instance details

Defined in ASCII.Isomorphism

Methods

toCharList :: [char] -> [Char]

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

StringSuperset string => StringIso (ASCII string) 
Instance details

Defined in ASCII.Refinement

Methods

toCharList :: ASCII string -> [Char]

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

Quasi-quoters

char

char :: QuasiQuoter #

Produces an expression or a pattern corresponding to an ASCII character.

The result will have an CharSuperset constraint; since this is polymorphic, use with a type signature to specify the particular you want is recommended.

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

>>> :set -XQuasiQuotes
>>> [char|e|] :: ASCII.Char
SmallLetterE
>>> [char|e|] :: Word8
101

Use in a pattern context requires enabling the ViewPatterns language extension.

>>> :set -XViewPatterns
>>> case Tilde of [char|@|] -> 1; [char|~|] -> 2; _ -> 3
2

string

string :: QuasiQuoter #

Produces an expression or a pattern corresponding to an ASCII string.

The result will have an StringSuperset constraint; since this is polymorphic, use with a type signature to specify the particular you want is recommended.

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

>>> :set -XQuasiQuotes
>>> [string|Hello!|] :: [ASCII.Char]
[CapitalLetterH,SmallLetterE,SmallLetterL,SmallLetterL,SmallLetterO,ExclamationMark]
>>> [string|Hello!|] :: Data.String.String
"Hello!"
>>> [string|Hello!|] :: Data.Text.Text
"Hello!"
>>> Data.ByteString.Builder.toLazyByteString [string|Hello!|]
"Hello!"

Use in a pattern context requires enabling the ViewPatterns language extension.

>>> :set -XViewPatterns
>>> case [CapitalLetterH, SmallLetterI] of [string|Bye|] -> 1; [string|Hi|] -> 2; _ -> 3
2