unicode-tricks-0.11.0.0: Functions to work with unicode blocks more convenient.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Core

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

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

Data Orientation Source # 
Instance details

Defined in Data.Char.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Orientation -> c Orientation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Orientation #

toConstr :: Orientation -> Constr #

dataTypeOf :: Orientation -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Orientation) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Orientation) #

gmapT :: (forall b. Data b => b -> b) -> Orientation -> Orientation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Orientation -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Orientation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Orientation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Orientation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Orientation -> m Orientation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Orientation -> m Orientation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Orientation -> m Orientation #

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

Generic Orientation Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep Orientation :: Type -> Type #

Arbitrary Orientation Source # 
Instance details

Defined in Data.Char.Core

NFData Orientation Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: Orientation -> () #

Hashable Orientation Source # 
Instance details

Defined in Data.Char.Core

type Rep Orientation Source # 
Instance details

Defined in Data.Char.Core

type Rep Orientation = D1 ('MetaData "Orientation" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "Horizontal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Vertical" 'PrefixI 'False) (U1 :: Type -> Type))

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

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

Data Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Methods

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 #

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

Generic Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep Rotate90 :: Type -> Type #

Methods

from :: Rotate90 -> Rep Rotate90 x #

to :: Rep Rotate90 x -> Rotate90 #

Arbitrary Rotate90 Source # 
Instance details

Defined in Data.Char.Core

NFData Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: Rotate90 -> () #

Hashable Rotate90 Source # 
Instance details

Defined in Data.Char.Core

Methods

hashWithSalt :: Int -> Rotate90 -> Int #

hash :: Rotate90 -> Int #

type Rep Rotate90 Source # 
Instance details

Defined in Data.Char.Core

type Rep Rotate90 = D1 ('MetaData "Rotate90" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" '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

data Oriented a Source #

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

Constructors

Oriented 

Fields

Instances

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

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

Eq1 Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

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

Ord1 Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

liftCompare :: (a -> b -> Ordering) -> Oriented a -> Oriented b -> Ordering #

NFData1 Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

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

Hashable1 Oriented Source # 
Instance details

Defined in Data.Char.Core

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Oriented a -> Int #

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

Defined in Data.Char.Core

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

Defined in Data.Char.Core

Methods

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

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

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

Defined in Data.Char.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Oriented a -> c (Oriented a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Oriented a) #

toConstr :: Oriented a -> Constr #

dataTypeOf :: Oriented a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Oriented a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Oriented a)) #

