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

Description

Unicode has two types of emoji for the moon: it contains eight emoji for the moonphase, and four emoji where the moon has a face.

Synopsis

Moon phase emoji

data MoonPhase Source #

A data type that defines the eight different moon phases, and is an instance of UnicodeCharacter to convert these to the corresponding Unicode character.

Constructors

NewMoon

The new moon, the first phase of the moon represented by 🌑.

WaxingCrescent

The waxing crescent, the second phase of the moon represented by 🌒.

FirstQuarter

The first quarter, the third phase of the moon represented by 🌓.

WaxingGibbous

The waxing gibbous, the fourth phase of the moon represented by 🌔.

FullMoon

The full moon, the fifth phase of the moon represented by 🌕.

WaningGibbous

The waning gibbous, the sixth phase of the moon represented by 🌖.

ThirdQuarter

The third quarter, the seventh phase of the moon represented by 🌗.

WaningCrescent

The waning crescent, the eighth phase of the moon represented by 🌘.

Instances

Instances details
Arbitrary MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Data MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Methods

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

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

toConstr :: MoonPhase -> Constr #

dataTypeOf :: MoonPhase -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Enum MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Generic MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Associated Types

type Rep MoonPhase :: Type -> Type #

Read MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Show MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

NFData MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Methods

rnf :: MoonPhase -> () #

Eq MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Ord MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Hashable MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

MirrorVertical MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

UnicodeCharacter MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

UnicodeText MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

type Rep MoonPhase Source # 
Instance details

Defined in Data.Char.Emoji.Moon

type Rep MoonPhase = D1 ('MetaData "MoonPhase" "Data.Char.Emoji.Moon" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (((C1 ('MetaCons "NewMoon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WaxingCrescent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FirstQuarter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WaxingGibbous" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FullMoon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WaningGibbous" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ThirdQuarter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WaningCrescent" 'PrefixI 'False) (U1 :: Type -> Type))))

Moon faces emoji

data MoonFace Source #

A data type that defines the four different moon faces (not to be confused with phases). This data type is an instance of the UnicodeCharacter type class to convert these to the corresponding Unicode character.

Constructors

NewMoonFace

The new moon, the first phase of the moon faces represented by 🌚.

FirstQuarterFace

The first quarter, the second phase of the moon faces represented by 🌛.

FullMoonFace

The full moon, the third phase of the moon faces represented by 🌝.

ThirdQuarterFace

The third quarter, the fourth phase of the moon faces represented by 🌜.

Instances

Instances details
Arbitrary MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Data MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Methods

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

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

toConstr :: MoonFace -> Constr #

dataTypeOf :: MoonFace -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Enum MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Generic MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Associated Types

type Rep MoonFace :: Type -> Type #

Methods

from :: MoonFace -> Rep MoonFace x #

to :: Rep MoonFace x -> MoonFace #

Read MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Show MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

NFData MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Methods

rnf :: MoonFace -> () #

Eq MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Ord MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Hashable MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

Methods

hashWithSalt :: Int -> MoonFace -> Int #

hash :: MoonFace -> Int #

MirrorVertical MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

UnicodeCharacter MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

UnicodeText MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

type Rep MoonFace Source # 
Instance details

Defined in Data.Char.Emoji.Moon

type Rep MoonFace = D1 ('MetaData "MoonFace" "Data.Char.Emoji.Moon" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) ((C1 ('MetaCons "NewMoonFace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FirstQuarterFace" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FullMoonFace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThirdQuarterFace" 'PrefixI 'False) (U1 :: Type -> Type)))

moonPhaseForDay Source #

Arguments

:: Day

The Day for which we want to deterime the moon phase.

-> MoonPhase

The corresponding MoonPhase icon

Determine the corresponding MoonPhase emoji for a given day. The algorithm is based on upon a subsystems publication https://www.subsystems.us/uploads/9/8/9/4/98948044/moonphase.pdf