Maintainer | hapytexeu+gh@gmail.com |
---|---|
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
- Possible rotations
- Rotated objects
- Letter case
- Ligating
- Types of fonts
- Character range checks
- Map characters from and to
Enum
s - Convert objects from and to Unicode
Char
acters - Mirroring items horizontally and/or vertically
- Ways to display numbers
- Functions to implement a number system
- Re-export of some functions of the
Char
module
This module defines data structures that are used in other modules, for example to rotate the characters.
Synopsis
- data Orientation
- data Rotate90
- data Oriented a = Oriented {
- oobject :: a
- orientation :: Orientation
- data Rotated a = Rotated {}
- data LetterCase
- splitLetterCase :: a -> a -> LetterCase -> a
- data Ligate
- splitLigate :: a -> a -> Ligate -> a
- ligate :: (a -> a) -> Ligate -> a -> a
- ligateF :: Functor f => (a -> a) -> Ligate -> f a -> f a
- data Emphasis
- splitEmphasis :: a -> a -> Emphasis -> a
- data ItalicType
- splitItalicType :: a -> a -> ItalicType -> a
- data FontStyle
- splitFontStyle :: a -> a -> FontStyle -> a
- isAsciiAlphaNum :: Char -> Bool
- isAsciiAlpha :: Char -> Bool
- isGreek :: Char -> Bool
- isACharacter :: Char -> Bool
- isNotACharacter :: Char -> Bool
- isReserved :: Char -> Bool
- isNotReserved :: Char -> Bool
- mapFromEnum :: Enum a => Int -> a -> Char
- mapToEnum :: Enum a => Int -> Char -> a
- mapToEnumSafe :: forall a. (Bounded a, Enum a) => Int -> Char -> Maybe a
- liftNumberFrom :: Int -> Int -> Int -> Int -> Maybe Char
- liftNumberFrom' :: Int -> Int -> Int -> Char
- liftNumber :: Int -> Int -> Int -> Maybe Char
- liftNumber' :: Int -> Int -> Char
- liftDigit :: Int -> Int -> Maybe Char
- liftDigit' :: Int -> Int -> Char
- liftUppercase :: Int -> Char -> Maybe Char
- liftUppercase' :: Int -> Char -> Char
- liftLowercase :: Int -> Char -> Maybe Char
- liftLowercase' :: Int -> Char -> Char
- liftUpperLowercase :: Int -> Int -> Char -> Maybe Char
- liftUpperLowercase' :: Int -> Int -> Char -> Char
- class UnicodeCharacter a where
- toUnicodeChar :: a -> Char
- fromUnicodeChar :: Char -> Maybe a
- fromUnicodeChar' :: Char -> a
- isInCharRange :: Char -> Bool
- type UnicodeChar = UnicodeCharacter
- class UnicodeText a where
- toUnicodeText :: a -> Text
- fromUnicodeText :: Text -> Maybe a
- fromUnicodeText' :: Text -> a
- isInTextRange :: Text -> Bool
- generateIsInTextRange :: (Char -> Bool) -> Text -> Bool
- generateIsInTextRange' :: forall a. UnicodeCharacter a => Text -> Bool
- class MirrorHorizontal a where
- mirrorHorizontal :: a -> a
- class MirrorVertical a where
- mirrorVertical :: a -> a
- data PlusStyle
- splitPlusStyle :: a -> a -> PlusStyle -> a
- withSign :: Integral i => (i -> Text) -> Char -> Char -> PlusStyle -> i -> Text
- signValueSystem :: Integral i => i -> (Int -> Int -> Text) -> Text -> Char -> Char -> PlusStyle -> i -> Text
- positionalNumberSystem :: Integral i => i -> (Int -> Char) -> Char -> Char -> PlusStyle -> i -> Text
- positionalNumberSystem10 :: Integral i => (Int -> Char) -> Char -> Char -> PlusStyle -> i -> Text
- chr :: Int -> Char
- isAlpha :: Char -> Bool
- isAlphaNum :: Char -> Bool
- isAscii :: Char -> Bool
- ord :: Char -> Int
Possible rotations
data Orientation Source #
The possible orientations of a unicode character, these can be horizontal, or vertical.
Horizontal | Horizontal orientation. |
Vertical | Vertical orientation. |
Instances
Possible rotations of a unicode character if that character can be rotated over 0, 90, 180, and 270 degrees.
R0 | No rotation. |
R90 | Rotation over 90 degrees. |
R180 | Rotation over 180 degrees. |
R270 | Rotation over 270 degrees. |
Instances
Arbitrary Rotate90 Source # | |
Data Rotate90 Source # | |
Defined in Data.Char.Core gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rotate90 -> c Rotate90 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rotate90 # toConstr :: Rotate90 -> Constr # dataTypeOf :: Rotate90 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rotate90) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rotate90) # gmapT :: (forall b. Data b => b -> b) -> Rotate90 -> Rotate90 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rotate90 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rotate90 -> r # gmapQ :: (forall d. Data d => d -> u) -> Rotate90 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rotate90 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rotate90 -> m Rotate90 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rotate90 -> m Rotate90 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rotate90 -> m Rotate90 # | |
Bounded Rotate90 Source # | |
Enum Rotate90 Source # | |
Generic Rotate90 Source # | |
Read Rotate90 Source # | |
Show Rotate90 Source # | |
NFData Rotate90 Source # | |
Defined in Data.Char.Core | |
Eq Rotate90 Source # | |
Ord Rotate90 Source # | |
Defined in Data.Char.Core | |
Hashable Rotate90 Source # | |
Defined in Data.Char.Core | |
type Rep Rotate90 Source # | |
Defined in Data.Char.Core type Rep Rotate90 = D1 ('MetaData "Rotate90" "Data.Char.Core" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) ((C1 ('MetaCons "R0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R90" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "R180" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R270" 'PrefixI 'False) (U1 :: Type -> Type))) |
Rotated objects
A data type that specifies that an item has been given an orientation.
Oriented | |
|
Instances
A data type that specifies that an item has been given a rotation.
Instances
Arbitrary1 Rotated Source # | |
Defined in Data.Char.Core liftArbitrary :: Gen a -> Gen (Rotated a) # liftShrink :: (a -> [a]) -> Rotated a -> [Rotated a] # | |
Foldable Rotated Source # | |
Defined in Data.Char.Core fold :: Monoid m => Rotated m -> m # foldMap :: Monoid m => (a -> m) -> Rotated a -> m # foldMap' :: Monoid m => (a -> m) -> Rotated a -> m # foldr :: (a -> b -> b) -> b -> Rotated a -> b # foldr' :: (a -> b -> b) -> b -> Rotated a -> b # foldl :: (b -> a -> b) -> b -> Rotated a -> b # foldl' :: (b -> a -> b) -> b -> Rotated a -> b # foldr1 :: (a -> a -> a) -> Rotated a -> a # foldl1 :: (a -> a -> a) -> Rotated a -> a # elem :: Eq a => a -> Rotated a -> Bool # maximum :: Ord a => Rotated a -> a # minimum :: Ord a => Rotated a -> a # | |
Eq1 Rotated Source # | |
Ord1 Rotated Source # | |
Defined in Data.Char.Core | |
Traversable Rotated Source # | |
Functor Rotated Source # | |
NFData1 Rotated Source # | |
Defined in Data.Char.Core | |
Hashable1 Rotated Source # | |
Defined in Data.Char.Core | |
Generic1 Rotated Source # | |
Arbitrary a => Arbitrary (Rotated a) Source # | |
Data a => Data (Rotated a) Source # | |
Defined in Data.Char.Core gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rotated a -> c (Rotated a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rotated a) # toConstr :: Rotated a -> Constr # dataTypeOf :: Rotated a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rotated a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rotated a)) # gmapT :: (forall b. Data b => b -> b) -> Rotated a -> Rotated a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rotated a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rotated a -> r # gmapQ :: (forall d. Data d => d -> u) -> Rotated a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rotated a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rotated a -> m (Rotated a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rotated a -> m (Rotated a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rotated a -> m (Rotated a) # | |
Bounded a => Bounded (Rotated a) Source # | |
Generic (Rotated a) Source # | |
Read a => Read (Rotated a) Source # | |
Show a => Show (Rotated a) Source # | |
NFData a => NFData (Rotated a) Source # | |
Defined in Data.Char.Core | |
Eq a => Eq (Rotated a) Source # | |
Ord a => Ord (Rotated a) Source # | |
Defined in Data.Char.Core | |
Hashable a => Hashable (Rotated a) Source # | |
Defined in Data.Char.Core | |
type Rep1 Rotated Source # | |
Defined in Data.Char.Core type Rep1 Rotated = D1 ('MetaData "Rotated" "Data.Char.Core" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Rotated" 'PrefixI 'True) (S1 ('MetaSel ('Just "robject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "rotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rotate90))) | |
type Rep (Rotated a) Source # | |
Defined in Data.Char.Core type Rep (Rotated a) = D1 ('MetaData "Rotated" "Data.Char.Core" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Rotated" 'PrefixI 'True) (S1 ('MetaSel ('Just "robject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "rotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rotate90))) |
Letter case
data LetterCase Source #
Specify whether we write a value in UpperCase
or LowerCase
. The
Default
is UpperCase
, since for example often Roman numerals are written
in upper case.
Instances
:: a | The value to return in case of |
-> a | The value to return in case of |
-> LetterCase | The given letter case. |
-> a | One of the two given values, depending on the |
Pick one of the two values based on the LetterCase
value.
Ligating
Specify if one should ligate, or not. When litigation is done
characters that are normally written in two (or more) characters
are combined in one character. For example Ⅲ
instead of ⅠⅠⅠ
.
Ligate | A ligate operation is performed on the characters, the |
NoLigate | No ligate operation is performed on the charaters. |
Instances
Arbitrary Ligate Source # | |
Data Ligate Source # | |
Defined in Data.Char.Core gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ligate -> c Ligate # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ligate # toConstr :: Ligate -> Constr # dataTypeOf :: Ligate -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ligate) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ligate) # gmapT :: (forall b. Data b => b -> b) -> Ligate -> Ligate # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ligate -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ligate -> r # gmapQ :: (forall d. Data d => d -> u) -> Ligate -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ligate -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ligate -> m Ligate # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ligate -> m Ligate # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ligate -> m Ligate # | |
Bounded Ligate Source # | |
Enum Ligate Source # | |
Defined in Data.Char.Core | |
Generic Ligate Source # | |
Read Ligate Source # | |
Show Ligate Source # | |
Default Ligate Source # | |
Defined in Data.Char.Core | |
NFData Ligate Source # | |
Defined in Data.Char.Core | |
Eq Ligate Source # | |
Ord Ligate Source # | |
Hashable Ligate Source # | |
Defined in Data.Char.Core | |
type Rep Ligate Source # | |
:: a | The value to return in case of 'v:Ligate'. |
-> a | The value to return in case of |
-> Ligate | The ligation style. |
-> a | One of the two given values, based on the 't:Ligate' value. |
Pick one of the two values based on the value for 't:Ligate'.
ligate :: (a -> a) -> Ligate -> a -> a Source #
Specify if the given ligate function should be performed on the input, if 'v:Ligate' is passed, and the identity function otherwise.
ligateF :: Functor f => (a -> a) -> Ligate -> f a -> f a Source #
Specify if the given ligate function is performed over the functor object if 'v:Ligate' is passed, and the identity function otherwise.
Types of fonts
A data type that lists the possible emphasis of a font. This can be Bold
or NoBold
the Default
is NoBold
.
Instances
Arbitrary Emphasis Source # | |
Data Emphasis Source # | |
Defined in Data.Char.Core gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Emphasis -> c Emphasis # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Emphasis # toConstr :: Emphasis -> Constr # dataTypeOf :: Emphasis -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Emphasis) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Emphasis) # gmapT :: (forall b. Data b => b -> b) -> Emphasis -> Emphasis # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Emphasis -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Emphasis -> r # gmapQ :: (forall d. Data d => d -> u) -> Emphasis -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Emphasis -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Emphasis -> m Emphasis # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Emphasis -> m Emphasis # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Emphasis -> m Emphasis # | |
Bounded Emphasis Source # | |
Enum Emphasis Source # | |
Generic Emphasis Source # | |
Read Emphasis Source # | |
Show Emphasis Source # | |
Default Emphasis Source # | |
Defined in Data.Char.Core | |
NFData Emphasis Source # | |
Defined in Data.Char.Core | |
Eq Emphasis Source # | |
Ord Emphasis Source # | |
Defined in Data.Char.Core | |
Hashable Emphasis Source # | |
Defined in Data.Char.Core | |
type Rep Emphasis Source # | |
:: a | The value to return in case of |
-> a | The value to return in case of |
-> Emphasis | The emphasis type. |
-> a | One of the two given values, based on the 't:Emphasis' value. |
Pick one of the two values based on the 't:Emphasis' value.
data ItalicType Source #
Instances
:: a | The value to return in case of |
-> a | The value to return in case of |
-> ItalicType | The italic type. |
-> a | One of the two given values, based on the 't:ItalicType' value. |
Pick one of the two values based on the 't:ItalicType' value.
A data type that specifies if the font is with serifs or not. The
'Defaul;t' is Serif
.
SansSerif | The character is a character rendered without serifs. |
Serif | The character is a character rendered with serifs. |
Instances
:: a | The value to return in case of |
-> a | The value to return in case of |
-> FontStyle | The font style. |
-> a | One of the two given values, based on the 't:FontStyle' value. |
Pick one of the two values based on the 't:FontStyle' value.
Character range checks
isAsciiAlphaNum :: Char -> Bool Source #
Checks if a character is an alphabetic or numerical character in ASCII.
The characters 0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz
satisfy this predicate.
isAsciiAlpha :: Char -> Bool Source #
Checks if a charcter is an alphabetic character in ASCII. The characters
ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz
satisfy this
predicate.
isGreek :: Char -> Bool Source #
Checks if a character is a basic greek alphabetic character or a Greek-like symbol.
The characters ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ
satisfy this predicate.
:: Char | The given |
-> Bool |
|
Check if the given character is a character according to the Unicode
specifications. Codepoints that are not a character are denoted in the
Unicode documentation with <not a character>
.
:: Char | The given |
-> Bool |
|
Check if the given character is not a character according to the Unicode
specifications. The Unicode documentation denotes these with <not a character>
.
Check if the given character is a reserved character. This is denoted in
the Unicode documentation with <reserved>
.
:: Char | The given |
-> Bool |
|
Check if the given character is not a reserved character. This is denoted in
the Unicode documentation with <reserved>
.
Map characters from and to Enum
s
:: Int | The given offset value. |
-> Int | The maximum value that can be mapped. |
-> Int | The given Unicode value used for the offset. |
-> Int | The given number to convert, must be between the offset and the maximum. |
-> Maybe Char | The corresponding |
Construct a function that maps digits to the character with the given value for the offset.
:: Int | The given offset value. |
-> Int | The given Unicode value used for the offset. |
-> Int | The given number to convert to a corresponding |
-> Char | The corresponding |
Construct a function that maps digits to the character with the given value for the offset.
:: Int | The maximum value that can be mapped. |
-> Int | The given Unicode value used for |
-> Int | The given digit to convert to a number between 0 and the maximum. |
-> Maybe Char | The corresponding |
Construct a function that maps digits to the character with the given value
for 0
.
:: Int | The given Unicode value used for |
-> Int | The given digit to convert. |
-> Char | The corresponding |
Construct a function that maps digits to characters with the given value
for 0
.
:: Int | The given Unicode value used for |
-> Int | The given digit to convert to a number between 0 and 9. |
-> Maybe Char | The corresponding |
Construct a function that maps digits to the character with the given value
for 0
.
:: Int | The given Unicode value used for |
-> Int | The given digit to convert, must be between |
-> Char | The corresponding |
Construct a function that maps digits to characters with the given value
for 0
.
:: Int | The given Unicode value for |
-> Char | The given character to convert. |
-> Maybe Char | The corresponding character wrapped in a |
Construct a function that maps upper case alphabetic characters with the
given value for A
.
:: Int | The given Unicode value for |
-> Char | The given upper case alphabetic value to convert. |
-> Char | The corresponding character, if the given value is outside the |
Construct a function that maps upper case alphabetic characters with the
given value for A
.
:: Int | The given Unicode value for |
-> Char | The given character to convert. |
-> Maybe Char | The corresponding character wrapped in a |
Construct a function that maps lower case alphabetic characters with the
given value for a
.
:: Int | The given Unicode value for |
-> Char | The given upper case alphabetic value to convert. |
-> Char | The corresponding character, if the given value is outside the |
Construct a function that maps lower case alphabetic characters with the
given value for a
.
:: Int | The given Unicode value for |
-> Int | The given Unicode value for |
-> Char | The given character to convert. |
-> Maybe Char | The corresponding character wrapped in a |
Construct a function that maps lower case alphabetic characters with the
given values for A
and a
.
:: Int | The given Unicode value for |
-> Int | The given Unicode value for |
-> Char | The given character to convert. |
-> Char | The corresponding character if the given character is in the |
Construct a function that maps lower case alphabetic characters with the
given values for A
and a
.
Convert objects from and to Unicode Char
acters
class UnicodeCharacter a where Source #
A class from which objects can be derived that map to and from a single unicode character.
Convert the given object to a Unicode Char
acter.
:: Char | The given |
-> Maybe a | An element if the given |
Convert the given Char
acter to an object wrapped in a Just
data
constructor if that exists; Nothing
otherwise.
:: Char | The given |
-> a | The given element that is equivalent to the given |
Convert the given Char
acter to an object. If the Char
acter does not
map on an element, the behavior is unspecified, it can for example
result in an error.
:: Char | The given |
-> Bool |
|
Check if the given Char
acter maps on an item of a
.
Instances
type UnicodeChar = UnicodeCharacter Source #
An alias of the UnicodeCharacter
type class.
class UnicodeText a where Source #
A class from which boejcts can be derived that map to and from a sequence of unicode characters.
Nothing
:: a | The given object to convert to a |
-> Text | A |
Convert the given object to a Text
object.
default toUnicodeText :: UnicodeCharacter a => a -> Text Source #
:: Text | The given |
-> Maybe a | The equivalent object wrapped in a |
Convert the given Text
to an object wrapped in a Just
data
constructor if that exists; Nothing
otherwise.
default fromUnicodeText :: UnicodeCharacter a => Text -> Maybe a Source #
:: Text | The given |
-> a | The given equivalent object. If there is no equivalent object, the behavior is unspecified. |
Convert the given Text
to an object. If the Text
does not map on
an element, the behavior is unspecified, it can for example result in
an error.
Determine if the given Text
value maps on a value of type a
.
Instances
generateIsInTextRange Source #
:: (Char -> Bool) | The given |
-> Text | The |
-> Bool |
|
Convert a given isInCharRange
check into a isInTextRange
check.
generateIsInTextRange' Source #
:: forall a. UnicodeCharacter a | |
=> Text | The given |
-> Bool |
|
Generate an isInTextRange
check with the isInCharRange
check for the instance of UnicodeCharacter
of that type.
Mirroring items horizontally and/or vertically
class MirrorHorizontal a where Source #
A type class that specifies that the items can be mirrored in the horizontal direction (such that up is now down). The mirror is not per se pixel perfect. For example the mirror of 🂁 is 🁵, so the dots of the bottom pat of the domino are not mirrored correctly.
:: a | The given item to mirror horizontally. |
-> a | The corresponding mirrored item. |
Obtain the horizontally mirrored variant of the given item. Applying the same function twice should return the original object.
Instances
MirrorHorizontal (Block a) Source # | |
Defined in Data.Char.Block mirrorHorizontal :: Block a -> Block a Source # | |
MirrorHorizontal (Sextant a) Source # | |
Defined in Data.Char.Block.Sextant mirrorHorizontal :: Sextant a -> Sextant a Source # | |
MirrorHorizontal (Braille a) Source # | |
Defined in Data.Char.Braille mirrorHorizontal :: Braille a -> Braille a Source # | |
MirrorHorizontal (Braille6 a) Source # | |
Defined in Data.Char.Braille mirrorHorizontal :: Braille6 a -> Braille6 a Source # | |
MirrorHorizontal (Oriented (Domino a)) Source # | |
Defined in Data.Char.Domino | |
MirrorHorizontal (Parts a) Source # | |
Defined in Data.Char.Frame mirrorHorizontal :: Parts a -> Parts a Source # | |
MirrorHorizontal (Vertical a) Source # | |
Defined in Data.Char.Frame mirrorHorizontal :: Vertical a -> Vertical a Source # |
class MirrorVertical a where Source #
A type class that specifies that the items can be mirrored in the vertical direction (such that left is now right). The mirror is not per se pixel perfect. For example the vertical mirror of 🁏 is 🁃, so the dots of the right part of the domino are not mirrored correctly.
:: a | The given item to mirror vertically. |
-> a | The corresponding mirrored item. |
Obtain the vertically mirrored variant of the given item. Applying the same function twice should return the original object.
Instances
Ways to display numbers
Specify whether we write a positive number with or without a plus sign.
the Default
is WithoutPlus
.
WithoutPlus | Write positive numbers without using a plus sign. |
WithPlus | Write positive numbers with a plus sign. |
Instances
:: a | The value to return in case of |
-> a | The value to return in case of |
-> PlusStyle | The plus style. |
-> a | One of the two given values, based on the 't:PlusStyle' value. |
Pick one of the two values based on the 't:PlusStyle' value.
Functions to implement a number system
:: Integral i | |
=> (i -> Text) | The function that maps the absolute value of the number to a |
-> Char | The plus sign to use. |
-> Char | The minus sign to use. |
-> PlusStyle | The given |
-> i | The given |
-> Text | A |
:: Integral i | |
=> i | The given radix to use. |
-> (Int -> Int -> Text) | A function that maps the value and the weight to a |
-> Text | The given |
-> Char | The given |
-> Char | The given |
-> PlusStyle | The given |
-> i | The given number to convert. |
-> Text | A |
A function to make it more convenient to implement a sign-value system.
This is done for a given radix a function that maps the given value and the
given weight to a Text
object, a Text
object for zero (since in some
systems that is different), and characters for plus and minus.
The function then will for a given PlusStyle
convert the number to a
sequence of characters with respect to how the sign-value system is
implemented.
positionalNumberSystem Source #
:: Integral i | |
=> i | The given radix to use. |
-> (Int -> Char) | A function that maps the value of a digit to the corresponding |
-> Char | The given character used to denote plus. |
-> Char | The given character used to denote minus. |
-> PlusStyle | The given |
-> i | The given number to convert. |
-> Text | A |
positionalNumberSystem10 Source #
:: Integral i | |
=> (Int -> Char) | A function that maps the value of a digit to the corresponding |
-> Char | The given character used to denote plus. |
-> Char | The given character used to denote minus. |
-> PlusStyle | The given |
-> i | The given number to convert. |
-> Text | A |
A function to make it more convenient to implement a /positional number system with radix/ 10.
Re-export of some functions of the Char
module
Selects alphabetic Unicode characters (lower-case, upper-case and
title-case letters, plus letters of caseless scripts and modifiers letters).
This function is equivalent to isLetter
.
isAlphaNum :: Char -> Bool #
Selects alphabetic or numeric Unicode characters.
Note that numeric digits outside the ASCII range, as well as numeric
characters which aren't digits, are selected by this function but not by
isDigit
. Such characters may be part of identifiers but are not used by
the printer and reader to represent numbers.
Selects the first 128 characters of the Unicode character set, corresponding to the ASCII character set.