ascii-superset-1.3.0.0: Representing ASCII with refined supersets
Safe HaskellSafe-Inferred
LanguageHaskell2010

ASCII.Superset

Synopsis

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.

Methods

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

Instances details
ToCaselessChar CaselessChar Source #

CaselessChar is trivially convertible to itself.

Instance details

Defined in ASCII.Superset

ToCaselessChar Char Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar Word8 Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar Natural Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar Char Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar Int Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar char => ToCaselessChar (ASCII char) Source # 
Instance details

Defined in ASCII.Refinement.Internal

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

Defined in ASCII.CaseRefinement

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.

Methods

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

Instances details
ToChar Char Source # 
Instance details

Defined in ASCII.Superset

ToChar Word8 Source # 
Instance details

Defined in ASCII.Superset

ToChar Natural Source # 
Instance details

Defined in ASCII.Superset

ToChar Char Source # 
Instance details

Defined in ASCII.Superset

ToChar Int Source # 
Instance details

Defined in ASCII.Superset

CharSuperset char => ToChar (ASCII char) Source # 
Instance details

Defined in ASCII.Refinement.Internal

Methods

isAsciiChar :: ASCII char -> Bool Source #

toCharUnsafe :: ASCII char -> Char Source #

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

Defined in ASCII.CaseRefinement

Methods

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

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

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.

Methods

fromChar :: Char -> char Source #

Conversion from Char

Instances

Instances details
FromChar CaselessChar Source # 
Instance details

Defined in ASCII.Superset

FromChar Char Source # 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char -> Char Source #

FromChar Word8 Source # 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char -> Word8 Source #

FromChar Natural Source # 
Instance details

Defined in ASCII.Superset

FromChar Char Source # 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char0 -> Char Source #

FromChar Int Source # 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char -> Int Source #

CharSuperset char => FromChar (ASCII char) Source # 
Instance details

Defined in ASCII.Refinement.Internal

Methods

fromChar :: Char -> ASCII char Source #

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

Character type with:

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

Methods

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

Instances details
CharSuperset Char Source #

Char is trivially a superset of itself.

Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Char -> Char Source #

CharSuperset Word8 Source # 
Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Word8 -> Word8 Source #

CharSuperset Natural Source # 
Instance details

Defined in ASCII.Superset

CharSuperset Char Source # 
Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Char -> Char Source #

CharSuperset Int Source # 
Instance details

Defined in ASCII.Superset

Methods

toCaseChar :: Case -> Int -> Int Source #

CharSuperset char => CharSuperset (ASCII char) Source # 
Instance details

Defined in ASCII.Refinement.Internal

Methods

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

class ToCasefulChar (letterCase :: Case) char where Source #

Instances

Instances details
KnownCase letterCase => ToCasefulChar letterCase Char Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulChar letterCase Word8 Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulChar letterCase Natural Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulChar letterCase Char Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulChar letterCase Int Source # 
Instance details

Defined in ASCII.Superset

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

Defined in ASCII.CaseRefinement

Methods

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.

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

toCharOrFail :: (ToChar char, MonadFail context) => char -> context Char Source #

toCaselessCharOrFail :: (ToCaselessChar char, MonadFail context) => char -> context CaselessChar Source #

toCharSub :: ToChar char => char -> Char 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.

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

Convert from one ASCII-superset character type to another via the ASCII Char type. Fails as Nothing if the input is outside the ASCII character set.

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

Convert from one ASCII-superset character type to another via the ASCII Char type. Fails with fail if the input is outside the ASCII character set.

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 [CaselessChar] type itself, which is already represented without case and does not have a ToString instance.

Methods

isAsciiCaselessString :: string -> Bool Source #

Test whether a character can be converted to [CaselessChar]

toCaselessCharListUnsafe :: string -> [CaselessChar] Source #

Conversion to [CaselessChar], defined only where isAsciiCaselessString is satisfied

toCaselessCharListSub :: string -> [CaselessChar] Source #

Conversion to [CaselessChar] achieved by using Substitute in place of any non-ASCII characters

Instances

Instances details
ToCaselessString Builder Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString ByteString Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString ByteString Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString Text Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString Builder Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString Text Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString string => ToCaselessString (ASCII string) Source # 
Instance details

Defined in ASCII.Refinement.Internal

ToCaselessChar char => ToCaselessString [char] Source # 
Instance details

Defined in ASCII.Superset

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

Defined in ASCII.CaseRefinement

class ToCaselessString string => ToString string where Source #

Partial conversion to [Char]

This includes [Char] type itself, strings of character sets that are supersets of ASCII, and sequences of 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.

Methods

isAsciiString :: string -> Bool Source #

