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

Description

Unicode has 2-by-2 blocks, this module aims to make it more convenient to render such blocks.

Synopsis

Datastructures to store the state of the frame.

data Row a Source #

A data type that determines the state of the row in a block. it determines the left and the right part of the row of the block.

Constructors

Row 

Fields

  • left :: a

    The left part of a row of the block.

  • right :: a

    The right part of the row of the block.

Instances

Instances details
Arbitrary1 Row Source # 
Instance details

Defined in Data.Char.Block

Methods

liftArbitrary :: Gen a -> Gen (Row a) #

liftShrink :: (a -> [a]) -> Row a -> [Row a] #

Foldable Row Source # 
Instance details

Defined in Data.Char.Block

Methods

fold :: Monoid m => Row m -> m #

foldMap :: Monoid m => (a -> m) -> Row a -> m #

foldMap' :: Monoid m => (a -> m) -> Row a -> m #

foldr :: (a -> b -> b) -> b -> Row a -> b #

foldr' :: (a -> b -> b) -> b -> Row a -> b #

foldl :: (b -> a -> b) -> b -> Row a -> b #

foldl' :: (b -> a -> b) -> b -> Row a -> b #

foldr1 :: (a -> a -> a) -> Row a -> a #

foldl1 :: (a -> a -> a) -> Row a -> a #

toList :: Row a -> [a] #

null :: Row a -> Bool #

length :: Row a -> Int #

elem :: Eq a => a -> Row a -> Bool #

maximum :: Ord a => Row a -> a #

minimum :: Ord a => Row a -> a #

sum :: Num a => Row a -> a #

product :: Num a => Row a -> a #

Eq1 Row Source # 
Instance details

Defined in Data.Char.Block

Methods

liftEq :: (a -> b -> Bool) -> Row a -> Row b -> Bool #

Ord1 Row Source # 
Instance details

Defined in Data.Char.Block

Methods

liftCompare :: (a -> b -> Ordering) -> Row a -> Row b -> Ordering #

Traversable Row Source # 
Instance details

Defined in Data.Char.Block

Methods

traverse :: Applicative f => (a -> f b) -> Row a -> f (Row b) #

sequenceA :: Applicative f => Row (f a) -> f (Row a) #

mapM :: Monad m => (a -> m b) -> Row a -> m (Row b) #

sequence :: Monad m => Row (m a) -> m (Row a) #

Applicative Row Source # 
Instance details

Defined in Data.Char.Block

Methods

pure :: a -> Row a #

(<*>) :: Row (a -> b) -> Row a -> Row b #

liftA2 :: (a -> b -> c) -> Row a -> Row b -> Row c #

(*>) :: Row a -> Row b -> Row b #

(<*) :: Row a -> Row b -> Row a #

Functor Row Source # 
Instance details

Defined in Data.Char.Block

Methods

fmap :: (a -> b) -> Row a -> Row b #

(<$) :: a -> Row b -> Row a #

NFData1 Row Source # 
Instance details

Defined in Data.Char.Block

Methods

liftRnf :: (a -> ()) -> Row a -> () #

Hashable1 Row Source # 
Instance details

Defined in Data.Char.Block

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Row a -> Int #

Generic1 Row Source # 
Instance details

Defined in Data.Char.Block

Associated Types

type Rep1 Row :: k -> Type #

Methods

from1 :: forall (a :: k). Row a -> Rep1 Row a #

to1 :: forall (a :: k). Rep1 Row a -> Row a #

