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

Description

Unicode has emojis for the twelve zodiac signs. In this module a data type is used to present the zodiac emoji and also defines pattern synonyms for these.

Synopsis

Zodiac datatype

data Zodiac Source #

A data type to deal with the zodiac sign emoji. The data type lists the different zodiac signs as data constructors, and the instance of the UnicodeCharacter allows to convert it from and to a Character.

Constructors

Aries

The aries zodiac sign, ram in English, is denoted as ♈.

Taurus

The taurus zodiac sign, bull in English, is denoted as ♉.

Gemini

The gemini zodiac sign, twins in English, is denoted as ♊.

Cancer

The cancer zodiac sign, crab in English, is denoted as ♋.

Leo

The leo zodiac sign, lion in English, is denoted as ♌.

Virgo

The virgo zodiac sign, maiden in English, is denoted as ♍.

Libra

The libra zodiac sign, scales in English, is denoted as ♎.

Scorpio

The scorpio zodiac sign, scorpion in English, is denoted as ♏.

Sagittarius

The saggitarius zodiac sign, archer in English, is denoted as ♐.

Capricorn

The capricorn zodiac sign, sea-goat in English, is denoted as ♑.

Aquarius

The aquarius zodiac sign, water-bearer in English, is denoted as ♒.

Pisces

The pices zodiac sign, fish in English, is denoted as ♓.

Instances

Instances details
Arbitrary Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Data Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Methods

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

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

toConstr :: Zodiac -> Constr #

dataTypeOf :: Zodiac -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Enum Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Generic Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Associated Types

type Rep Zodiac :: Type -> Type #

Methods

from :: Zodiac -> Rep Zodiac x #

to :: Rep Zodiac x -> Zodiac #

Read Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Show Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

NFData Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Methods

rnf :: Zodiac -> () #

Eq Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Methods

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

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

Ord Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Hashable Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

Methods

hashWithSalt :: Int -> Zodiac -> Int #

hash :: Zodiac -> Int #

UnicodeCharacter Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

UnicodeText Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

type Rep Zodiac Source # 
Instance details

Defined in Data.Char.Emoji.Zodiac

type Rep Zodiac = D1 ('MetaData "Zodiac" "Data.Char.Emoji.Zodiac" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (((C1 ('MetaCons "Aries" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Taurus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gemini" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Cancer" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Leo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Virgo" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Libra" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Scorpio" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sagittarius" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Capricorn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Aquarius" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pisces" 'PrefixI 'False) (U1 :: Type -> Type)))))

Pattern aliasses

pattern Ram :: Zodiac Source #

The English name for the Aries zodiac sign.

pattern Bull :: Zodiac Source #

The English name for the Taurus zodiac sign.

pattern Twins :: Zodiac Source #

The English name for the Gemini zodiac sign.

pattern Crab :: Zodiac Source #

The English name for the Cancer zodiac sign.

pattern Lion :: Zodiac Source #

The English name for the Leo zodiac sign.

pattern Maiden :: Zodiac Source #

The English name for the Virgo zodiac sign.

pattern Scales :: Zodiac Source #

The English name for the Libra zodiac sign.

pattern Scorpius :: Zodiac Source #

The name of the constellation of the Scorpio zodiac sign.

pattern Scorpion :: Zodiac Source #

The English name for the Scorpio zodiac sign.

pattern Centaur :: Zodiac Source #

An English name for the Sagittarius zodiac sign.

pattern Archer :: Zodiac Source #

An English name for the Sagittarius zodiac sign.

pattern Capricornus :: Zodiac Source #

The name of the constellation of the Capricorn zodiac sign.

pattern MountainGoat :: Zodiac Source #

An English name for the Capricorn zodiac sign.

pattern GoatHorned :: Zodiac Source #

An English name for the Capricorn zodiac sign.

pattern SeaGoat :: Zodiac Source #

An English name for the Capricorn zodiac sign.

pattern WaterBearer :: Zodiac Source #

The English name for the Aquarius zodiac sign.

pattern Fish :: Zodiac Source #

The English name for the Pisces zodiac sign.