ascii-char-1.0.1.0: A Char type representing an ASCII character
Safe HaskellSafe-Inferred
LanguageHaskell2010

ASCII.Char

Description

The Char type has 128 nullary constructors, listed in order according to each character's 7-bit numeric code.

Synopsis

The Char type

data Char Source #

A character in the ASCII character set

Constructors

Null 
StartOfHeading 
StartOfText 
EndOfText 
EndOfTransmission 
Enquiry 
Acknowledgement 
Bell 
Backspace 
HorizontalTab 
LineFeed 
VerticalTab 
FormFeed 
CarriageReturn 
ShiftOut 
ShiftIn 
DataLinkEscape 
DeviceControl1 
DeviceControl2 
DeviceControl3 
DeviceControl4 
NegativeAcknowledgement 
SynchronousIdle 
EndOfTransmissionBlock 
Cancel 
EndOfMedium 
Substitute 
Escape 
FileSeparator 
GroupSeparator 
RecordSeparator 
UnitSeparator 
Space 
ExclamationMark

!

QuotationMark

"

NumberSign

#

DollarSign

$

PercentSign

%

Ampersand

&

Apostrophe

#

LeftParenthesis

(

RightParenthesis

)

Asterisk

*

PlusSign

+

Comma

,

HyphenMinus

-

FullStop

.

Slash

/

Digit0 
Digit1 
Digit2 
Digit3 
Digit4 
Digit5 
Digit6 
Digit7 
Digit8 
Digit9 
Colon

:

Semicolon

;

LessThanSign

<

EqualsSign

=

GreaterThanSign

>

QuestionMark

?

AtSign

@

CapitalLetterA 
CapitalLetterB 
CapitalLetterC 
CapitalLetterD 
CapitalLetterE 
CapitalLetterF 
CapitalLetterG 
CapitalLetterH 
CapitalLetterI 
CapitalLetterJ 
CapitalLetterK 
CapitalLetterL 
CapitalLetterM 
CapitalLetterN 
CapitalLetterO 
CapitalLetterP 
CapitalLetterQ 
CapitalLetterR 
CapitalLetterS 
CapitalLetterT 
CapitalLetterU 
CapitalLetterV 
CapitalLetterW 
CapitalLetterX 
CapitalLetterY 
CapitalLetterZ 
LeftSquareBracket

[

Backslash

\

RightSquareBracket

]

Caret

^

Underscore

_

GraveAccent

`

SmallLetterA 
SmallLetterB 
SmallLetterC 
SmallLetterD 
SmallLetterE 
SmallLetterF 
SmallLetterG 
SmallLetterH 
SmallLetterI 
SmallLetterJ 
SmallLetterK 
SmallLetterL 
SmallLetterM 
SmallLetterN 
SmallLetterO 
SmallLetterP 
SmallLetterQ 
SmallLetterR 
SmallLetterS 
SmallLetterT 
SmallLetterU 
SmallLetterV 
SmallLetterW 
SmallLetterX 
SmallLetterY 
SmallLetterZ 
LeftCurlyBracket

{

VerticalLine

|

RightCurlyBracket

}

Tilde

~

Delete 

Instances

Instances details
Data Char Source #

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

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

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

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

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

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

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 #

type Rep Char Source #

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

Int

toInt :: Char -> Int Source #

Converts an ASCII character to its corresponding numeric value between 0 and 127

toInt Null == 0
toInt CapitalLetterA == 6
toInt SmallLetterA == 97
toInt Delete == 127

fromIntMaybe :: Int -> Maybe Char Source #

Returns Just the ASCII character corresponding to a numeric value between 0 and 127, or Nothing for numbers outside this range

fromIntMaybe (-1) == Nothing
fromIntMaybe 0 == Just Null
fromIntMaybe 65 == Just CapitalLetterA
fromIntMaybe 127 == Just Delete
fromIntMaybe 128 == Nothing

fromIntUnsafe :: Int -> Char Source #

The inverse of toInt

This is marked as unsafe because it is undefined for numbers below 0 or above 127. The safe variant of this function is fromIntMaybe.

fromIntUnsafe (-1) == undefined
fromIntUnsafe 65 == CapitalLetterA
fromIntUnsafe 66 == CapitalLetterB
fromIntUnsafe 67 == CapitalLetterC
fromIntUnsafe 128 == undefined

Word8

toWord8 :: Char -> Word8 Source #

Converts an ASCII character to its corresponding byte between 0 and 127

toWord8 Null == 0
toWord8 CapitalLetterA == 6
toWord8 SmallLetterA == 97
toWord8 Delete == 127

fromWord8Maybe :: Word8 -> Maybe Char Source #

Returns Just the ASCII character corresponding to a byte between 0 and 127, or Nothing for bytes above this range

fromWord8Maybe 0 == Just Null
fromWord8Maybe 65 == Just CapitalLetterA
fromWord8Maybe 127 == Just Delete
fromWord8Maybe 128 == Nothing

fromWord8Unsafe :: Word8 -> Char Source #

The inverse of toWord8

This is marked as unsafe because it is undefined bytes above 127. The safe variant of this function is fromWord8Maybe.

fromWord8Unsafe 65 == CapitalLetterA
fromWord8Unsafe 66 == CapitalLetterB
fromWord8Unsafe 67 == CapitalLetterC
fromWord8Unsafe 128 == undefined

Enumeration

Notes

There are 128 characters in total.

length allCharacters == 128

Null is the first character.

minBound == Null

Delete is the last character.

maxBound == Delete