Arbitrary a => Arbitrary (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

arbitrary :: Gen (Row a) #

shrink :: Row a -> [Row a] #

Data a => Data (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

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

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

toConstr :: Row a -> Constr #

dataTypeOf :: Row a -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded a => Bounded (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

minBound :: Row a #

maxBound :: Row a #

Generic (Row a) Source # 
Instance details

Defined in Data.Char.Block

Associated Types

type Rep (Row a) :: Type -> Type #

Methods

from :: Row a -> Rep (Row a) x #

to :: Rep (Row a) x -> Row a #

Read a => Read (Row a) Source # 
Instance details

Defined in Data.Char.Block

Show a => Show (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

showsPrec :: Int -> Row a -> ShowS #

show :: Row a -> String #

showList :: [Row a] -> ShowS #

NFData a => NFData (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

rnf :: Row a -> () #

Eq a => Eq (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

(==) :: Row a -> Row a -> Bool #

(/=) :: Row a -> Row a -> Bool #

Ord a => Ord (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

compare :: Row a -> Row a -> Ordering #

(<) :: Row a -> Row a -> Bool #

(<=) :: Row a -> Row a -> Bool #

(>) :: Row a -> Row a -> Bool #

(>=) :: Row a -> Row a -> Bool #

max :: Row a -> Row a -> Row a #

min :: Row a -> Row a -> Row a #

Hashable a => Hashable (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

hashWithSalt :: Int -> Row a -> Int #

hash :: Row a -> Int #

MirrorVertical (Row a) Source # 
Instance details

Defined in Data.Char.Block

Methods

mirrorVertical :: Row a -> Row a Source #

type Rep1 Row Source # 
Instance details

Defined in Data.Char.Block

type Rep1 Row = D1 ('MetaData "Row" "Data.Char.Block" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Row" 'PrefixI 'True) (S1 ('MetaSel ('Just "left") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "right") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Row a) Source # 
Instance details

Defined in Data.Char.Block

type Rep (Row a) = D1 ('MetaData "Row" "Data.Char.Block" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Row" 'PrefixI 'True) (S1 ('MetaSel ('Just "left") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "right") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

rowValue Source #

Arguments

:: Row Bool

The given Row of Bools to convert.

-> Int

The corresponding numerical value.

Convert the given Row of Booleans to an Int where the left Bool has value 1, and the right one has value two. The four different Rows thus are mapped to integers from zero to three (both inclusive).

toRow Source #

Arguments

:: Int

The given number to convert.

-> Maybe (Row Bool)

The corresponding Row of Bools.

Convert the given number to a Row of Bools wrapped in a Just. if the value is out of bounds, Nothing is returned.

toRow' Source #

Arguments

:: Int

The given number to convert.

-> Row Bool

The corresponding Row of Bools.

Convert the given number to a Row of Bools. If the value is out of bounds, it is unspecified what will happen.

pattern EmptyRow :: Row Bool Source #

A pattern synonym for a Row where both the left and right subpart are False.

pattern FullRow :: Row Bool Source #

A pattern synonym for a Row where both the left and right subpart are True.

pattern LeftRow :: Row Bool Source #

A pattern synonym for a Row where the left part is set to True, and the right part is set to False.

pattern RightRow :: Row Bool Source #

A pattern synonym for a Row where the left part is set to False, and the right part is set to True.

data Block a Source #

A data type that determines the state of the four subparts of the block.

Constructors

Block 

Fields

  • upper :: Row a

    The upper part of the block.

  • lower :: Row a

    The lower part of the block.

Instances

Instances details
Arbitrary1 Block Source # 
Instance details

Defined in Data.Char.Block

Methods

liftArbitrary :: Gen a -> Gen (Block a) #

liftShrink :: (a -> [a]) -> Block a -> [Block a] #

Foldable Block Source # 
Instance details

Defined in Data.Char.Block

Methods

fold :: Monoid m => Block m -> m #

foldMap :: Monoid m => (a -> m) -> Block a -> m #

foldMap' :: Monoid m => (a -> m) -> Block a -> m #

foldr :: (a -> b -> b) -> b -> Block a -> b #

foldr' :: (a -> b -> b) -> b -> Block a -> b #

foldl :: (b -> a -> b) -> b -> Block a -> b #

foldl' :: (b -> a -> b) -> b -> Block a -> b #

foldr1 :: (a -> a -> a) -> Block a -> a #

foldl1 :: (a -> a -> a) -> Block a -> a #

toList :: Block a -> [a] #

null :: Block a -> Bool #

length :: Block a -> Int #

elem :: Eq a => a -> Block a -> Bool #

maximum :: Ord a => Block a -> a #

minimum :: Ord a => Block a -> a #

sum :: Num a => Block a -> a #

product :: Num a => Block a -> a #

Eq1 Block Source # 
Instance details

Defined in Data.Char.Block

Methods

liftEq :: (a -> b -> Bool) -> Block a -> Block b -> Bool #

Ord1 Block Source # 
Instance details

Defined in Data.Char.Block

Methods

liftCompare :: (a -> b -> Ordering) -> Block a -> Block b -> Ordering #

Traversable Block Source # 
Instance details

Defined in Data.Char.Block

Methods

traverse :: Applicative f => (a -> f b) -> Block a -> f (Block b) #

sequenceA :: Applicative f => Block (f a) -> f (Block a) #

mapM :: Monad m => (a -> m b) -> Block a -> m (Block b) #

sequence :: Monad m => Block (m a) -> m (Block a) #

Applicative Block Source # 
Instance details

Defined in Data.Char.Block

Methods

pure :: a -> Block a #

(<*>) :: Block (a -> b) -> Block a -> Block b #

liftA2 :: (a -> b -> c) -> Block a -> Block b -> Block c #

(*>) :: Block a -> Block b -> Block b #

(<*) :: Block a -> Block b -> Block a #

Functor Block Source # 
Instance details

Defined in Data.Char.Block

Methods

fmap :: (a -> b) -> Block a -> Block b #

(<$) :: a -> Block b -> Block a #

NFData1 Block Source # 
Instance details

Defined in Data.Char.Block

Methods

liftRnf :: (a -> ()) -> Block a -> () #

Hashable1 Block Source # 
Instance details

Defined in Data.Char.Block

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Block a -> Int #

Generic1 Block Source # 
Instance details

Defined in Data.Char.Block

Associated Types

type Rep1 Block :: k -> Type #

Methods

from1 :: forall (a :: k). Block a -> Rep1 Block a #

to1 :: forall (a :: k). Rep1 Block a -> Block a #

Arbitrary a => Arbitrary (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

arbitrary :: Gen (Block a) #

shrink :: Block a -> [Block a] #

Data a => Data (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

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

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

toConstr :: Block a -> Constr #

dataTypeOf :: Block a -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded a => Bounded (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

minBound :: Block a #

maxBound :: Block a #

Generic (Block a) Source # 
Instance details

Defined in Data.Char.Block

Associated Types

type Rep (Block a) :: Type -> Type #

Methods

from :: Block a -> Rep (Block a) x #

to :: Rep (Block a) x -> Block a #

Read a => Read (Block a) Source # 
Instance details

Defined in Data.Char.Block

Show a => Show (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

showsPrec :: Int -> Block a -> ShowS #

show :: Block a -> String #

showList :: [Block a] -> ShowS #

NFData a => NFData (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

rnf :: Block a -> () #

Eq a => Eq (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

(==) :: Block a -> Block a -> Bool #

(/=) :: Block a -> Block a -> Bool #

Ord a => Ord (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

compare :: Block a -> Block a -> Ordering #

(<) :: Block a -> Block a -> Bool #

(<=) :: Block a -> Block a -> Bool #

(>) :: Block a -> Block a -> Bool #

(>=) :: Block a -> Block a -> Bool #

max :: Block a -> Block a -> Block a #

min :: Block a -> Block a -> Block a #

Hashable a => Hashable (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

hashWithSalt :: Int -> Block a -> Int #

hash :: Block a -> Int #

MirrorHorizontal (Block a) Source # 
Instance details

Defined in Data.Char.Block

MirrorVertical (Block a) Source # 
Instance details

Defined in Data.Char.Block

Methods

mirrorVertical :: Block a -> Block a Source #

UnicodeCharacter (Block Bool) Source # 
Instance details

Defined in Data.Char.Block

UnicodeText (Block Bool) Source # 
Instance details

Defined in Data.Char.Block

type Rep1 Block Source # 
Instance details

Defined in Data.Char.Block

type Rep1 Block = D1 ('MetaData "Block" "Data.Char.Block" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "upper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Row) :*: S1 ('MetaSel ('Just "lower") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Row)))
type Rep (Block a) Source # 
Instance details

Defined in Data.Char.Block

type Rep (Block a) = D1 ('MetaData "Block" "Data.Char.Block" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "upper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Row a)) :*: S1 ('MetaSel ('Just "lower") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Row a))))

A unicode character that is (partially) filled block.

filled Source #

Arguments

:: Block Bool

The given Block of Bools to convert to a Character.

-> Char

The equivalent Unicode Character for the given Block of Bools.

Convert the given Block value to a block character in unicode. True means that part is filled, and False means the part is not filled.

Convert a Character to a (partially) filled block.

fromBlock Source #

Arguments

:: Char

The given Character to convert to a Block of Bools.

-> Maybe (Block Bool) 

Convert the given Character to a Block of Bools wrapped in a Just if it exists; Nothing otherwise.

fromBlock' Source #

Arguments

:: Char

The given Character to convert to a Block of Bools.

-> Block Bool

The equivalent Block of Bools.

Convert the given Character to a Block of Bools if it exists; unspecified result otherwise.

Pattern synonyms for blocks

pattern EmptyBlock :: Char Source #

A pattern synonym for a block Character that will render an empty block, this is equivalent to a space.

pattern FullBlock :: Char Source #

A pattern synonym for the block Character that will render a full block.

pattern LeftHalfBlock :: Char Source #

A pattern synonym for a block Character that will render a block where the left half of the block is filled.

pattern RightHalfBlock :: Char Source #

A pattern synonym for a block Character that will render a block where the right half of the block is filled.