patat-0.14.2.0: Terminal-based presentations using Pandoc
Safe HaskellSafe-Inferred
LanguageHaskell2010

Patat.Presentation.Syntax

Synopsis

Documentation

data Block Source #

This is similar to Block. Having our own datatype has some advantages:

  • We can extend it with slide-specific data (eval, reveals)
  • We can remove stuff we don't care about
  • We can parse attributes and move them to haskell datatypes
  • This conversion can happen in a single parsing phase
  • We can catch backwards-incompatible pandoc changes in this module

We try to follow the naming conventions from Pandoc as much as possible.

Instances

Instances details
Show Block Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Eq Block Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

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

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

data Inline Source #

See comment on Block.

Instances

Instances details
Show Inline Source # 
Instance details

Defined in Patat.Presentation.Syntax

Eq Inline Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

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

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

dftBlocks :: forall m. Monad m => (Block -> m [Block]) -> (Inline -> m [Inline]) -> [Block] -> m [Block] Source #

Depth-First Traversal of blocks (and inlines).

dftInlines :: forall m. Monad m => (Block -> m [Block]) -> (Inline -> m [Inline]) -> [Inline] -> m [Inline] Source #

Depth-First Traversal of inlines (and blocks).

newtype Var Source #

A variable is like a placeholder in the instructions, something we don't know yet, dynamic content. Currently this is only used for code evaluation.

Constructors

Var Unique 

Instances

Instances details
Show Var Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Eq Var Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

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

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

Ord Var Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

compare :: Var -> Var -> Ordering #

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

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

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Hashable Var Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

hashWithSalt :: Int -> Var -> Int #

hash :: Var -> Int #

variables :: [Block] -> HashSet Var Source #

Finds all variables that appear in some content.

newtype RevealID Source #

A counter is used to change state in a slide. As counters increment, content may deterministically show or hide.

Constructors

RevealID Unique 

Instances

Instances details
Show RevealID Source # 
Instance details

Defined in Patat.Presentation.Syntax

Eq RevealID Source # 
Instance details

Defined in Patat.Presentation.Syntax

Ord RevealID Source # 
Instance details

Defined in Patat.Presentation.Syntax

blocksRevealSteps :: [Block] -> Int Source #

Number of reveal steps in some blocks.

blocksRevealStep :: Int -> [Block] -> RevealState Source #

Construct the reveal state for a specific step.

blocksRevealLastStep :: [Block] -> RevealState Source #

Construct the final reveal state.

blocksRevealOrder :: [Block] -> [RevealID] Source #

This does a deep traversal of some blocks, and returns all reveals that should be advanced in-order.

blocksReveal :: RevealState -> [Block] -> [Block] Source #

Apply revealToBlocks recursively at each position, removing reveals in favor of their currently visible content.

type RevealState = Map RevealID Int Source #

Stores the state of several counters.

revealToBlocks :: RevealState -> RevealWrapper -> RevealSequence [Block] -> [Block] Source #

Render a reveal by applying its constructor to what is visible.

data RevealWrapper Source #

This determines how we construct content based on the visible items. This could also be represented as `[[Block]] -> [Block]` but then we lose the convenient Eq and Show instances.

Instances

Instances details
Show RevealWrapper Source # 
Instance details

Defined in Patat.Presentation.Syntax

Eq RevealWrapper Source # 
Instance details

Defined in Patat.Presentation.Syntax

data RevealSequence a Source #

A reveal sequence stores content which can be hidden or shown depending on a counter state.

The easiest example to think about is a bullet list which appears incrmentally on a slide. Initially, the counter state is 0. As it is incremented (the user goes to the next fragment in the slide), more list items become visible.

Constructors

RevealSequence 

Fields

Instances

Instances details
Foldable RevealSequence Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

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

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

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

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

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

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

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

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

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

toList :: RevealSequence a -> [a] #

null :: RevealSequence a -> Bool #

length :: RevealSequence a -> Int #

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

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

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

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

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

Traversable RevealSequence Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

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

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

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

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

Functor RevealSequence Source # 
Instance details

Defined in Patat.Presentation.Syntax

Methods

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

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

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

Defined in Patat.Presentation.Syntax

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

Defined in Patat.Presentation.Syntax