ascii-superset-1.1.0.0: Representing ASCII with refined supersets
Safe HaskellNone
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 Char Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar Int Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar Natural Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar Word8 Source # 
Instance details

Defined in ASCII.Superset

ToCaselessChar CaselessChar Source #

CaselessChar is trivially convertible to itself. (This instance is uninteresting.)

Instance details

Defined in ASCII.Superset

Methods

isAsciiCaselessChar :: CaselessChar -> Bool Source #

toCaselessCharUnsafe :: CaselessChar -> CaselessChar Source #

ToCaselessChar Char Source # 
Instance details

Defined in ASCII.Superset

Methods

isAsciiCaselessChar :: Char -> Bool Source #

toCaselessCharUnsafe :: Char -> CaselessChar Source #

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

Defined in ASCII.Refinement

Methods

isAsciiCaselessChar :: ASCII char -> Bool Source #

toCaselessCharUnsafe :: ASCII char -> CaselessChar Source #

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.

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 Int Source # 
Instance details

Defined in ASCII.Superset

ToChar Natural Source # 
Instance details

Defined in ASCII.Superset

ToChar Word8 Source # 
Instance details

Defined in ASCII.Superset

ToChar Char Source # 
Instance details

Defined in ASCII.Superset

Methods

isAsciiChar :: Char -> Bool Source #

toCharUnsafe :: Char -> Char Source #

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

Defined in ASCII.Refinement

Methods

isAsciiChar :: ASCII char -> Bool Source #

toCharUnsafe :: ASCII 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.

Methods

fromChar :: Char -> char Source #

Conversion from Char

Instances

Instances details
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 #

FromChar Natural Source # 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char -> Natural Source #

FromChar Word8 Source # 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char -> Word8 Source #

FromChar Char Source # 
Instance details

Defined in ASCII.Superset

Methods

fromChar :: Char -> Char Source #

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

Defined in ASCII.Refinement

Methods

fromChar :: Char -> ASCII char Source #

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

Character type with:

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

Instances

Instances details
CharSuperset Char Source # 
Instance details

Defined in ASCII.Superset

CharSuperset Int Source # 
Instance details

Defined in ASCII.Superset

CharSuperset Natural Source # 
Instance details

Defined in ASCII.Superset

CharSuperset Word8 Source # 
Instance details

Defined in ASCII.Superset

CharSuperset Char Source #

Char is trivially a superset of itself. (This instance is uninteresting.)

Instance details

Defined in ASCII.Superset

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

Defined in ASCII.Refinement

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 #

toCaselessCharMaybe :: ToCaselessChar char => char -> Maybe CaselessChar 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 #

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.

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 ByteString Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString ByteString Source # 
Instance details

Defined in ASCII.Superset

ToCaselessString Builder 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 Text Source # 
Instance details

Defined in ASCII.Superset

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

Defined in ASCII.Superset

Methods

isAsciiCaselessString :: [char] -> Bool Source #

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

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

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

Defined in ASCII.Refinement

Methods

isAsciiCaselessString :: ASCII string -> Bool Source #

toCaselessCharListUnsafe :: ASCII string -> [CaselessChar] Source #

toCaselessCharListSub :: ASCII string -> [CaselessChar] Source #

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.

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 ByteString Source # 
Instance details

Defined in ASCII.Superset

ToString ByteString Source # 
Instance details

Defined in ASCII.Superset

ToString Builder 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 Text Source # 
Instance details

Defined in ASCII.Superset

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 string) Source # 
Instance details

Defined in ASCII.Refinement

Methods

isAsciiString :: ASCII string -> Bool Source #

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

toCharListSub :: ASCII 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.

Methods

fromCharList :: [Char] -> string Source #

Conversion from [Char]

Instances

Instances details
FromString ByteString Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> ByteString Source #

FromString ByteString Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> ByteString Source #

FromString Builder Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> Builder Source #

FromString Builder Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> Builder Source #

FromString Text Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> Text Source #

FromString Text Source # 
Instance details

Defined in ASCII.Superset

Methods

fromCharList :: [Char] -> Text Source #

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

Defined in ASCII.Superset

Methods

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

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

Defined in ASCII.Refinement

Methods

fromCharList :: [Char] -> ASCII string 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

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 #

Instances

Instances details
StringSuperset ByteString Source # 
Instance details

Defined in ASCII.Superset

StringSuperset ByteString Source # 
Instance details

Defined in ASCII.Superset

StringSuperset Builder 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

Methods

substituteString :: Text -> Text Source #

mapCharsUnsafe :: (Char -> Char) -> Text -> Text Source #

StringSuperset Text Source # 
Instance details

Defined in ASCII.Superset

Methods

substituteString :: Text -> Text Source #

mapCharsUnsafe :: (Char -> Char) -> Text -> Text Source #

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

Defined in ASCII.Superset

Methods

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

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

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

Defined in ASCII.Refinement

Methods

substituteString :: ASCII string -> ASCII string Source #

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

Functions

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

toCaselessCharListMaybe :: ToCaselessString string => string -> Maybe [CaselessChar] 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.