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 Ligate
- ligate :: (a -> a) -> Ligate -> a -> a
- ligateF :: Functor f => (a -> a) -> Ligate -> f a -> f a
- data Emphasis
- data ItalicType
- data FontStyle
- isAsciiAlphaNum :: Char -> Bool
- isAsciiAlpha :: Char -> Bool
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 # | |
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. |
NoLigate | No ligate operation is performed on the charaters. |
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 |
data ItalicType Source #
Instances
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 |
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.