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

Contents

Description

The emoji have 24 clock emoji, each time with 30 minutes difference.

Synopsis

Clock emoji

data Clock Source #

A Clock object that can be converted to a unicode character that displays a clock with the given time. The Clock has an hours field that contains the given hours between 0 and 12, and a minutes30 field that if True, means that the clock is half past that hour.

Instances

Instances details
Arbitrary Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Methods

arbitrary :: Gen Clock #

shrink :: Clock -> [Clock] #

Data Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Methods

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

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

toConstr :: Clock -> Constr #

dataTypeOf :: Clock -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Enum Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Generic Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Associated Types

type Rep Clock :: Type -> Type #

Methods

from :: Clock -> Rep Clock x #

to :: Rep Clock x -> Clock #

Read Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Show Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Methods

showsPrec :: Int -> Clock -> ShowS #

show :: Clock -> String #

showList :: [Clock] -> ShowS #

NFData Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Methods

rnf :: Clock -> () #

Eq Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Methods

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

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

Ord Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Methods

compare :: Clock -> Clock -> Ordering #

(<) :: Clock -> Clock -> Bool #

(<=) :: Clock -> Clock -> Bool #

(>) :: Clock -> Clock -> Bool #

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

max :: Clock -> Clock -> Clock #

min :: Clock -> Clock -> Clock #

Hashable Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

Methods

hashWithSalt :: Int -> Clock -> Int #

hash :: Clock -> Int #

UnicodeCharacter Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

UnicodeText Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

type Rep Clock Source # 
Instance details

Defined in Data.Char.Emoji.Clock

type Rep Clock = D1 ('MetaData "Clock" "Data.Char.Emoji.Clock" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Clock" 'PrefixI 'True) (S1 ('MetaSel ('Just "hours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "minutes30") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

hours :: Clock -> Int Source #

The number of hours on the given clock. Is between 0 and 12. For 0, the minutes30 is True; and for 12, the minutes30 is False.

minutes30 :: Clock -> Bool Source #

Is True if it is half past the given hour on the Clock.

clock Source #

Arguments

:: Int

The given hour of the clock, can be any value, but will be set between 1 and 12.

-> Bool

A Boolean that indicates if it is half past that hour, so True means we add 30 minutes.

-> Clock

A clock object that represents the time that is passed through an hour and .

Construct a Clock object with the given number of hours, and a Boolean that indicates if it is half past that hour. The function will ensure that the hours are between 0 and 12 (both inclusive). For half past 12, we use half past 0, for 12 hours, we use simply 12.

closestClock Source #

Arguments

:: Int

The number of hours.

-> Int

The number of minutes, must be between 0 and 60.

-> Clock

The clock object that is the closest to the given hours and minutes.

Generate the Clock object that is the closest to the given hours and minutes.