unicode-tricks-0.8.0.0: Functions to work with unicode blocks more convenient.

Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Core

Contents

Description

This module defines data structures that are used in other modules, for example to rotate the characters.

Synopsis

Possible rotations

data Orientation Source #

The possible orientations of a unicode character, these can be horizontal, or vertical.

Constructors

Horizontal

Horizontal orientation.

Vertical

Vertical orientation.

Instances
Bounded Orientation Source # 
Instance details

Defined in Data.Char.Core

Enum Orientation Source # 
Instance details

Defined in Data.Char.Core

Eq Orientation Source # 
Instance details

Defined in Data.Char.Core

Ord Orientation Source # 
Instance details

Defined in Data.Char.Core

Read Orientation Source # 
Instance details

Defined in Data.Char.Core

Show Orientation Source # 
Instance details

Defined in Data.Char.Core

Arbitrary Orientation Source # 
Instance details

Defined in Data.Char.Core

data Rotate90 Source #

Possible rotations of a unicode character if that character can be rotated over 0, 90, 180, and 270 degrees.

Constructors

R0

No rotation.

R90

Rotation over 90 degrees.

R180

Rotation over 180 degrees.

R270

Rotation over 270 degrees.

Instances
Bounded Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Enum Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Eq Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Ord Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Read Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Show Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Arbitrary Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Rotated objects

data Oriented a Source #

A data type that specifies that an item has been given an orientation.

Constructors

Oriented 

Fields

Instances
Functor Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

fmap :: (a -> b) -> Oriented a -> Oriented b #

(<$) :: a -> Oriented b -> Oriented a #

Foldable Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

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 #

toList :: Oriented a -> [a] #

null :: Oriented a -> Bool #

length :: Oriented a -> Int #

elem :: Eq a => a -> Oriented a -> Bool #

maximum :: Ord a => Oriented a -> a #

minimum :: Ord a => Oriented a -> a #

sum :: Num a => Oriented a -> a #

product :: Num a => Oriented a -> a #

Traversable Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

traverse :: Applicative f => (a -> f b) -> Oriented a -> f (Oriented b) #

sequenceA :: Applicative f => Oriented (f a) -> f (Oriented a) #

mapM :: Monad m => (a -> m b) -> Oriented a -> m (Oriented b) #

sequence :: Monad m => Oriented (m a) -> m (Oriented a) #

Arbitrary1 Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

liftArbitrary :: Gen a -> Gen (Oriented a) #

liftShrink :: (a -> [a]) -> Oriented a -> [Oriented a] #

Eq a => Eq (Oriented a) Source # 
Instance details

Defined in Data.Char.Core

Methods

(==) :: Oriented a -> Oriented a -> Bool #

(/=) :: Oriented a -> Oriented a -> Bool #

Ord a => Ord (Oriented a) Source # 
Instance details

Defined in Data.Char.Core

Methods

compare :: Oriented a -> Oriented a -> Ordering #

(<) :: Oriented a -> Oriented a -> Bool #

(<=) :: Oriented a -> Oriented a -> Bool #

(>) :: Oriented a -> Oriented a -> Bool #

(>=) :: Oriented a -> Oriented a -> Bool #

max :: Oriented a -> Oriented a -> Oriented a #

min :: Oriented a -> Oriented a -> Oriented a #

Read a => Read (Oriented a) Source # 
Instance details

Defined in Data.Char.Core

Show a => Show (Oriented a) Source # 
Instance details

Defined in Data.Char.Core

Methods

showsPrec :: Int -> Oriented a -> ShowS #

show :: Oriented a -> String #

showList :: [Oriented a] -> ShowS #

Arbitrary a => Arbitrary (Oriented a) Source # 
Instance details

Defined in Data.Char.Core

Methods

arbitrary :: Gen (Oriented a) #

shrink :: Oriented a -> [Oriented a] #

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.

Constructors

UpperCase

The upper case formatting.

LowerCase

The lower case formatting.

Instances
Bounded LetterCase Source # 
Instance details

Defined in Data.Char.Core

