ascii-superset-1.0.1.8: Representing ASCII with refined supersets
Safe HaskellNone
LanguageHaskell2010

ASCII.Refinement

Synopsis

ASCII type constructor

data ASCII superset Source #

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 ASCII Text may contain only ASCII characters.

Instances

Instances details
Eq superset => Eq (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Methods

(==) :: ASCII superset -> ASCII superset -> Bool #

(/=) :: ASCII superset -> ASCII superset -> Bool #

Data superset => Data (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ASCII superset -> c (ASCII superset) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ASCII superset) #

toConstr :: ASCII superset -> Constr #

dataTypeOf :: ASCII superset -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ASCII superset)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ASCII superset)) #

gmapT :: (forall b. Data b => b -> b) -> ASCII superset -> ASCII superset #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ASCII superset -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ASCII superset -> r #

gmapQ :: (forall d. Data d => d -> u) -> ASCII superset -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ASCII superset -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ASCII superset -> m (ASCII superset) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ASCII superset -> m (ASCII superset) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ASCII superset -> m (ASCII superset) #

Ord superset => Ord (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Methods

compare :: ASCII superset -> ASCII superset -> Ordering #

(<) :: ASCII superset -> ASCII superset -> Bool #

(<=) :: ASCII superset -> ASCII superset -> Bool #

(>) :: ASCII superset -> ASCII superset -> Bool #

(>=) :: ASCII superset -> ASCII superset -> Bool #

max :: ASCII superset -> ASCII superset -> ASCII superset #

min :: ASCII superset -> ASCII superset -> ASCII superset #

Show superset => Show (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Methods

showsPrec :: Int -> ASCII superset -> ShowS #

show :: ASCII superset -> String #

showList :: [ASCII superset] -> ShowS #

Generic (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Associated Types

type Rep (ASCII superset) :: Type -> Type #

Methods

from :: ASCII superset -> Rep (ASCII superset) x #

to :: Rep (ASCII superset) x -> ASCII superset #

Semigroup superset => Semigroup (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Methods

(<>) :: ASCII superset -> ASCII superset -> ASCII superset #

sconcat :: NonEmpty (ASCII superset) -> ASCII superset #

stimes :: Integral b => b -> ASCII superset -> ASCII superset #

Monoid superset => Monoid (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Methods

mempty :: ASCII superset #

mappend :: ASCII superset -> ASCII superset -> ASCII superset #

mconcat :: [ASCII superset] -> ASCII superset #

Hashable superset => Hashable (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

Methods

hashWithSalt :: Int -> ASCII superset -> Int #

hash :: ASCII superset -> Int #

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

Defined in ASCII.Refinement

Methods

isAsciiString :: ASCII string -> Bool Source #

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

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

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

substituteString :: ASCII string -> ASCII string Source #

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

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

Defined in ASCII.Refinement

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

Defined in ASCII.Refinement

Methods

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

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

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

Defined in ASCII.Refinement

Methods

toChar :: ASCII char -> Char Source #

Lift (ASCII superset) superset Source #

A value from an ASCII superset that has been refined by the ASCII type constructor may be lifted back into the superset by unwrapping it from the ASCII type.

Instance details

Defined in ASCII.Lift

Methods

lift :: ASCII superset -> superset Source #

type Rep (ASCII superset) Source # 
Instance details

Defined in ASCII.Refinement

type Rep (ASCII superset) = D1 ('MetaData "ASCII" "ASCII.Refinement" "ascii-superset-1.0.1.8-GuKIfXzsfU0Bz1p0RbXOC3" 'True) (C1 ('MetaCons "ASCII_Unsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "lift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 superset)))

lift :: ASCII superset -> superset Source #

asciiUnsafe :: superset -> ASCII superset Source #

Character functions

validateChar :: CharSuperset superset => superset -> Maybe (ASCII superset) Source #

>>> map validateChar [-1, 65, 97, 128] :: [Maybe (ASCII Int)]
[Nothing,Just (asciiUnsafe 65),Just (asciiUnsafe 97),Nothing]

fromChar :: CharSuperset superset => Char -> ASCII superset Source #

toChar :: CharSuperset superset => ASCII superset -> Char Source #

substituteChar :: CharSuperset superset => superset -> ASCII superset Source #

asChar :: CharSuperset superset => (Char -> Char) -> ASCII superset -> ASCII superset Source #

String functions

validateString :: StringSuperset superset => superset -> Maybe (ASCII superset) Source #

>>> map validateString ["Hello", "Cristóbal"] :: [Maybe (ASCII Text)]
[Just (asciiUnsafe "Hello"),Nothing]
>>> map validateString ["Hello", "Cristóbal"] :: [Maybe (ASCII String)]
[Just (asciiUnsafe "Hello"),Nothing]

fromCharList :: StringSuperset superset => [Char] -> ASCII superset Source #

>>> fromCharList [CapitalLetterH,SmallLetterI,ExclamationMark] :: ASCII Text
asciiUnsafe "Hi!"

toCharList :: StringSuperset superset => ASCII superset -> [Char] Source #

>>> toCharList (substituteString "Piñata" :: ASCII Text)
[CapitalLetterP,SmallLetterI,Substitute,SmallLetterA,SmallLetterT,SmallLetterA]

substituteString :: StringSuperset superset => superset -> ASCII superset Source #

Forces a string from a larger character set into ASCII by using the Substitute character in place of any non-ASCII characters.

>>> substituteString "Cristóbal" :: ASCII Text
asciiUnsafe "Crist\SUBbal"

mapChars :: StringSuperset superset => (Char -> Char) -> ASCII superset -> ASCII superset Source #