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

Description

Unicode has emoji's for hands. In this module we make it more convenient to render hand gestures with a specific skin color.

Synopsis

Documentation

data SingleCharHandGesture Source #

A datatype that constructs hand gestures that correspond with a single Character.

Constructors

WavingHand

A waving hand, this is denoted with 👋.

RaisedBackOfHand

The raised back of a hand, this is denoted with 🤚.

RaisedHand

A raised hand, this is denoted with ✋.

VulcanSalute

The Vulcan salute, this is denoted with 🖖.

OkHandSign

The okay hand sign, this is denoted with 👌.

PinchedFingers

The pinched fingers gesture, this is denoted with 🤌.

PinchingHand

The pinching hand gesture, this is denoted with 🤏.

CrossedFingers

The crossed fingers gesture, this is denoted with 🤞.

LoveYouGesture

The love you gesture, this is denoted with 🤟.

SignOfTheHorns

The sign of the horns, this is denoted with 🤘.

CallMeHand

The call me hand sign, this is denoted with 🤙.

Instances

Instances details
Arbitrary SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Data SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Methods

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

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

toConstr :: SingleCharHandGesture -> Constr #

dataTypeOf :: SingleCharHandGesture -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Enum SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Generic SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Associated Types

type Rep SingleCharHandGesture :: Type -> Type #

Read SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Show SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

NFData SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Methods

rnf :: SingleCharHandGesture -> () #

Eq SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Ord SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Hashable SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

UnicodeCharacter SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

UnicodeText SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

WithSkinColorModifierUnicodeText SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

type Rep SingleCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

type Rep SingleCharHandGesture = D1 ('MetaData "SingleCharHandGesture" "Data.Char.Emoji.Hand" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) ((((C1 ('MetaCons "WavingHand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RaisedBackOfHand" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RaisedHand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VulcanSalute" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OkHandSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PinchedFingers" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PinchingHand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CrossedFingers" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "LoveYouGesture" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SignOfTheHorns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CallMeHand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MiddleFinger" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ThumbsUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThumbsDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RaisedFist" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FistedHand" 'PrefixI 'False) (U1 :: Type -> Type)))))

data MultiCharHandGesture Source #

Emoji with hands that map on a sequence of characters instead of one character.

Instances

Instances details
Arbitrary MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Data MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Methods

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

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

toConstr :: MultiCharHandGesture -> Constr #

dataTypeOf :: MultiCharHandGesture -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Enum MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Generic MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Associated Types

type Rep MultiCharHandGesture :: Type -> Type #

Read MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Show MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

NFData MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Methods

rnf :: MultiCharHandGesture -> () #

Eq MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Ord MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

Hashable MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

UnicodeText MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

WithSkinColorModifierUnicodeText MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

type Rep MultiCharHandGesture Source # 
Instance details

Defined in Data.Char.Emoji.Hand

type Rep MultiCharHandGesture = D1 ('MetaData "MultiCharHandGesture" "Data.Char.Emoji.Hand" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "RaisedHandWithFingersSplayed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VictoryHand" 'PrefixI 'False) (U1 :: Type -> Type))

pattern SpockHand :: SingleCharHandGesture Source #

A pattern synonym for the VulcanSalute.

pattern HornsSign :: SingleCharHandGesture Source #

A pattern synonym for SignOfTheHorns.