unicode-tricks-0.8.0.0: Functions to work with unicode blocks more convenient.

Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Frame

Contents

Description

A frame is represented as a pair of horizontal and vertical lines. These can be any items, but currently only booleans and weight objects are covered to convert the item to a corresponding character.

Synopsis

Line weight

data Weight Source #

The weights of the frame lines, these can be Empty, Light or Heavy.

Constructors

Empty

The frame does not contain such line.

Light

The frame contains such line.

Heavy

The frame contains such line, in boldface.

Instances
Bounded Weight Source # 
Instance details

Defined in Data.Char.Frame

Enum Weight Source # 
Instance details

Defined in Data.Char.Frame

Eq Weight Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

Ord Weight Source # 
Instance details

Defined in Data.Char.Frame

Read Weight Source # 
Instance details

Defined in Data.Char.Frame

Show Weight Source # 
Instance details

Defined in Data.Char.Frame

Arbitrary Weight Source # 
Instance details

Defined in Data.Char.Frame

Datastructures to store the four directions

data Horizontal a Source #

A data type that determines the state of the horizontal lines of the frame (left and right).

Constructors

Horizontal 

Fields

  • left :: a

    The state of the left line of the frame.

  • right :: a

    The state of the right line of the frame.

Instances
Functor Horizontal Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

Applicative Horizontal Source # 
Instance details

Defined in Data.Char.Frame

Methods

pure :: a -> Horizontal a #

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

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

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

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

Foldable Horizontal Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

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

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

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

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

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

toList :: Horizontal a -> [a] #

null :: Horizontal a -> Bool #

length :: Horizontal a -> Int #

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

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

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

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

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

Traversable Horizontal Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

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

Arbitrary1 Horizontal Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

Defined in Data.Char.Frame

Methods

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

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

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

Defined in Data.Char.Frame

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

Defined in Data.Char.Frame

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

Defined in Data.Char.Frame

Semigroup a => Semigroup (Horizontal a) Source # 
Instance details

Defined in Data.Char.Frame

Monoid a => Monoid (Horizontal a) Source # 
Instance details

Defined in Data.Char.Frame

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

Defined in Data.Char.Frame

data Vertical a Source #

A data type that determines the state of the vertical lines of the frame (up and down).

Constructors

Vertical 

Fields

  • up :: a

    The state of the line in the up direction of the frame.

  • down :: a

    The state of the line in the down direction of the frame.

Instances
Functor Vertical Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

Applicative Vertical Source # 
Instance details

Defined in Data.Char.Frame

Methods

pure :: a -> Vertical a #

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

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

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

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

Foldable Vertical Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

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

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

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

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

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

toList :: Vertical a -> [a] #

null :: Vertical a -> Bool #

length :: Vertical a -> Int #

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

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

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

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

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

Traversable Vertical Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

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

Arbitrary1 Vertical Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

Defined in Data.Char.Frame

Methods

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

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

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

Defined in Data.Char.Frame

Methods

compare :: Vertical a -> Vertical a -> Ordering #

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

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

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

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

max :: Vertical a -> Vertical a -> Vertical a #

min :: Vertical a -> Vertical a -> Vertical a #

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

Defined in Data.Char.Frame

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

Defined in Data.Char.Frame

Methods

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

show :: Vertical a -> String #

showList :: [Vertical a] -> ShowS #

Semigroup a => Semigroup (Vertical a) Source # 
Instance details

Defined in Data.Char.Frame

Methods

(<>) :: Vertical a -> Vertical a -> Vertical a #

sconcat :: NonEmpty (Vertical a) -> Vertical a #

stimes :: Integral b => b -> Vertical a -> Vertical a #

Monoid a => Monoid (Vertical a) Source # 
Instance details

Defined in Data.Char.Frame

Methods

mempty :: Vertical a #

mappend :: Vertical a -> Vertical a -> Vertical a #

mconcat :: [Vertical a] -> Vertical a #

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

Defined in Data.Char.Frame

Methods

arbitrary :: Gen (Vertical a) #

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

