ascii-caseless-0.0.0.1: ASCII character without an upper/lower case distinction
Safe HaskellSafe-Inferred
LanguageGHC2021

ASCII.Caseless

Synopsis

The CaselessChar type

data CaselessChar Source #

A character in the ASCII character set, without an upper/lower case distinction for letters

Instances

Instances details
Data CaselessChar Source # 
Instance details

Defined in ASCII.Caseless

Methods

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 Source #

You can write ([minBound .. maxBound] :: [CaselessChar]) to get a list of all the caseless ASCII characters.

Instance details

Defined in ASCII.Caseless

Enum CaselessChar Source #

The Enum instance allows us to use range syntax, for example [LetterA .. LetterZ] is a list all letters from a to z.

Instance details

Defined in ASCII.Caseless

Generic CaselessChar Source # 
Instance details

Defined in ASCII.Caseless

Associated Types

type Rep CaselessChar :: Type -> Type #

Show CaselessChar Source #

show produces the name of a constructor. For example, the character e is shown as “LetterE”. See ASCII.Caseless for the complete list of constructor names.

Instance details

Defined in ASCII.Caseless

Eq CaselessChar Source #

ASCII characters can be compared for equality using (==).

Instance details

Defined in ASCII.Caseless

Ord CaselessChar Source #

Caseless ASCII characters are ordered; for example, the letter A is "less than" (<) the letter B because it appears earlier in the list. The ordering of caseless ASCII characters is roughly the same as the ordering of the corresponding Unicode Chars, with caseless letters appearing in the place of case-sensitive capital letters.

Instance details

Defined in ASCII.Caseless

Hashable CaselessChar Source # 
Instance details

Defined in ASCII.Caseless

type Rep CaselessChar Source # 
Instance details

Defined in ASCII.Caseless

type Rep CaselessChar = D1 ('MetaData "CaselessChar" "ASCII.Caseless" "ascii-caseless-0.0.0.1-HctL79sq60tHUCPbYuHQ6i" '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))))))))

Enumeration

allCharacters :: [CaselessChar] Source #

There are 102 characters in total.

Conversion

assumeCaseUnsafe :: Case -> Char -> CaselessChar Source #

Like disregardCase, but defined only where the character is either a letter in the given case or a non-letter

For upper case, this is slightly more efficient than disregardCase.