Test whether a string can be converted to [Char]

toCharListUnsafe :: string -> [Char] Source #

Conversion to [Char], defined only where isAsciiString is satisfied

toCharListSub :: string -> [Char] Source #

Conversion to [Char] achieved by using Substitute in place of any non-ASCII characters

Instances

Instances details
ToString Builder Source # 
Instance details

Defined in ASCII.Superset

ToString ByteString Source # 
Instance details

Defined in ASCII.Superset

ToString ByteString Source # 
Instance details

Defined in ASCII.Superset

ToString Text Source # 
Instance details

Defined in ASCII.Superset

ToString Builder Source # 
Instance details

Defined in ASCII.Superset

ToString Text Source # 
Instance details

Defined in ASCII.Superset

ToString string => ToString (ASCII string) Source # 
Instance details

Defined in ASCII.Refinement.Internal

Methods

isAsciiString :: ASCII string -> Bool Source #

toCharListUnsafe :: ASCII string -> [Char] Source #

toCharListSub :: ASCII string -> [Char] Source #

ToChar char => ToString [char] Source # 
Instance details

Defined in ASCII.Superset

Methods

isAsciiString :: [char] -> Bool Source #

toCharListUnsafe :: [char] -> [Char] Source #

toCharListSub :: [char] -> [Char] Source #

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

Defined in ASCII.CaseRefinement

Methods

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

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

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

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 [CaselessChar], in which case fromCharList discards case information from letters.

This does not include [ASCII'case], because that represents a subset of ASCII; not all ASCII characters are of case wanted by ASCII'case, so no total conversion is possible without changing case.

Methods

fromCharList :: [Char] -> string Source #

Conversion from [Char]

Instances

Instances details
FromString Builder Source # 
Instance details

Defined in ASCII.Superset

FromString ByteString Source # 
Instance details

Defined in ASCII.Superset

FromString ByteString Source # 
Instance details

Defined in ASCII.Superset

FromString Text Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> Text Source #

FromString Builder Source # 
Instance details

Defined in ASCII.Superset

FromString Text Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> Text Source #

FromString string => FromString (ASCII string) Source # 
Instance details

Defined in ASCII.Refinement.Internal

Methods

fromCharList :: [Char] -> ASCII string Source #

FromChar char => FromString [char] Source # 
Instance details

Defined in ASCII.Superset

Methods

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

Minimal complete definition

substituteString, toCaseString

Methods

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

Instances details
StringSuperset Builder Source # 
Instance details

Defined in ASCII.Superset

StringSuperset ByteString Source # 
Instance details

Defined in ASCII.Superset

StringSuperset ByteString Source # 
Instance details

Defined in ASCII.Superset

StringSuperset Text Source # 
Instance details

Defined in ASCII.Superset

StringSuperset Builder Source # 
Instance details

Defined in ASCII.Superset

StringSuperset Text Source # 
Instance details

Defined in ASCII.Superset

StringSuperset string => StringSuperset (ASCII string) Source # 
Instance details

Defined in ASCII.Refinement.Internal

Methods

substituteString :: ASCII string -> ASCII string Source #

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

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

CharSuperset char => StringSuperset [char] Source # 
Instance details

Defined in ASCII.Superset

Methods

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

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

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

class ToCasefulString (letterCase :: Case) string where Source #

Methods

toCasefulString :: [CaselessChar] -> string Source #

Instances

Instances details
KnownCase letterCase => ToCasefulString letterCase Builder Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulString letterCase ByteString Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulString letterCase ByteString Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulString letterCase Text Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulString letterCase Builder Source # 
Instance details

Defined in ASCII.Superset

KnownCase letterCase => ToCasefulString letterCase Text Source # 
Instance details

Defined in ASCII.Superset

(ToCasefulChar letterCase char, KnownCase letterCase) => ToCasefulString letterCase [char] Source # 
Instance details

Defined in ASCII.Superset

Methods

toCasefulString :: [CaselessChar] -> [char] Source #

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

Defined in ASCII.CaseRefinement

Methods

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

Functions

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

toCharListOrFail :: (ToString string, MonadFail context) => string -> context [Char] Source #

toCaselessCharListOrFail :: (ToCaselessString string, MonadFail context) => string -> context [CaselessChar] Source #

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

Convert from one ASCII-superset string type to another by converting each character of the input string to an ASCII Char, and then converting the ASCII character list to the desired output type. Fails as Nothing if the input contains any character that is outside the ASCII character set.

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

Convert from one ASCII-superset string type to another by converting each character of the input string to an ASCII Char, and then converting the ASCII character list to the desired output type. Fails with fail if the input contains any character that is outside the ASCII character set.