Enum LetterCase Source # 
Instance details

Defined in Data.Char.Core

Eq LetterCase Source # 
Instance details

Defined in Data.Char.Core

Ord LetterCase Source # 
Instance details

Defined in Data.Char.Core

Read LetterCase Source # 
Instance details

Defined in Data.Char.Core

Show LetterCase Source # 
Instance details

Defined in Data.Char.Core

Arbitrary LetterCase Source # 
Instance details

Defined in Data.Char.Core

Default LetterCase Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: LetterCase #

splitLetterCase Source #

Arguments

:: a

The value to return in case of UpperCase.

-> a

The value to return in case of LowerCase.

-> LetterCase

The given letter case.

-> a

One of the two given values, depending on the LetterCase value.

Pick one of the two values based on the LetterCase value.

Ligating

data Ligate Source #

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 ⅠⅠⅠ.

Constructors

Ligate

A ligate operation is performed on the characters, the def for 't:Ligate'.

NoLigate

No ligate operation is performed on the charaters.

Instances
Bounded Ligate Source # 
Instance details

Defined in Data.Char.Core

Enum Ligate Source # 
Instance details

Defined in Data.Char.Core

Eq Ligate Source # 
Instance details

Defined in Data.Char.Core

Methods

(==) :: Ligate -> Ligate -> Bool #

(/=) :: Ligate -> Ligate -> Bool #

Ord Ligate Source # 
Instance details

Defined in Data.Char.Core

Read Ligate Source # 
Instance details

Defined in Data.Char.Core

Show Ligate Source # 
Instance details

Defined in Data.Char.Core

Arbitrary Ligate Source # 
Instance details

Defined in Data.Char.Core

Default Ligate Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: Ligate #

splitLigate Source #

Arguments

:: a

The value to return in case of 'v:Ligate'.

-> a

The value to return in case of NoLigate.

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

data Emphasis Source #

A data type that lists the possible emphasis of a font. This can be Bold or NoBold the Default is NoBold.

Constructors

NoBold

The characters are not stressed with boldface.

Bold

The characters are stressed in boldface.

Instances
Bounded Emphasis Source # 
Instance details

Defined in Data.Char.Core

Enum Emphasis Source # 
Instance details

Defined in Data.Char.Core

Eq Emphasis Source # 
Instance details

Defined in Data.Char.Core

Ord Emphasis Source # 
Instance details

Defined in Data.Char.Core

Read Emphasis Source # 
Instance details

Defined in Data.Char.Core

Show Emphasis Source # 
Instance details

Defined in Data.Char.Core

Arbitrary Emphasis Source # 
Instance details

Defined in Data.Char.Core

Default Emphasis Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: Emphasis #

splitEmphasis Source #

Arguments

:: a

The value to return in case of NoBold.

-> a

The value to return in case of Bold.

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

A data type that can be used to specify if an italic character is used. The Default is NoItalic.

Constructors

NoItalic

No italic characters are used.

Italic

Italic characters are used.

Instances
Bounded ItalicType Source # 
Instance details

Defined in Data.Char.Core

Enum ItalicType Source # 
Instance details

Defined in Data.Char.Core

Eq ItalicType Source # 
Instance details

Defined in Data.Char.Core

Ord ItalicType Source # 
Instance details

Defined in Data.Char.Core

Read ItalicType Source # 
Instance details

Defined in Data.Char.Core

Show ItalicType Source # 
Instance details

Defined in Data.Char.Core

Arbitrary ItalicType Source # 
Instance details

Defined in Data.Char.Core

Default ItalicType Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: ItalicType #

splitItalicType Source #

Arguments

:: a

The value to return in case of NoItalic.

-> a

The value to return in case of Italic.

-> 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.

data FontStyle Source #

A data type that specifies if the font is with serifs or not. The 'Defaul;t' is Serif.

Constructors

SansSerif

The character is a character rendered without serifs.

Serif

The character is a character rendered with serifs.

Instances
Bounded FontStyle Source # 
Instance details

Defined in Data.Char.Core