gmapT :: (forall b. Data b => b -> b) -> Oriented a -> Oriented a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Oriented a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Oriented a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Oriented a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Oriented a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Oriented a -> m (Oriented a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Oriented a -> m (Oriented a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Oriented a -> m (Oriented a) #

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 #

Generic (Oriented a) Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep (Oriented a) :: Type -> Type #

Methods

from :: Oriented a -> Rep (Oriented a) x #

to :: Rep (Oriented a) x -> Oriented a #

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

Defined in Data.Char.Core

Methods

arbitrary :: Gen (Oriented a) #

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

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

Defined in Data.Char.Core

Methods

rnf :: Oriented a -> () #

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

Defined in Data.Char.Core

Methods

hashWithSalt :: Int -> Oriented a -> Int #

hash :: Oriented a -> Int #

UnicodeText (Oriented (Domino (Maybe DieValue))) Source # 
Instance details

Defined in Data.Char.Domino

UnicodeText (Oriented (Domino DieValue)) Source # 
Instance details

Defined in Data.Char.Domino

UnicodeCharacter (Oriented (Domino (Maybe DieValue))) Source # 
Instance details

Defined in Data.Char.Domino

UnicodeCharacter (Oriented (Domino DieValue)) Source # 
Instance details

Defined in Data.Char.Domino

Generic1 Oriented Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep1 Oriented :: k -> Type #

Methods

from1 :: forall (a :: k). Oriented a -> Rep1 Oriented a #

to1 :: forall (a :: k). Rep1 Oriented a -> Oriented a #

type Rep (Oriented a) Source # 
Instance details

Defined in Data.Char.Core

type Rep (Oriented a) = D1 ('MetaData "Oriented" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "Oriented" 'PrefixI 'True) (S1 ('MetaSel ('Just "oobject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "orientation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Orientation)))
type Rep1 Oriented Source # 
Instance details

Defined in Data.Char.Core

type Rep1 Oriented = D1 ('MetaData "Oriented" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "Oriented" 'PrefixI 'True) (S1 ('MetaSel ('Just "oobject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "orientation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Orientation)))

data Rotated a Source #

A data type that specifies that an item has been given a rotation.

Constructors

Rotated 

Fields

Instances

Instances details
Functor Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

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

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

Foldable Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

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 #

toList :: Rotated a -> [a] #

null :: Rotated a -> Bool #

length :: Rotated a -> Int #

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

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

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

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

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

Traversable Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

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

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

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

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

Arbitrary1 Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

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

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

Eq1 Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

liftEq :: (a -> b -> Bool) -> Rotated a -> Rotated b -> Bool #

Ord1 Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

liftCompare :: (a -> b -> Ordering) -> Rotated a -> Rotated b -> Ordering #

NFData1 Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

liftRnf :: (a -> ()) -> Rotated a -> () #

Hashable1 Rotated Source # 
Instance details

Defined in Data.Char.Core

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Rotated a -> Int #

Bounded a => Bounded (Rotated a) Source # 
Instance details

Defined in Data.Char.Core

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

Defined in Data.Char.Core

Methods

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

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

Data a => Data (Rotated a) Source # 
Instance details

Defined in Data.Char.Core

Methods

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

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

Defined in Data.Char.Core

Methods

compare :: Rotated a -> Rotated a -> Ordering #

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

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

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

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

max :: Rotated a -> Rotated a -> Rotated a #

min :: Rotated a -> Rotated a -> Rotated a #

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

Defined in Data.Char.Core

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

Defined in Data.Char.Core

Methods

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

show :: Rotated a -> String #

showList :: [Rotated a] -> ShowS #

Generic (Rotated a) Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep (Rotated a) :: Type -> Type #

Methods

from :: Rotated a -> Rep (Rotated a) x #

to :: Rep (Rotated a) x -> Rotated a #

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

Defined in Data.Char.Core

Methods

arbitrary :: Gen (Rotated a) #

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

NFData a => NFData (Rotated a) Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: Rotated a -> () #

Hashable a => Hashable (Rotated a) Source # 
Instance details

Defined in Data.Char.Core

Methods

hashWithSalt :: Int -> Rotated a -> Int #

hash :: Rotated a -> Int #

Generic1 Rotated Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep1 Rotated :: k -> Type #

Methods

from1 :: forall (a :: k). Rotated a -> Rep1 Rotated a #

to1 :: forall (a :: k). Rep1 Rotated a -> Rotated a #

type Rep (Rotated a) Source # 
Instance details

Defined in Data.Char.Core

type Rep (Rotated a) = D1 ('MetaData "Rotated" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "Rotated" 'PrefixI 'True) (S1 ('MetaSel ('Just "robject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "rotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rotate90)))
type Rep1 Rotated Source # 
Instance details

Defined in Data.Char.Core

type Rep1 Rotated = D1 ('MetaData "Rotated" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "Rotated" 'PrefixI 'True) (S1 ('MetaSel ('Just "robject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: 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.

Constructors

UpperCase

The upper case formatting.

LowerCase

The lower case formatting.

Instances

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

Data LetterCase Source # 
Instance details

Defined in Data.Char.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LetterCase -> c LetterCase #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LetterCase #

toConstr :: LetterCase -> Constr #

dataTypeOf :: LetterCase -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LetterCase) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LetterCase) #

gmapT :: (forall b. Data b => b -> b) -> LetterCase -> LetterCase #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LetterCase -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LetterCase -> r #

gmapQ :: (forall d. Data d => d -> u) -> LetterCase -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LetterCase -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LetterCase -> m LetterCase #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LetterCase -> m LetterCase #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LetterCase -> m LetterCase #

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

Generic LetterCase Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep LetterCase :: Type -> Type #

Arbitrary LetterCase Source # 
Instance details

Defined in Data.Char.Core

Default LetterCase Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: LetterCase #

NFData LetterCase Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: LetterCase -> () #

Hashable LetterCase Source # 
Instance details

Defined in Data.Char.Core

type Rep LetterCase Source # 
Instance details

Defined in Data.Char.Core

type Rep LetterCase = D1 ('MetaData "LetterCase" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "UpperCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LowerCase" 'PrefixI 'False) (U1 :: Type -> Type))

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

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

Data Ligate Source # 
Instance details

Defined in Data.Char.Core

Methods

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 #

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

Generic Ligate Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep Ligate :: Type -> Type #

Methods

from :: Ligate -> Rep Ligate x #

to :: Rep Ligate x -> Ligate #

Arbitrary Ligate Source # 
Instance details

Defined in Data.Char.Core

Default Ligate Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: Ligate #

NFData Ligate Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: Ligate -> () #

Hashable Ligate Source # 
Instance details

Defined in Data.Char.Core

Methods

hashWithSalt :: Int -> Ligate -> Int #

hash :: Ligate -> Int #

type Rep Ligate Source # 
Instance details

Defined in Data.Char.Core

type Rep Ligate = D1 ('MetaData "Ligate" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "Ligate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoLigate" 'PrefixI 'False) (U1 :: Type -> Type))

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

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

Data Emphasis Source # 
Instance details

Defined in Data.Char.Core

Methods

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 #

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

Generic Emphasis Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep Emphasis :: Type -> Type #

Methods

from :: Emphasis -> Rep Emphasis x #

to :: Rep Emphasis x -> Emphasis #

Arbitrary Emphasis Source # 
Instance details

Defined in Data.Char.Core

Default Emphasis Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: Emphasis #

NFData Emphasis Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: Emphasis -> () #

Hashable Emphasis Source # 
Instance details

Defined in Data.Char.Core

Methods

hashWithSalt :: Int -> Emphasis -> Int #

hash :: Emphasis -> Int #

type Rep Emphasis Source # 
Instance details

Defined in Data.Char.Core

type Rep Emphasis = D1 ('MetaData "Emphasis" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "NoBold" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bold" 'PrefixI 'False) (U1 :: Type -> Type))

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

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

Data ItalicType Source # 
Instance details

Defined in Data.Char.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ItalicType -> c ItalicType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ItalicType #

toConstr :: ItalicType -> Constr #

dataTypeOf :: ItalicType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ItalicType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ItalicType) #

gmapT :: (forall b. Data b => b -> b) -> ItalicType -> ItalicType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ItalicType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ItalicType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ItalicType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ItalicType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ItalicType -> m ItalicType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ItalicType -> m ItalicType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ItalicType -> m ItalicType #

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

Generic ItalicType Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep ItalicType :: Type -> Type #

Arbitrary ItalicType Source # 
Instance details

Defined in Data.Char.Core

Default ItalicType Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: ItalicType #

NFData ItalicType Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: ItalicType -> () #

Hashable ItalicType Source # 
Instance details

Defined in Data.Char.Core

type Rep ItalicType Source # 
Instance details

Defined in Data.Char.Core

type Rep ItalicType = D1 ('MetaData "ItalicType" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "NoItalic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Italic" 'PrefixI 'False) (U1 :: Type -> Type))

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

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

Data FontStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FontStyle -> c FontStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FontStyle #

toConstr :: FontStyle -> Constr #

dataTypeOf :: FontStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FontStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FontStyle) #

gmapT :: (forall b. Data b => b -> b) -> FontStyle -> FontStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FontStyle -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FontStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> FontStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FontStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FontStyle -> m FontStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FontStyle -> m FontStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FontStyle -> m FontStyle #

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

Generic FontStyle Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep FontStyle :: Type -> Type #

Arbitrary FontStyle Source # 
Instance details

Defined in Data.Char.Core

Default FontStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: FontStyle #

NFData FontStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: FontStyle -> () #

Hashable FontStyle Source # 
Instance details

Defined in Data.Char.Core

type Rep FontStyle Source # 
Instance details

Defined in Data.Char.Core

type Rep FontStyle = D1 ('MetaData "FontStyle" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "SansSerif" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Serif" 'PrefixI 'False) (U1 :: Type -> Type))

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.

isGreek :: Char -> Bool Source #

Checks if a charcter is a basic greek alphabetic character or a Greek-like symbol. The characters ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ 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>.

isNotReserved Source #

Arguments

:: Char

The given Character to check.

-> Bool

True if the given Character is not reserved; False otherwise.

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

Map characters from and to Enums

mapFromEnum Source #

Arguments

:: Enum a 
=> Int

The given offset value.

-> a

The given Enum value to convert to a Character.

-> Char

The character that corresponds to the given Enum object.

Map the given object with a type that is an instance of Enum to a Character with a given offset for the Character value.

mapToEnum Source #

Arguments

:: Enum a 
=> Int

The given offset value.

-> Char

The Character to map to an Enum object.

-> a

The given Enum object for the given Char.

Map the given Char object to an object with a type that is an instance of Enum with a given offset for the Character range.

mapToEnumSafe Source #

Arguments

:: forall a. (Bounded a, Enum a) 
=> Int

The given offset value.

-> Char

The given Character to map to an Enum object.

-> Maybe a

The given Enum object for the given Character wrapped in a Just if that exists; Nothing otherwise.

Map the given Char object to an object with a type that is an instance of Enum. It first checks if the mapping results in a value between the fromEnum values for minBound and maxBound.

liftNumberFrom Source #

Arguments

:: 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 Character wrapped in a Just if the number is between the offset and the maximum; Nothing otherwise.

Construct a function that maps digits to the character with the given value for the offset.

liftNumberFrom' Source #

Arguments

:: Int

The given offset value.

-> Int

The given Unicode value used for the offset.

-> Int

The given number to convert to a corresponding Character.

-> Char

The corresponding Character for the given mapping function.

Construct a function that maps digits to the character with the given value for the offset.

liftNumber Source #

Arguments

:: Int

The maximum value that can be mapped.

-> Int

The given Unicode value used for 0.

-> Int

The given digit to convert to a number between 0 and the maximum.

-> Maybe Char

The corresponding Character wrapped in a Just if the number is between 0 and 9; Nothing otherwise.

Construct a function that maps digits to the character with the given value for 0.

liftNumber' Source #

Arguments

:: Int

The given Unicode value used for 0.

-> Int

The given digit to convert.

-> Char

The corresponding Character, for numbers outside the 0-9 range, the result is unspecified.

Construct a function that maps digits to characters with the given value for 0.

liftDigit Source #

Arguments

:: Int

The given Unicode value used for 0.

-> Int

The given digit to convert to a number between 0 and 9.

-> Maybe Char

The corresponding Character wrapped in a Just if the number is between 0 and 9; Nothing otherwise.

Construct a function that maps digits to the character with the given value for 0.

liftDigit' Source #

Arguments

:: Int

The given Unicode value used for 0.

-> Int

The given digit to convert, must be between 0 and 9.

-> Char

The corresponding Character, for numbers outside the 0-9 range, the result is unspecified.

Construct a function that maps digits to characters with the given value for 0.

liftUppercase Source #

Arguments

:: Int

The given Unicode value for A.

-> Char

The given character to convert.

-> Maybe Char

The corresponding character wrapped in a Just if the given character is in the A-Z range; Nothing otherwise.

Construct a function that maps upper case alphabetic characters with the given value for A.

liftUppercase' Source #

Arguments

:: Int

The given Unicode value for A.

-> Char

The given upper case alphabetic value to convert.

-> Char

The corresponding character, if the given value is outside the A-Z range, the result is unspecified.

Construct a function that maps upper case alphabetic characters with the given value for A.

liftLowercase Source #

Arguments

:: Int

The given Unicode value for a.

-> Char

The given character to convert.

-> Maybe Char

The corresponding character wrapped in a Just if the given character is in the a-z range; Nothing otherwise.

Construct a function that maps lower case alphabetic characters with the given value for a.

liftLowercase' Source #

Arguments

:: Int

The given Unicode value for a.

-> Char

The given upper case alphabetic value to convert.

-> Char

The corresponding character, if the given value is outside the a-z range, the result is unspecified.

Construct a function that maps lower case alphabetic characters with the given value for a.

liftUpperLowercase Source #

Arguments

:: Int

The given Unicode value for A.

-> Int

The given Unicode value for a.

-> Char

The given character to convert.

-> Maybe Char

The corresponding character wrapped in a Just if the given character is in the A-Z,a-z range; Nothing otherwise.

Construct a function that maps lower case alphabetic characters with the given values for A and a.

liftUpperLowercase' Source #

Arguments

:: Int

The given Unicode value for A.

-> Int

The given Unicode value for a.

-> Char

The given character to convert.

-> Char

The corresponding character if the given character is in the A-Z,a-z range; unspecified otherwise.

Construct a function that maps lower case alphabetic characters with the given values for A and a.

Convert objects from and to Unicode Characters

class UnicodeCharacter a where Source #

A class from which objects can be derived that map to and from a single unicode character.

Minimal complete definition

toUnicodeChar, fromUnicodeChar

Methods

toUnicodeChar Source #

Arguments

:: a

The given object to convert to a Character.

-> Char

The equivalent Unicode Character.

Convert the given object to a Unicode Character.

fromUnicodeChar Source #

Arguments

:: Char

The given Character to convert to an element.

-> Maybe a

An element if the given Character maps to an element wrapped in a Just; Nothing otherwise.

Convert the given Character to an object wrapped in a Just data constructor if that exists; Nothing otherwise.

fromUnicodeChar' Source #

Arguments

:: Char

The given Character to convert to an element.

-> a

The given element that is equivalent to the given Character.

Convert the given Character to an object. If the Character does not map on an element, the behavior is unspecified, it can for example result in an error.

Instances

Instances details
UnicodeCharacter Char Source # 
Instance details

Defined in Data.Char.Core

UnicodeCharacter CombiningCharacter Source # 
Instance details

Defined in Data.Char.Combining

UnicodeCharacter CardSuit Source # 
Instance details

Defined in Data.Char.Card

UnicodeCharacter BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

UnicodeCharacter Currency Source # 
Instance details

Defined in Data.Char.Currency

UnicodeCharacter DieValue Source # 
Instance details

Defined in Data.Char.Dice

UnicodeCharacter MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeCharacter Zodiac Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeCharacter SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeCharacter Clock Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeCharacter MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

UnicodeCharacter RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

UnicodeCharacter Klingon Source # 
Instance details

Defined in Data.Char.Private.Klingon

UnicodeCharacter (Oriented (Domino (Maybe DieValue))) Source # 
Instance details

Defined in Data.Char.Domino

UnicodeCharacter (Oriented (Domino DieValue)) Source # 
Instance details

Defined in Data.Char.Domino

UnicodeCharacter (Block Bool) Source # 
Instance details

Defined in Data.Char.Block

UnicodeCharacter (Braille Bool) Source # 
Instance details

Defined in Data.Char.Braille

UnicodeCharacter (Braille6 Bool) Source # 
Instance details

Defined in Data.Char.Braille

UnicodeCharacter (Parts Bool) Source # 
Instance details

Defined in Data.Char.Frame

UnicodeCharacter (Parts Weight) Source # 
Instance details

Defined in Data.Char.Frame

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.

Minimal complete definition

Nothing

Methods

toUnicodeText Source #

Arguments

:: a

The given object to convert to a Text object.

-> Text

A Text object that is the Unicode representation of the element.

Convert the given object to a Text object.

fromUnicodeText Source #

Arguments

:: Text

The given Text to convert to an object.

-> Maybe a

The equivalent object wrapped in a Just data constructor if it exists; Nothing otherwise.

Convert the given Text to an object wrapped in a Just data constructor if that exists; Nothing otherwise.

fromUnicodeText' Source #

Arguments

:: Text

The given Text to convert to an object.

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

Instances

Instances details
UnicodeText Char Source # 
Instance details

Defined in Data.Char.Core

UnicodeText Text Source # 
Instance details

Defined in Data.Char.Core

UnicodeText CombiningCharacter Source # 
Instance details

Defined in Data.Char.Combining

UnicodeText CardSuit Source # 
Instance details

Defined in Data.Char.Card

UnicodeText BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

UnicodeText Currency Source # 
Instance details

Defined in Data.Char.Currency

UnicodeText DieValue Source # 
Instance details

Defined in Data.Char.Dice

UnicodeText MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText Zodiac Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText Gender Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText BloodType Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText Clock Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText SubFlag Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText Flag Source # 
Instance details

Defined in Data.Char.Emoji

UnicodeText MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

UnicodeText RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

UnicodeText Klingon Source # 
Instance details

Defined in Data.Char.Private.Klingon

UnicodeText [Char] Source # 
Instance details

Defined in Data.Char.Core

UnicodeText (Oriented (Domino (Maybe DieValue))) Source # 
Instance details

Defined in Data.Char.Domino

UnicodeText (Oriented (Domino DieValue)) Source # 
Instance details

Defined in Data.Char.Domino

UnicodeText (Block Bool) Source # 
Instance details

Defined in Data.Char.Block

UnicodeText (Braille Bool) Source # 
Instance details

Defined in Data.Char.Braille

UnicodeText (Braille6 Bool) Source # 
Instance details

Defined in Data.Char.Braille

UnicodeText (Parts Bool) Source # 
Instance details

Defined in Data.Char.Frame

UnicodeText (Parts Weight) Source # 
Instance details

Defined in Data.Char.Frame

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

Methods

mirrorHorizontal Source #

Arguments

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

Instances details
MirrorHorizontal (Block a) Source # 
Instance details

Defined in Data.Char.Block

MirrorHorizontal (Braille a) Source # 
Instance details

Defined in Data.Char.Braille

MirrorHorizontal (Braille6 a) Source # 
Instance details

Defined in Data.Char.Braille

MirrorHorizontal (Parts a) Source # 
Instance details

Defined in Data.Char.Frame

MirrorHorizontal (Vertical a) Source # 
Instance details

Defined in Data.Char.Frame

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

Methods

mirrorVertical Source #

Arguments

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

Instances details
MirrorVertical MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji

MirrorVertical (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

mirrorVertical :: Block a -> Block a Source #

MirrorVertical (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

mirrorVertical :: Row a -> Row a Source #

MirrorVertical (Braille a) Source # 
Instance details

Defined in Data.Char.Braille

MirrorVertical (Braille6 a) Source # 
Instance details

Defined in Data.Char.Braille

MirrorVertical (Parts a) Source # 
Instance details

Defined in Data.Char.Frame

Methods

mirrorVertical :: Parts a -> Parts a Source #

MirrorVertical (Horizontal a) Source # 
Instance details

Defined in Data.Char.Frame

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

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

Data PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlusStyle -> c PlusStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlusStyle #

toConstr :: PlusStyle -> Constr #

dataTypeOf :: PlusStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PlusStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlusStyle) #

gmapT :: (forall b. Data b => b -> b) -> PlusStyle -> PlusStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlusStyle -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlusStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlusStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlusStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlusStyle -> m PlusStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlusStyle -> m PlusStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlusStyle -> m PlusStyle #

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

Generic PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Associated Types

type Rep PlusStyle :: Type -> Type #

Arbitrary PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Default PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

def :: PlusStyle #

NFData PlusStyle Source # 
Instance details

Defined in Data.Char.Core

Methods

rnf :: PlusStyle -> () #

Hashable PlusStyle Source # 
Instance details

Defined in Data.Char.Core

type Rep PlusStyle Source # 
Instance details

Defined in Data.Char.Core

type Rep PlusStyle = D1 ('MetaData "PlusStyle" "Data.Char.Core" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "WithoutPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WithPlus" 'PrefixI 'False) (U1 :: Type -> Type))

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.