data Parts a Source #

A data type that specifies the four lines that should (not) be drawn for the frame.

Constructors

Parts (Vertical a) (Horizontal a) 
Instances
Functor Parts Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

Applicative Parts Source # 
Instance details

Defined in Data.Char.Frame

Methods

pure :: a -> Parts a #

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

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

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

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

Foldable Parts Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

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

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

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

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

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

toList :: Parts a -> [a] #

null :: Parts a -> Bool #

length :: Parts a -> Int #

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

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

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

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

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

Traversable Parts Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

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

Arbitrary1 Parts Source # 
Instance details

Defined in Data.Char.Frame

Methods

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

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

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

Defined in Data.Char.Frame

Methods

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

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

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

Defined in Data.Char.Frame

Methods

compare :: Parts a -> Parts a -> Ordering #

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

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

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

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

max :: Parts a -> Parts a -> Parts a #

min :: Parts a -> Parts a -> Parts a #

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

Defined in Data.Char.Frame

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

Defined in Data.Char.Frame

Methods

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

show :: Parts a -> String #

showList :: [Parts a] -> ShowS #

Semigroup a => Semigroup (Parts a) Source # 
Instance details

Defined in Data.Char.Frame

Methods

(<>) :: Parts a -> Parts a -> Parts a #

sconcat :: NonEmpty (Parts a) -> Parts a #

stimes :: Integral b => b -> Parts a -> Parts a #

Monoid a => Monoid (Parts a) Source # 
Instance details

Defined in Data.Char.Frame

Methods

mempty :: Parts a #

mappend :: Parts a -> Parts a -> Parts a #

mconcat :: [Parts a] -> Parts a #

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

Defined in Data.Char.Frame

Methods

arbitrary :: Gen (Parts a) #

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

Type aliasses and pattern synonyms for convenient Parts

type Simple = Parts Bool Source #

A type synonym that makes it more convenient to work with a Parts object that wraps Bools. Usually True means it should draw a line, and False that there is no line in that direction.

type Weighted = Parts Weight Source #

A type synonym that makes it more convenient to work with a Parts object that wraps Weight objects. These specify the weight .

pattern Frame Source #

Arguments

:: a

The state of the line in the up direction.

-> a

The state of the line in the down direction.

-> a

The state of the line in the left direction.

-> a

The state of the line in the right direction.

-> Parts a

The Parts pattern with the state of the given lines.

A pattern that makes pattern matching and expressions with Parts more convenient.

Functions to render specific frame values

simple Source #

Arguments

:: Simple

The given Simple frame to convert.

-> Char

The corresponding characer for this Simple frame.

Convert a Simple frame to a corresponding Char. Here True is mapped to a Light line.

simple' Source #

Arguments

:: Simple

The given Simple frame to convert.

-> Char

The corresponding characer for this Simple frame.

Convert a Simple frame to a corresponding Char. Here True is mapped to a Heavy line.

simpleWithArc Source #

Arguments

:: Simple

The given Simple frame to convert.

-> Char

The corresponding characer for this Simple frame.

Generate a Char where turns are done with an arc instead of a corner. This can only be done for Light lines.

weighted Source #

Arguments

:: Weighted

The Weighted object that specifies how the lines on the four directions should look like.

-> Char

The character that represents these lines.

Converts a given Weighted to the char that can be used to render frames.

Convert a Simple to a Weighted

simpleToWeighted Source #

Arguments

:: Weight

The Weight that is used for True values.

-> Simple

The Simple frame to convert.

-> Weighted

The resulting Weighted frame.

Convert a Simple frame to a Weighted frame by converting True to the given Weight value.

simpleToLight Source #

Arguments

:: Simple

The Simple frame to convert.

-> Weighted

The resulting Weighted frame.

Convert a Simple frame to a Weighted frame by converting True to Light.

simpleToHeavy Source #

Arguments

:: Simple

The 'Simple frame to convert.

-> Weighted

The resulting Weighted frame.

Convert a Simple frame to a Weighted frame by converting True to Heavy.