Maintainer | hapytexeu+gh@gmail.com |
---|---|
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
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 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
- isACharacter :: Char -> Bool
- isNotACharacter :: Char -> Bool
- isReserved :: Char -> Bool
- 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
Bounded Rotate90 Source # | |
Enum Rotate90 Source # | |
Eq Rotate90 Source # | |
Ord Rotate90 Source # | |
Defined in Data.Char.Core | |
Read Rotate90 Source # | |
Show Rotate90 Source # | |
Arbitrary Rotate90 Source # | |
Rotated objects
A data type that specifies that an item has been given an orientation.
Oriented | |
|
Instances
Functor Oriented Source # | |
Foldable Oriented Source # | |
Defined in Data.Char.Core fold :: Monoid m => Oriented m -> m # foldMap :: Monoid m => (a -> m) -> Oriented a -> m # foldr :: (a -> b -> b) -> b -> Oriented a -> b # foldr' :: (a -> b -> b) -> b -> Oriented a -> b # foldl :: (b -> a -> b) -> b -> Oriented a -> b # foldl' :: (b -> a -> b) -> b -> Oriented a -> b # foldr1 :: (a -> a -> a) -> Oriented a -> a # foldl1 :: (a -> a -> a) -> Oriented a -> a # elem :: Eq a => a -> Oriented a -> Bool # maximum :: Ord a => Oriented a -> a # minimum :: Ord a => Oriented a -> a # | |
Traversable Oriented Source # | |
Arbitrary1 Oriented Source # | |
Defined in Data.Char.Core liftArbitrary :: Gen a -> Gen (Oriented a) # liftShrink :: (a -> [a]) -> Oriented a -> [Oriented a] # | |
Eq a => Eq (Oriented a) Source # | |
Ord a => Ord (Oriented a) Source # | |
Read a => Read (Oriented a) Source # | |
Show a => Show (Oriented a) Source # | |
Arbitrary a => Arbitrary (Oriented a) Source # | |
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. |
:: 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
Bounded Emphasis Source # | |
Enum Emphasis Source # | |
Eq Emphasis Source # | |
Ord Emphasis Source # | |
Defined in Data.Char.Core | |
Read Emphasis Source # | |
Show Emphasis Source # | |
Arbitrary Emphasis Source # | |
Default Emphasis Source # | |
Defined in Data.Char.Core |
:: 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
Bounded FontStyle Source # | |
Enum FontStyle Source # | |
Defined in Data.Char.Core succ :: FontStyle -> FontStyle # pred :: FontStyle -> FontStyle # fromEnum :: FontStyle -> Int # enumFrom :: FontStyle -> [FontStyle] # enumFromThen :: FontStyle -> FontStyle -> [FontStyle] # enumFromTo :: FontStyle -> FontStyle -> [FontStyle] # enumFromThenTo :: FontStyle -> FontStyle -> FontStyle -> [FontStyle] # | |
Eq FontStyle Source # | |
Ord FontStyle Source # | |
Defined in Data.Char.Core | |
Read FontStyle Source # | |
Show FontStyle Source # | |
Arbitrary FontStyle Source # | |
Default FontStyle Source # | |
Defined in Data.Char.Core |
:: 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.
:: 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>
.
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
Bounded PlusStyle Source # | |
Enum PlusStyle Source # | |
Defined in Data.Char.Core succ :: PlusStyle -> PlusStyle # pred :: PlusStyle -> PlusStyle # fromEnum :: PlusStyle -> Int # enumFrom :: PlusStyle -> [PlusStyle] # enumFromThen :: PlusStyle -> PlusStyle -> [PlusStyle] # enumFromTo :: PlusStyle -> PlusStyle -> [PlusStyle] # enumFromThenTo :: PlusStyle -> PlusStyle -> PlusStyle -> [PlusStyle] # | |
Eq PlusStyle Source # | |
Ord PlusStyle Source # | |
Defined in Data.Char.Core | |
Read PlusStyle Source # | |
Show PlusStyle Source # | |
Arbitrary PlusStyle Source # | |
Default PlusStyle Source # | |
Defined in Data.Char.Core |
:: 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.