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

Data.Char.Emoji.SkinColor

Description

For several emoji, one can specify the color of the skin of the person(s) of the emoji. This module defines the skin color modifiers together with its values on the Fitzpatrick scale.

Synopsis

Skin color modifier

data SkinColorModifier Source #

Some emoji deal with people. One can change the color of the skin with the SkinColorModifier. For the skin color, the /Fitzpatrick scale/ is used. A numerical classification system for skin types.

Constructors

Light

An emoji modifier that applies Fitzpatrick skin type one or two to the Emoji.

MediumLight

An emoji modifier that applies Fitzpatrick skin type three to the Emoji.

Medium

An emoji modifier that applies Fitzpatrick skin type four to the Emoji.

MediumDark

An emoji modifier that applies Fitzpatrick skin type five to the Emoji.

Dark

An emoji modifier that applies Fitzpatrick skin type six to the Emoji.

Instances

Instances details
Arbitrary SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Data SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Methods

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

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

toConstr :: SkinColorModifier -> Constr #

dataTypeOf :: SkinColorModifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Enum SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Generic SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Associated Types

type Rep SkinColorModifier :: Type -> Type #

Read SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Show SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

NFData SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Methods

rnf :: SkinColorModifier -> () #

Eq SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Ord SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

Hashable SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

UnicodeCharacter SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

UnicodeText SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

type Rep SkinColorModifier Source # 
Instance details

Defined in Data.Char.Emoji.SkinColor

type Rep SkinColorModifier = D1 ('MetaData "SkinColorModifier" "Data.Char.Emoji.SkinColor" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) ((C1 ('MetaCons "Light" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MediumLight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Medium" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MediumDark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Dark" 'PrefixI 'False) (U1 :: Type -> Type))))

type OptionalSkinColorModifier = Maybe SkinColorModifier Source #

For emoji often the skin color is optional: in case there is no skin color specified, the emoji have often a yellow skin color.

fromFitzpatrick Source #

Arguments

:: Integral i 
=> i

The given Fitzpatrick skin type.

-> Maybe SkinColorModifier

The corresponding SkinColorModifier wrapped in a Just; Nothing if no such modifier exists.

Convert the given Fitzpatrick skin type to the corresponding SkinColorModifier wrapped in a Just, if no such SkinColorModifier exists, Nothing is returned.

isSkinColorModifier Source #

Arguments

:: Char

The given Character to check.

-> Bool

True if the given Character is a skin color modifier, False otherwise.

Check if the given Character is a skin color modifier.

Create emoji with a SkinColorModifier

class UnicodeText a => WithSkinColorModifierUnicodeText a where Source #

A typeclass where one can specify that the object can be rendered with a given skin color modifier.

Minimal complete definition

Nothing

Methods

withSkinModifier Source #

Arguments

:: a

The given item to render to a unicode Text object.

-> SkinColorModifier

The given skin color modifier to apply.

-> Text

The corresponding Text where we applied the given SkinColorModifier.

Apply the given SkinColorModifier to the item and obtain a Text object where the item has been modified with the SkinColorModifier.

withOptionalSkinModifier Source #

Arguments

:: a

The given item to render to a unicode Text object.

-> OptionalSkinColorModifier

The given optional skin color modifier.

-> Text

The corresponding Text where we applied the given SkinColorModifier.

Apply the given SkinColorModifier to the item given it is not Nothing such that the object is rendered with the given skin color modifier.

withoutOptionalSkinModifier Source #

Arguments

:: Text

The given Text object that should be decoded.

-> Maybe (a, OptionalSkinColorModifier)

An optional 2-tuple with the item that has been read, and an optional SkinColorModifier.

Convert the given Text to an item with an OptionalSkinColorModifier that might have been applied.

withSkinModifier' Source #

Arguments

:: Text

The given Text object where we want to specify the skin color.

-> SkinColorModifier

The givenSkinColorModifier to apply.

-> Text

The given Text object combined with the given SkinColorModifier.

Append the given Text object with the Unicode character to modify its skin color.

withOptionalSkinModifier' Source #

Arguments

:: Text

The given Text object where we want to specify the skin color.

-> OptionalSkinColorModifier

The givenOptionalSkinColorModifier to apply.

-> Text

The given Text object combined with the given SkinColorModifier.

Append the given Text object with the Unicode character to modify its skin color. If Nothing, then no modification is applied.

withoutOptionalSkinModifier' Source #

Arguments

:: Text

The given Text to decompose.

-> (Text, OptionalSkinColorModifier)

A 2-tuple where the first item is the remaining Text and where the second item is an optioanl SkinColorModifier.

Convert the given Text object to a wrapped Text object with an OptionalSkinColorModifier.

Pattern synonyms for the SkinColorModifier elements

pattern FitzpatrickI :: SkinColorModifier Source #

The SkinColorModifier that corresponds to type one of the /Fitzpatrick scale/.

pattern FitzpatrickII :: SkinColorModifier Source #

The SkinColorModifier that corresponds to type two of the /Fitzpatrick scale/.

pattern FitzpatrickIII :: SkinColorModifier Source #

The SkinColorModifier that corresponds to type three of the /Fitzpatrick scale/.

pattern FitzpatrickIV :: SkinColorModifier Source #

The SkinColorModifier that corresponds to type four of the /Fitzpatrick scale/.

pattern FitzpatrickV :: SkinColorModifier Source #

The SkinColorModifier that corresponds to type five of the /Fitzpatrick scale/.

pattern FitzpatrickVI :: SkinColorModifier Source #

The SkinColorModifier that corresponds to type six of the /Fitzpatrick scale/.