Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
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
- data Char
- type UnicodeChar = Char
- data CaselessChar
- data Group
- charGroup :: CharIso char => char -> Group
- inGroup :: CharSuperset char => Group -> char -> Bool
- data Case
- letterCase :: CharSuperset char => char -> Maybe Case
- isCase :: CharSuperset char => Case -> char -> Bool
- toCaseChar :: CharSuperset char => Case -> char -> char
- toCaseString :: StringSuperset string => Case -> string -> string
- disregardCase :: Char -> CaselessChar
- refineCharToCase :: forall (letterCase :: Case) char. (KnownCase letterCase, CharSuperset char) => ASCII char -> ASCII'case letterCase char
- refineStringToCase :: forall (letterCase :: Case) char. (KnownCase letterCase, StringSuperset char) => ASCII char -> ASCII'case letterCase char
- isLetter :: CharSuperset char => char -> Bool
- isAlphaNum :: CharSuperset char => char -> Bool
- isDigit :: CharSuperset char => char -> Bool
- data Digit
- isHexDigit :: CharSuperset char => char -> Bool
- data HexChar
- isOctDigit :: CharSuperset char => char -> Bool
- isSpace :: CharSuperset char => char -> Bool
- isPunctuation :: CharSuperset char => char -> Bool
- isSymbol :: CharSuperset char => char -> Bool
- isVisible :: CharSuperset char => char -> Bool
- charToInt :: Char -> Int
- intToCharMaybe :: Int -> Maybe Char
- intToCharUnsafe :: Int -> Char
- charToWord8 :: Char -> Word8
- word8ToCharMaybe :: Word8 -> Maybe Char
- word8ToCharUnsafe :: Word8 -> Char
- charToUnicode :: Char -> UnicodeChar
- unicodeToCharMaybe :: UnicodeChar -> Maybe Char
- unicodeToCharUnsafe :: UnicodeChar -> Char
- digitToWord8 :: Digit -> Word8
- word8ToDigitMaybe :: Word8 -> Maybe Digit
- word8ToDigitUnsafe :: Word8 -> Digit
- digitToChar :: Digit -> Char
- charToDigitMaybe :: Char -> Maybe Digit
- charToDigitUnsafe :: Char -> Digit
- digitToUnicode :: Digit -> UnicodeChar
- unicodeToDigitMaybe :: UnicodeChar -> Maybe Digit
- unicodeToDigitUnsafe :: UnicodeChar -> Digit
- hexCharToWord8 :: HexChar -> Word8
- word8ToHexCharMaybe :: Word8 -> Maybe HexChar
- word8ToHexCharUnsafe :: Word8 -> HexChar
- hexCharToChar :: HexChar -> Char
- charToHexCharMaybe :: Char -> Maybe HexChar
- charToHexCharUnsafe :: Char -> HexChar
- hexCharToUnicode :: HexChar -> UnicodeChar
- unicodeToHexCharMaybe :: UnicodeChar -> Maybe HexChar
- unicodeToHexCharUnsafe :: UnicodeChar -> HexChar
- charListToUnicodeString :: [Char] -> String
- unicodeStringToCharListMaybe :: String -> Maybe [Char]
- unicodeStringToCharListUnsafe :: String -> [Char]
- charListToText :: [Char] -> Text
- textToCharListMaybe :: Text -> Maybe [Char]
- textToCharListUnsafe :: Text -> [Char]
- charListToByteString :: [Char] -> ByteString
- byteStringToCharListMaybe :: ByteString -> Maybe [Char]
- byteStringToCharListUnsafe :: ByteString -> [Char]
- asciiByteStringToText :: ASCII ByteString -> Text
- asciiByteStringToTextLazy :: ASCII ByteString -> Text
- byteStringToUnicodeStringMaybe :: ByteString -> Maybe String
- unicodeStringToByteStringMaybe :: String -> Maybe ByteString
- byteListToUnicodeStringMaybe :: [Word8] -> Maybe String
- unicodeStringToByteListMaybe :: String -> Maybe [Word8]
- showNaturalDigits :: Natural -> [Digit]
- readNaturalDigits :: [Digit] -> Maybe Natural
- showNaturalHexChars :: Case -> Natural -> [HexChar]
- readNaturalHexChars :: [HexChar] -> Maybe Natural
- data ASCII superset
- data ASCII'case (letterCase :: Case) superset
- type ASCII'upper superset = ASCII'case 'UpperCase superset
- type ASCII'lower superset = ASCII'case 'LowerCase superset
- class KnownCase (letterCase :: Case) where
- toCharMaybe :: ToChar char => char -> Maybe Char
- toCharListMaybe :: ToString string => string -> Maybe [Char]
- toDigitMaybe :: DigitSuperset char => char -> Maybe Digit
- toHexCharMaybe :: HexCharSuperset char => char -> Maybe HexChar
- validateChar :: CharSuperset superset => superset -> Maybe (ASCII superset)
- validateString :: StringSuperset superset => superset -> Maybe (ASCII superset)
- lift :: ASCII superset -> superset
- toStrictText :: ToText a => a -> Text
- toLazyText :: ToText a => a -> Text
- toUnicodeCharList :: ToText a => a -> [Char]
- fromChar :: FromChar char => Char -> char
- fromCharList :: FromString string => [Char] -> string
- fromDigit :: DigitSuperset char => Digit -> char
- fromDigitList :: DigitStringSuperset string => [Digit] -> string
- fromHexChar :: HexCharSuperset char => HexChar -> char
- fromHexCharList :: HexStringSuperset string => [HexChar] -> string
- forgetCase :: forall (letterCase :: Case) superset. ASCII'case letterCase superset -> ASCII superset
- convertCharMaybe :: (CharSuperset char1, CharSuperset char2) => char1 -> Maybe char2
- convertCharOrFail :: (CharSuperset char1, CharSuperset char2, MonadFail context) => char1 -> context char2
- convertStringMaybe :: (StringSuperset string1, StringSuperset string2) => string1 -> Maybe string2
- convertStringOrFail :: (StringSuperset string1, StringSuperset string2, MonadFail context) => string1 -> context string2
- convertRefinedString :: StringSupersetConversion a b => ASCII a -> ASCII b
- showIntegralDecimal :: (Integral n, StringSuperset string) => n -> string
- showIntegralHexadecimal :: (Integral n, StringSuperset string) => Case -> n -> string
- readIntegralDecimal :: (StringSuperset string, Integral number, Bits number) => string -> Maybe number
- readIntegralHexadecimal :: (StringSuperset string, Integral number, Bits number) => string -> Maybe number
- showNaturalDecimal :: DigitStringSuperset string => Natural -> string
- showNaturalHexadecimal :: HexStringSuperset string => Case -> Natural -> string
- readNaturalDecimal :: DigitStringSuperset string => string -> Maybe Natural
- readNaturalHexadecimal :: HexStringSuperset string => string -> Maybe Natural
- digitString :: DigitStringSuperset string => Digit -> string
- hexCharString :: HexStringSuperset string => HexChar -> string
- class (ToChar char, FromChar char) => CharSuperset char
- class (ToString string, FromString string) => StringSuperset string
- class (StringSuperset a, StringSuperset b) => StringSupersetConversion a b
- class ToText a
- class CharSuperset char => CharIso char
- class StringSuperset string => StringIso string
- class DigitSuperset char
- class DigitStringSuperset string
- class HexCharSuperset char
- class HexStringSuperset string
- char :: QuasiQuoter
- string :: QuasiQuoter
- caseless :: QuasiQuoter
- lower :: QuasiQuoter
- upper :: QuasiQuoter
Char
ASCII
See also: ASCII.Char
A character in the ASCII character set
Instances
DigitSuperset Char | |
HexCharSuperset Char | |
Defined in ASCII.Hexadecimal | |
CharIso Char |
|
Defined in ASCII.Isomorphism | |
CharSuperset Char |
|
Defined in ASCII.Superset toCaseChar :: Case -> Char -> Char # | |
FromChar Char | |
Defined in ASCII.Superset | |
ToCaselessChar Char | |
Defined in ASCII.Superset isAsciiCaselessChar :: Char -> Bool # | |
ToChar Char | |
Defined in ASCII.Superset isAsciiChar :: Char -> Bool # toCharUnsafe :: Char -> Char # | |
Data Char | The |
Defined in ASCII.Char 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 # 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 |
Enum Char | The |
Generic Char | |
Show Char |
|
Eq Char | ASCII characters can be compared for equality using |
Ord Char | ASCII characters are ordered; for example, the letter A is "less than"
( |
Hashable Char | The |
Defined in ASCII.Char | |
KnownCase letterCase => ToCasefulChar letterCase Char | |
Defined in ASCII.Superset toCasefulChar :: CaselessChar -> Char # | |
DigitStringSuperset [Char] | |
Defined in ASCII.Decimal fromDigitList :: [Digit] -> [Char] # isDigitString :: [Char] -> Bool # toDigitListUnsafe :: [Char] -> [Digit] # toDigitListMaybe :: [Char] -> Maybe [Digit] # | |
HexStringSuperset [Char] | |
Defined in ASCII.Hexadecimal fromHexCharList :: [HexChar] -> [Char] # isHexString :: [Char] -> Bool # toHexCharListUnsafe :: [Char] -> [HexChar] # toHexCharListMaybe :: [Char] -> Maybe [HexChar] # | |
type Rep Char | The |
Defined in ASCII.Char type Rep Char = D1 ('MetaData "Char" "ASCII.Char" "ascii-char-1.0.1.0-3pT4pDaGksW4VqlCD3LUv" '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
FromChar CaselessChar | |
Defined in ASCII.Superset fromChar :: Char -> CaselessChar # | |
ToCaselessChar CaselessChar |
|
Defined in ASCII.Superset | |
Data CaselessChar | |
Defined in ASCII.Caseless 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 |
Defined in ASCII.Caseless | |
Enum CaselessChar | The |
Defined in ASCII.Caseless succ :: CaselessChar -> CaselessChar # pred :: CaselessChar -> CaselessChar # toEnum :: Int -> CaselessChar # fromEnum :: CaselessChar -> Int # enumFrom :: CaselessChar -> [CaselessChar] # enumFromThen :: CaselessChar -> CaselessChar -> [CaselessChar] # enumFromTo :: CaselessChar -> CaselessChar -> [CaselessChar] # enumFromThenTo :: CaselessChar -> CaselessChar -> CaselessChar -> [CaselessChar] # | |
Generic CaselessChar | |
Defined in ASCII.Caseless type Rep CaselessChar :: Type -> Type # from :: CaselessChar -> Rep CaselessChar x # to :: Rep CaselessChar x -> CaselessChar # | |
Show CaselessChar |
|
Defined in ASCII.Caseless showsPrec :: Int -> CaselessChar -> ShowS # show :: CaselessChar -> String # showList :: [CaselessChar] -> ShowS # | |
Eq CaselessChar | ASCII characters can be compared for equality using |
Defined in ASCII.Caseless (==) :: CaselessChar -> CaselessChar -> Bool # (/=) :: CaselessChar -> CaselessChar -> Bool # | |
Ord CaselessChar | Caseless ASCII characters are ordered; for example, the letter
A is "less than" ( |
Defined in ASCII.Caseless compare :: CaselessChar -> CaselessChar -> Ordering # (<) :: CaselessChar -> CaselessChar -> Bool # (<=) :: CaselessChar -> CaselessChar -> Bool # (>) :: CaselessChar -> CaselessChar -> Bool # (>=) :: CaselessChar -> CaselessChar -> Bool # max :: CaselessChar -> CaselessChar -> CaselessChar # min :: CaselessChar -> CaselessChar -> CaselessChar # | |
Hashable CaselessChar | |
Defined in ASCII.Caseless hashWithSalt :: Int -> CaselessChar -> Int # hash :: CaselessChar -> Int # | |
type Rep CaselessChar | |
Defined in ASCII.Caseless type Rep CaselessChar = D1 ('MetaData "CaselessChar" "ASCII.Caseless" "ascii-caseless-0.0.0.1-IMLONnoVfe0ER2pqwW65yd" '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
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
Data Group | |
Defined in ASCII.Group 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 # 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 | |
Enum Group | |
Generic Group | |
Show Group | |
Eq Group | |
Ord Group | |
Hashable Group | |
Defined in ASCII.Group | |
type Rep Group | |
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
UpperCase | The letters from |
LowerCase | The letters from |
Instances
Data Case | |
Defined in ASCII.Case 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 # 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 | |
Enum Case | |
Generic Case | |
Show Case | |
Eq Case | |
Ord Case | |
Hashable Case | |
Defined in ASCII.Case | |
type Rep Case | |
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 #
Decimal digits
See also: ASCII.Decimal
isDigit :: CharSuperset char => char -> Bool Source #
Instances
DigitSuperset Digit | |
Data Digit | |
Defined in ASCII.Decimal 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 # 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 | |
Enum Digit | |
Generic Digit | |
Show Digit | |
Eq Digit | |
Ord Digit | |
Hashable Digit | |
Defined in ASCII.Decimal | |
DigitStringSuperset [Digit] | |
Defined in ASCII.Decimal fromDigitList :: [Digit] -> [Digit] # isDigitString :: [Digit] -> Bool # toDigitListUnsafe :: [Digit] -> [Digit] # toDigitListMaybe :: [Digit] -> Maybe [Digit] # | |
type Rep Digit | |
Defined in ASCII.Decimal type Rep Digit = D1 ('MetaData "Digit" "ASCII.Decimal" "ascii-numbers-1.2.0.1-EVTqWeSDirPQuaDR2v6Pt" '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
See also: ASCII.Hexadecimal
isHexDigit :: CharSuperset char => char -> Bool Source #
Returns True for characters in any of the following ranges:
The subset of ASCII used to represent hexadecimal numbers:
Instances
HexCharSuperset HexChar | |
Defined in ASCII.Hexadecimal | |
Data HexChar | |
Defined in ASCII.Hexadecimal 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 | |
Enum HexChar | |
Generic HexChar | |
Show HexChar | |
Eq HexChar | |
Ord HexChar | |
Hashable HexChar | |
Defined in ASCII.Hexadecimal | |
HexStringSuperset [HexChar] | |
Defined in ASCII.Hexadecimal fromHexCharList :: [HexChar] -> [HexChar] # isHexString :: [HexChar] -> Bool # toHexCharListUnsafe :: [HexChar] -> [HexChar] # toHexCharListMaybe :: [HexChar] -> Maybe [HexChar] # | |
type Rep HexChar | |
Defined in ASCII.Hexadecimal type Rep HexChar = D1 ('MetaData "HexChar" "ASCII.Hexadecimal" "ascii-numbers-1.2.0.1-EVTqWeSDirPQuaDR2v6Pt" '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 #
Spaces and symbols
isSpace :: CharSuperset char => char -> Bool Source #
Returns True for the following characters:
isPunctuation :: CharSuperset char => char -> Bool Source #
isSymbol :: 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.Char
↔ Int
charToInt :: Char -> Int Source #
map charToInt [Null, CapitalLetterA, SmallLetterA, Delete] == [0, 65, 97, 127]
intToCharUnsafe :: Int -> Char Source #
ASCII.Char
↔ Word8
charToWord8 :: Char -> Word8 Source #
map charToWord8 [Null, CapitalLetterA, SmallLetterA, Delete] == [0, 65, 97, 127]
word8ToCharUnsafe :: Word8 -> Char Source #
ASCII.Char
↔ UnicodeChar
These functions convert between the ASCII Char
type and the UnicodeChar
type.
charToUnicode :: Char -> UnicodeChar Source #
Monomorphic digit conversions
Digit
↔ Word8
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.
digitToWord8 :: Digit -> Word8 Source #
word8ToDigitUnsafe :: Word8 -> Digit Source #
Digit
↔ ASCII.Char
digitToChar :: Digit -> Char Source #
charToDigitUnsafe :: Char -> Digit Source #
Digit
↔ UnicodeChar
These functions convert between the ASCII Digit
type and the UnicodeChar
type.
digitToUnicode :: Digit -> UnicodeChar Source #
HexChar
↔ Word8
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.
hexCharToWord8 :: HexChar -> Word8 Source #
word8ToHexCharUnsafe :: Word8 -> HexChar Source #
HexChar
↔ ASCII.Char
hexCharToChar :: HexChar -> Char Source #
charToHexCharUnsafe :: Char -> HexChar Source #
HexChar
↔ UnicodeChar
These functions convert between the ASCII HexChar
type and the UnicodeChar
type.
Monomorphic string conversions
ASCII.Char
↔ String
These functions convert between [
(a list of ASCII characters) and
Char
]String
(a list of Unicode characters).
charListToUnicodeString :: [Char] -> String Source #
unicodeStringToCharListUnsafe :: String -> [Char] Source #
ASCII.Char
↔ Text
charListToText :: [Char] -> Text Source #
charListToText [CapitalLetterH, SmallLetterI, ExclamationMark] == "Hi!"
textToCharListUnsafe :: Text -> [Char] Source #
ASCII.Char
↔ ByteString
These functions convert between [
and Char
]ByteString
.
charListToByteString :: [Char] -> ByteString Source #
byteStringToCharListMaybe :: ByteString -> Maybe [Char] Source #
byteStringToCharListUnsafe :: ByteString -> [Char] Source #
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
ByteString
↔ String
[Word8]
↔ String
Monomorphic numeric string conversions
Natural
↔ [Digit]
showNaturalDigits :: Natural -> [Digit] Source #
Specialization of showNaturalDecimal
See also: showIntegralDecimal
readNaturalDigits :: [Digit] -> Maybe Natural Source #
Specialization of readNaturalDecimal
See also: readIntegralDecimal
Natural
↔ [HexChar]
showNaturalHexChars :: Case -> Natural -> [HexChar] Source #
Specialization of showNaturalHexadecimal
See also: showIntegralHexadecimal
readNaturalHexChars :: [HexChar] -> Maybe Natural Source #
Specialization of readNaturalHexadecimal
See also: readIntegralHexadecimal
Refinement types
See also: ASCII.Refinement, ASCII.CaseRefinement
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
may contain
only ASCII characters.ASCII
Text
Instances
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
may contain only uppercase ASCII letters and ASCII
non-letters.ASCII'case
'UpperCase
Text
Instances
(FromChar superset, KnownCase letterCase) => ToCasefulChar letterCase (ASCII'case letterCase superset) | |
Defined in ASCII.CaseRefinement toCasefulChar :: CaselessChar -> ASCII'case letterCase superset # | |
(FromString superset, KnownCase letterCase) => ToCasefulString letterCase (ASCII'case letterCase superset) | |
Defined in ASCII.CaseRefinement toCasefulString :: [CaselessChar] -> ASCII'case letterCase superset # | |
ToCaselessChar char => ToCaselessChar (ASCII'case letterCase char) | |
Defined in ASCII.CaseRefinement isAsciiCaselessChar :: ASCII'case letterCase char -> Bool # toCaselessCharUnsafe :: ASCII'case letterCase char -> CaselessChar # | |
ToCaselessString string => ToCaselessString (ASCII'case letterCase string) | |
Defined in ASCII.CaseRefinement 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) | |
Defined in ASCII.CaseRefinement isAsciiChar :: ASCII'case letterCase char -> Bool # toCharUnsafe :: ASCII'case letterCase char -> Char # | |
ToString string => ToString (ASCII'case letterCase string) | |
Defined in ASCII.CaseRefinement isAsciiString :: ASCII'case letterCase string -> Bool # toCharListUnsafe :: ASCII'case letterCase string -> [Char] # toCharListSub :: ASCII'case letterCase string -> [Char] # | |
ToText (ASCII'case letterCase ByteString) | |
Defined in ASCII.Superset.Text toStrictText :: ASCII'case letterCase ByteString -> Text # toLazyText :: ASCII'case letterCase ByteString -> Text # toUnicodeCharList :: ASCII'case letterCase ByteString -> [Char] # | |
ToText (ASCII'case letterCase ByteString) | |
Defined in ASCII.Superset.Text toStrictText :: ASCII'case letterCase ByteString -> Text # toLazyText :: ASCII'case letterCase ByteString -> Text # toUnicodeCharList :: ASCII'case letterCase ByteString -> [Char] # | |
ToText (ASCII'case letterCase Text) | |
Defined in ASCII.Superset.Text toStrictText :: ASCII'case letterCase Text -> Text # toLazyText :: ASCII'case letterCase Text -> Text0 # toUnicodeCharList :: ASCII'case letterCase Text -> [Char] # | |
ToText (ASCII'case letterCase Text) | |
Defined in ASCII.Superset.Text toStrictText :: ASCII'case letterCase Text -> Text0 # toLazyText :: ASCII'case letterCase Text -> Text # toUnicodeCharList :: ASCII'case letterCase Text -> [Char] # | |
ToText (ASCII'case letterCase [Char]) | |
Defined in ASCII.Superset.Text 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) | |
Defined in ASCII.CaseRefinement 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) | |
Defined in ASCII.CaseRefinement 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) | |
Defined in ASCII.CaseRefinement (<>) :: 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) | |
Defined in ASCII.CaseRefinement type Rep (ASCII'case letterCase superset) :: Type -> Type # 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) | |
Defined in ASCII.CaseRefinement 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) | |
Defined in ASCII.CaseRefinement (==) :: 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) | |
Defined in ASCII.CaseRefinement 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) | |
Defined in ASCII.CaseRefinement hashWithSalt :: Int -> ASCII'case letterCase superset -> Int # hash :: ASCII'case letterCase superset -> Int # | |
type Rep (ASCII'case letterCase superset) | |
Defined in ASCII.CaseRefinement type Rep (ASCII'case letterCase superset) = D1 ('MetaData "ASCII'case" "ASCII.CaseRefinement" "ascii-superset-1.3.0.1-4LRykEnw1ehLVC8UFVRcEd" '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 #
Polymorphic conversions
Narrowing
toCharMaybe :: ToChar char => char -> Maybe Char #
toCharListMaybe :: ToString string => string -> Maybe [Char] #
toDigitMaybe :: DigitSuperset char => char -> Maybe Digit Source #
toHexCharMaybe :: HexCharSuperset char => char -> Maybe HexChar Source #
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
See also: ASCII.Superset.ToText
toStrictText :: ToText a => a -> Text #
toLazyText :: ToText a => a -> Text #
toUnicodeCharList :: ToText a => a -> [Char] #
See also: ASCII.Superset
fromCharList :: FromString string => [Char] -> string #
Conversion from [
Char
]
See also: ASCII.Decimal
fromDigit :: DigitSuperset char => Digit -> char #
fromDigitList :: DigitStringSuperset string => [Digit] -> string #
See also: ASCII.Hexadecimal
fromHexChar :: HexCharSuperset char => HexChar -> char #
fromHexCharList :: HexStringSuperset string => [HexChar] -> string #
See also: ASCII.CaseRefinement
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
See also: ASCII.Decimal and ASCII.Hexadecimal
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
:
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
:
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
Instances
CharSuperset Char |
|
Defined in ASCII.Superset toCaseChar :: Case -> Char -> Char # | |
CharSuperset Word8 | |
Defined in ASCII.Superset toCaseChar :: Case -> Word8 -> Word8 # | |
CharSuperset Natural | |
Defined in ASCII.Superset toCaseChar :: Case -> Natural -> Natural # | |
CharSuperset Char | |
Defined in ASCII.Superset toCaseChar :: Case -> Char -> Char # | |
CharSuperset Int | |
Defined in ASCII.Superset toCaseChar :: Case -> Int -> Int # | |
CharSuperset char => CharSuperset (ASCII char) | |
Defined in ASCII.Refinement.Internal 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
Instances
class (StringSuperset a, StringSuperset b) => StringSupersetConversion a b #
Instances
Instances
Equivalents to ASCII
class CharSuperset char => CharIso char #
class StringSuperset string => StringIso string #
Instances
StringSuperset string => StringIso (ASCII string) | |
CharIso char => StringIso [char] | |
Defined in ASCII.Isomorphism |
Supersets of numeric characters
class DigitSuperset char #
Instances
class DigitStringSuperset string #
Instances
class HexCharSuperset char #
Instances
HexCharSuperset Char | |
Defined in ASCII.Hexadecimal | |
HexCharSuperset HexChar | |
Defined in ASCII.Hexadecimal | |
HexCharSuperset Word8 | |
Defined in ASCII.Hexadecimal | |
HexCharSuperset Char | |
Defined in ASCII.Hexadecimal | |
HexCharSuperset char => HexCharSuperset (ASCII char) | |
Defined in ASCII.Hexadecimal |
class HexStringSuperset string #
Instances
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
(
constraint.
Any letters in the quoted content will be converted to lower case.ToCasefulString
'LowerCase
)
[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
(
constraint.
Any letters in the quoted content will be converted to upper case.ToCasefulString
'UpperCase
)
[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