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

Description

Unicode has a block named Miscellaneous Symbols that includes unicode characters for boxes that are empty, contain a check or a cross, this module aims to make it more convenient to render these.

Synopsis

Represent a ballot box.

data BallotBox Source #

A datatype that represents the different types of ballot boxes.

Constructors

Empty

The box is empty, this is represented with ☐.

Check

The box has a check, this is represented with ☑.

Cross

The box has a cross, this is represented with ☒.

Instances

Instances details
Arbitrary BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Data BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Methods

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

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

toConstr :: BallotBox -> Constr #

dataTypeOf :: BallotBox -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Enum BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Generic BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Associated Types

type Rep BallotBox :: Type -> Type #

Read BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Show BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

NFData BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Methods

rnf :: BallotBox -> () #

Eq BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Ord BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

Hashable BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

UnicodeCharacter BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

UnicodeText BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

type Rep BallotBox Source # 
Instance details

Defined in Data.Char.BallotBox

type Rep BallotBox = D1 ('MetaData "BallotBox" "Data.Char.BallotBox" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Check" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cross" 'PrefixI 'False) (U1 :: Type -> Type)))

Convert a boolean to a ballot box.

toCheckBox Source #

Arguments

:: Bool

The given Bool that determines if the box contains a Check.

-> BallotBox

The corresponding BallotBox.

Convert the given Boolean to a BallotBox that is Empty, or contains a Check.

toCrossBox Source #

Arguments

:: Bool

The given Bool that determines if the box contains a Cross.

-> BallotBox

The corresponding BallotBox.

Convert the given Boolean to a BallotBox that is Empty, or contains a Cross.