Enum FontStyle Source # 
Instance details

Defined in Data.Char.Core

Eq FontStyle Source # 
Instance details

Defined in Data.Char.Core

Ord FontStyle Source # 
Instance details

Defined in Data.Char.Core

Read FontStyle Source # 
Instance details

Defined in Data.Char.Core

Show FontStyle Source # 
Instance details

Defined in Data.Char.Core

Arbitrary FontStyle Source # 
Instance details

Defined in Data.Char.Core

Default FontStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: FontStyle #

splitFontStyle Source #

Arguments

:: a

The value to return in case of SansSerif.

-> a

The value to return in case of Serif.

-> 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.

isACharacter Source #

Arguments

:: Char

The given Character to check.

-> Bool

True if the given Character is a character (according to the Unicode specifications); False otherwise.

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>.

isNotACharacter Source #

Arguments

:: Char

The given Character to check.

-> Bool

True if the given Character is not a character (according to the Unicode specifications); False otherwise.

Check if the given character is not a character according to the Unicode specifications. The Unicode documentation denotes these with <not a character>.

isReserved Source #

Arguments

:: Char

The given Character to check.

-> Bool

True if the given Character is reserved; False otherwise.

Check if the given character is a reserved character. This is denoted in the Unicode documentation with <reserved>.

Ways to display numbers

data PlusStyle Source #

Specify whether we write a positive number with or without a plus sign. the Default is WithoutPlus.

Constructors

WithoutPlus

Write positive numbers without using a plus sign.

WithPlus

Write positive numbers with a plus sign.

Instances
Bounded PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Enum PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Eq PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Ord PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Read PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Show PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Arbitrary PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Default PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: PlusStyle #

splitPlusStyle Source #

Arguments

:: a

The value to return in case of WithoutPlus.

-> a

The value to return in case of WithPlus.

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

withSign Source #

Arguments

:: Integral i 
=> (i -> Text)

The function that maps the absolute value of the number to a Text object that is appended to the sign.

-> Char

The plus sign to use.

-> Char

The minus sign to use.

-> PlusStyle

The given PlusStyle to use.

-> i

The given Integral number to render.

-> Text

A Text object that represents the given number, with the given sign numbers in the given PlusStyle.

Calculate for a given plus and minus sign a Text object for the given number in the given PlusStyle.

signValueSystem Source #

Arguments

:: Integral i 
=> i

The given radix to use.

-> (Int -> Int -> Text)

A function that maps the value and the weight to a Text object.

-> Text

The given Text used to represent zero.

-> Char

The given Char used to denote plus.

-> Char

The given Char used to denote minus.

-> PlusStyle

The given PlusStyle to use.

-> i

The given number to convert.

-> Text

A Text object that denotes the given number with the given sign-value system.

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 #

Arguments

:: Integral i 
=> i

The given radix to use.

-> (Int -> Char)

A function that maps the value of a digit to the corresponding Char.

-> Char

The given character used to denote plus.

-> Char

The given character used to denote minus.

-> PlusStyle

The given PlusStyle to use.

-> i

The given number to convert.

-> Text

A Text object that denotes the given number with the given positional number system.

A function to make it more convenient to implement a /positional number system. This is done for a given radix/ a given conversion funtion that maps a value to a Char, and a Char for plus and minus. The function then construct a Text object for a given PlusStyle and a given number.

positionalNumberSystem10 Source #

Arguments

:: Integral i 
=> (Int -> Char)

A function that maps the value of a digit to the corresponding Char.

-> Char

The given character used to denote plus.

-> Char

The given character used to denote minus.

-> PlusStyle

The given PlusStyle to use.

-> i

The given number to convert.

-> Text

A Text object that denotes the given number with the given positional number system.

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

chr :: Int -> Char #

The toEnum method restricted to the type Char.

isAlpha :: Char -> Bool #

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.

isAscii :: Char -> Bool #

Selects the first 128 characters of the Unicode character set, corresponding to the ASCII character set.

ord :: Char -> Int #

The fromEnum method restricted to the type Char.