Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class ToCaselessChar char where
- isAsciiCaselessChar :: char -> Bool
- toCaselessCharUnsafe :: char -> CaselessChar
- class ToCaselessChar char => ToChar char where
- isAsciiChar :: char -> Bool
- toCharUnsafe :: char -> Char
- class FromChar char where
- class (ToChar char, FromChar char) => CharSuperset char where
- toCaseChar :: Case -> char -> char
- class ToCasefulChar (letterCase :: Case) char where
- toCasefulChar :: CaselessChar -> char
- asCharUnsafe :: CharSuperset char => (Char -> Char) -> char -> char
- toCharMaybe :: ToChar char => char -> Maybe Char
- toCaselessCharMaybe :: ToCaselessChar char => char -> Maybe CaselessChar
- toCharOrFail :: (ToChar char, MonadFail context) => char -> context Char
- toCaselessCharOrFail :: (ToCaselessChar char, MonadFail context) => char -> context CaselessChar
- toCharSub :: ToChar char => char -> Char
- toCaselessCharSub :: ToCaselessChar char => char -> CaselessChar
- substituteChar :: CharSuperset char => char -> char
- convertCharMaybe :: (ToChar char1, FromChar char2) => char1 -> Maybe char2
- convertCharOrFail :: (ToChar char1, FromChar char2, MonadFail context) => char1 -> context char2
- class ToCaselessString string where
- isAsciiCaselessString :: string -> Bool
- toCaselessCharListUnsafe :: string -> [CaselessChar]
- toCaselessCharListSub :: string -> [CaselessChar]
- class ToCaselessString string => ToString string where
- isAsciiString :: string -> Bool
- toCharListUnsafe :: string -> [Char]
- toCharListSub :: string -> [Char]
- class FromString string where
- fromCharList :: [Char] -> string
- class (ToString string, FromString string) => StringSuperset string where
- substituteString :: string -> string
- mapCharsUnsafe :: (Char -> Char) -> string -> string
- toCaseString :: Case -> string -> string
- class ToCasefulString (letterCase :: Case) string where
- toCasefulString :: [CaselessChar] -> string
- toCharListMaybe :: ToString string => string -> Maybe [Char]
- toCaselessCharListMaybe :: ToCaselessString string => string -> Maybe [CaselessChar]
- toCharListOrFail :: (ToString string, MonadFail context) => string -> context [Char]
- toCaselessCharListOrFail :: (ToCaselessString string, MonadFail context) => string -> context [CaselessChar]
- convertStringMaybe :: (ToString string1, FromString string2) => string1 -> Maybe string2
- convertStringOrFail :: (ToString string1, FromString string2, MonadFail context) => string1 -> context string2
Characters
Class
class ToCaselessChar char where Source #
Partial conversion to CaselessChar
Generally this will be a superset of the ASCII character set with a ToChar
instance as well, and the conversion will be achieved by discarding the case of
letters. A notable exception is the instance for the CaselessChar
type itself,
which is already represented without case and does not have a ToChar
instance.
isAsciiCaselessChar :: char -> Bool Source #
Test whether a character can be converted to CaselessChar
toCaselessCharUnsafe :: char -> CaselessChar Source #
Conversion to CaselessChar
, defined only where isAsciiCaselessChar
is satisfied
Instances
class ToCaselessChar char => ToChar char where Source #
Partial conversion to Char
This includes the Char
type itself, character sets that are supersets
of ASCII, and numeric types such as Word8
that are often used to represent
ASCII characters.
This does not include CaselessChar
, because that cannot be converted to
Char
without choosing a case.
isAsciiChar :: char -> Bool Source #
Test whether a character can be converted to Char
toCharUnsafe :: char -> Char Source #
Conversion to Char
, defined only where isAsciiChar
is satisfied
Instances
class FromChar char where Source #
Total conversion from Char
This class includes supersets of ASCII, in which case fromChar
is a lifting
function. It also includes CaselessChar
, in which case fromChar
discards
case information.
This does not include ASCII'case
, because that represents
a subset of Char
; not all characters are of the wanted case, so no total
conversion is possible without changing case.
class (ToChar char, FromChar char) => CharSuperset char where Source #
Character type with:
- a total conversion from ASCII; and
- a partial conversion to ASCII
toCaseChar :: Case -> char -> char Source #
Convert a character in the superset to the designated case, if it is an ASCII letter of the opposite case. Otherwise, return the argument unmodified.
Instances
CharSuperset Char Source # |
|
Defined in ASCII.Superset | |
CharSuperset Word8 Source # | |
Defined in ASCII.Superset | |
CharSuperset Natural Source # | |
Defined in ASCII.Superset | |
CharSuperset Char Source # | |
Defined in ASCII.Superset | |
CharSuperset Int Source # | |
Defined in ASCII.Superset | |
CharSuperset char => CharSuperset (ASCII char) Source # | |
Defined in ASCII.Refinement.Internal |
class ToCasefulChar (letterCase :: Case) char where Source #
toCasefulChar :: CaselessChar -> char Source #
Instances
KnownCase letterCase => ToCasefulChar letterCase Char Source # | |
Defined in ASCII.Superset toCasefulChar :: CaselessChar -> Char Source # | |
KnownCase letterCase => ToCasefulChar letterCase Word8 Source # | |
Defined in ASCII.Superset toCasefulChar :: CaselessChar -> Word8 Source # | |
KnownCase letterCase => ToCasefulChar letterCase Natural Source # | |
Defined in ASCII.Superset toCasefulChar :: CaselessChar -> Natural Source # | |
KnownCase letterCase => ToCasefulChar letterCase Char Source # | |
Defined in ASCII.Superset toCasefulChar :: CaselessChar -> Char Source # | |
KnownCase letterCase => ToCasefulChar letterCase Int Source # | |
Defined in ASCII.Superset toCasefulChar :: CaselessChar -> Int Source # | |
(FromChar superset, KnownCase letterCase) => ToCasefulChar letterCase (ASCII'case letterCase superset) Source # | |
Defined in ASCII.CaseRefinement toCasefulChar :: CaselessChar -> ASCII'case letterCase superset Source # |
Functions
asCharUnsafe :: CharSuperset char => (Char -> Char) -> char -> char Source #
Manipulate a character as if it were an ASCII Char
, assuming that it is
Defined only where isAsciiChar
is satisfied.
toCaselessCharMaybe :: ToCaselessChar char => char -> Maybe CaselessChar Source #
toCaselessCharOrFail :: (ToCaselessChar char, MonadFail context) => char -> context CaselessChar Source #
toCaselessCharSub :: ToCaselessChar char => char -> CaselessChar Source #
substituteChar :: CharSuperset char => char -> char Source #
Force a character into ASCII by replacing it with Substitute
if it
is not already an ASCII character
The resulting character satisfies isAsciiChar
and isAsciiCaselessChar
.
convertCharOrFail :: (ToChar char1, FromChar char2, MonadFail context) => char1 -> context char2 Source #
Strings
Class
class ToCaselessString string where Source #
Partial conversion to [
CaselessChar
]
Generally this will be a superset of ASCII strings with a ToString
instance as
well, and the conversion will be achieved by discarding the case of letters. A
notable exception is the instance for [
type itself, which is
already represented without case and does not have a CaselessChar
]ToString
instance.
isAsciiCaselessString :: string -> Bool Source #
Test whether a character can be converted to [
CaselessChar
]
toCaselessCharListUnsafe :: string -> [CaselessChar] Source #
Conversion to [
, defined only where
CaselessChar
]isAsciiCaselessString
is satisfied
toCaselessCharListSub :: string -> [CaselessChar] Source #
Conversion to [
achieved by using
CaselessChar
]Substitute
in place of any non-ASCII characters
Instances
class ToCaselessString string => ToString string where Source #
Partial conversion to [
Char
]
This includes [
type itself, strings of character sets that are
supersets of ASCII, and sequences of numeric types such as Char
]Word8
that are
often used to represent ASCII characters.
This does not include [
, because that cannot be converted
to CaselessChar
][
without choosing a case. Char
]
isAsciiString :: string -> Bool Source #
Test whether a string can be converted to [
Char
]
toCharListUnsafe :: string -> [Char] Source #
Conversion to [
, defined only where Char
]isAsciiString
is satisfied
toCharListSub :: string -> [Char] Source #
Conversion to [
achieved by using
Char
]Substitute
in place of any non-ASCII characters
Instances
class FromString string where Source #
Total conversion from [
Char
]
This class includes supersets of ASCII, in which case fromCharList
lifts each
character into the larger character set. It also includes [
, in
which case CaselessChar
]fromCharList
discards case information from letters.
This does not include [
, because that
represents a subset of ASCII; not all ASCII characters are of case wanted by
ASCII'case
]ASCII'case
, so no total conversion is possible without
changing case.
fromCharList :: [Char] -> string Source #
Conversion from [
Char
]
Instances
FromString Builder Source # | |
Defined in ASCII.Superset fromCharList :: [Char] -> Builder Source # | |
FromString ByteString Source # | |
Defined in ASCII.Superset fromCharList :: [Char] -> ByteString Source # | |
FromString ByteString Source # | |
Defined in ASCII.Superset fromCharList :: [Char] -> ByteString Source # | |
FromString Text Source # | |
Defined in ASCII.Superset fromCharList :: [Char] -> Text Source # | |
FromString Builder Source # | |
Defined in ASCII.Superset fromCharList :: [Char] -> Builder Source # | |
FromString Text Source # | |
Defined in ASCII.Superset fromCharList :: [Char] -> Text Source # | |
FromString string => FromString (ASCII string) Source # | |
Defined in ASCII.Refinement.Internal fromCharList :: [Char] -> ASCII string Source # | |
FromChar char => FromString [char] Source # | |
Defined in ASCII.Superset fromCharList :: [Char] -> [char] Source # |
class (ToString string, FromString string) => StringSuperset string where Source #
String type with:
- a total conversion from ASCII; and
- a partial conversion to ASCII
substituteString :: string -> string Source #
Force a string into ASCII by replacing any non-ASCII character with Substitute
The resulting string satisfies isAsciiString
and isAsciiCaselessString
.
mapCharsUnsafe :: (Char -> Char) -> string -> string Source #
toCaseString :: Case -> string -> string Source #
Convert each character in the superset to the designated case, if it is an ASCII letter of the opposite case. Leaves other characters unchanged.
Instances
class ToCasefulString (letterCase :: Case) string where Source #
toCasefulString :: [CaselessChar] -> string Source #
Instances
Functions
toCaselessCharListMaybe :: ToCaselessString string => string -> Maybe [CaselessChar] Source #
toCaselessCharListOrFail :: (ToCaselessString string, MonadFail context) => string -> context [CaselessChar] Source #
convertStringMaybe :: (ToString string1, FromString string2) => string1 -> Maybe string2 Source #
convertStringOrFail :: (ToString string1, FromString string2, MonadFail context) => string1 -> context string2 Source #