| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Patat.Presentation.Internal
Synopsis
- type Breadcrumbs = [(Int, [Inline])]
- data Presentation = Presentation {
- pFilePath :: !FilePath
- pEncodingFallback :: !EncodingFallback
- pTitle :: ![Inline]
- pAuthor :: ![Inline]
- pSettings :: !PresentationSettings
- pSlides :: !(Seq Slide)
- pBreadcrumbs :: !(Seq Breadcrumbs)
- pSlideSettings :: !(Seq PresentationSettings)
- pTransitionGens :: !(Seq (Maybe TransitionGen))
- pActiveFragment :: !Index
- pSyntaxMap :: !SyntaxMap
- pEvalBlocks :: !EvalBlocks
- pVarGen :: !VarGen
- pVars :: !(HashMap Var [Block])
- data PresentationSettings = PresentationSettings {
- psRows :: !(Maybe (FlexibleNum Int))
- psColumns :: !(Maybe (FlexibleNum Int))
- psMargins :: !(Maybe MarginSettings)
- psWrap :: !(Maybe Wrap)
- psTabStop :: !(Maybe (FlexibleNum Int))
- psTheme :: !(Maybe Theme)
- psIncrementalLists :: !(Maybe Bool)
- psAutoAdvanceDelay :: !(Maybe (FlexibleNum Int))
- psSlideLevel :: !(Maybe Int)
- psPandocExtensions :: !(Maybe ExtensionList)
- psImages :: !(Maybe ImageSettings)
- psBreadcrumbs :: !(Maybe Bool)
- psEval :: !(Maybe EvalSettingsMap)
- psSlideNumber :: !(Maybe Bool)
- psSyntaxDefinitions :: !(Maybe [FilePath])
- psSpeakerNotes :: !(Maybe SpeakerNotesSettings)
- psTransition :: !(Maybe TransitionSettings)
- defaultPresentationSettings :: PresentationSettings
- data MarginSettings = MarginSettings {}
- data Margins = Margins {}
- margins :: PresentationSettings -> Margins
- newtype ExtensionList = ExtensionList {}
- defaultExtensionList :: ExtensionList
- data ImageSettings = ImageSettings {}
- type EvalSettingsMap = HashMap Text EvalSettings
- data EvalSettings = EvalSettings {
- evalCommand :: !Text
- evalReplace :: !Bool
- evalFragment :: !Bool
- evalContainer :: !EvalSettingsContainer
- evalStderr :: !Bool
- data Slide = Slide {}
- data SlideContent
- = ContentSlide (Instructions Block)
- | TitleSlide Int [Inline]
- newtype Fragment = Fragment [Block]
- type Index = (Int, Int)
- getSlide :: Int -> Presentation -> Maybe Slide
- numFragments :: Slide -> Int
- data ActiveFragment
- activeFragment :: Presentation -> Maybe ActiveFragment
- activeSpeakerNotes :: Presentation -> SpeakerNotes
- activeVars :: Presentation -> HashSet Var
- getSettings :: Int -> Presentation -> PresentationSettings
- activeSettings :: Presentation -> PresentationSettings
- data Size
- getPresentationSize :: Presentation -> IO Size
- updateVar :: Var -> [Block] -> Presentation -> Presentation
Documentation
type Breadcrumbs = [(Int, [Inline])] Source #
data Presentation Source #
Constructors
| Presentation | |
Fields
| |
data PresentationSettings Source #
These are patat-specific settings. That is where they differ from more general metadata (author, title...)
Constructors
| PresentationSettings | |
Fields
| |
Instances
| FromJSON PresentationSettings Source # | |
Defined in Patat.Presentation.Settings Methods parseJSON :: Value -> Parser PresentationSettings # parseJSONList :: Value -> Parser [PresentationSettings] # | |
| Monoid PresentationSettings Source # | |
Defined in Patat.Presentation.Settings Methods mempty :: PresentationSettings # mappend :: PresentationSettings -> PresentationSettings -> PresentationSettings # | |
| Semigroup PresentationSettings Source # | |
Defined in Patat.Presentation.Settings Methods (<>) :: PresentationSettings -> PresentationSettings -> PresentationSettings # sconcat :: NonEmpty PresentationSettings -> PresentationSettings # stimes :: Integral b => b -> PresentationSettings -> PresentationSettings # | |
| Show PresentationSettings Source # | |
Defined in Patat.Presentation.Settings Methods showsPrec :: Int -> PresentationSettings -> ShowS # show :: PresentationSettings -> String # showList :: [PresentationSettings] -> ShowS # | |
data MarginSettings Source #
Constructors
| MarginSettings | |
Instances
| FromJSON MarginSettings Source # | |
Defined in Patat.Presentation.Settings Methods parseJSON :: Value -> Parser MarginSettings # parseJSONList :: Value -> Parser [MarginSettings] # | |
| Monoid MarginSettings Source # | |
Defined in Patat.Presentation.Settings Methods mappend :: MarginSettings -> MarginSettings -> MarginSettings # mconcat :: [MarginSettings] -> MarginSettings # | |
| Semigroup MarginSettings Source # | |
Defined in Patat.Presentation.Settings Methods (<>) :: MarginSettings -> MarginSettings -> MarginSettings # sconcat :: NonEmpty MarginSettings -> MarginSettings # stimes :: Integral b => b -> MarginSettings -> MarginSettings # | |
| Show MarginSettings Source # | |
Defined in Patat.Presentation.Settings Methods showsPrec :: Int -> MarginSettings -> ShowS # show :: MarginSettings -> String # showList :: [MarginSettings] -> ShowS # | |
newtype ExtensionList Source #
Constructors
| ExtensionList | |
Fields | |
Instances
| FromJSON ExtensionList Source # | |
Defined in Patat.Presentation.Settings Methods parseJSON :: Value -> Parser ExtensionList # parseJSONList :: Value -> Parser [ExtensionList] # | |
| Show ExtensionList Source # | |
Defined in Patat.Presentation.Settings Methods showsPrec :: Int -> ExtensionList -> ShowS # show :: ExtensionList -> String # showList :: [ExtensionList] -> ShowS # | |
data ImageSettings Source #
Constructors
| ImageSettings | |
Instances
| FromJSON ImageSettings Source # | |
Defined in Patat.Presentation.Settings Methods parseJSON :: Value -> Parser ImageSettings # parseJSONList :: Value -> Parser [ImageSettings] # | |
| Show ImageSettings Source # | |
Defined in Patat.Presentation.Settings Methods showsPrec :: Int -> ImageSettings -> ShowS # show :: ImageSettings -> String # showList :: [ImageSettings] -> ShowS # | |
type EvalSettingsMap = HashMap Text EvalSettings Source #
data EvalSettings Source #
Constructors
| EvalSettings | |
Fields
| |
Instances
| FromJSON EvalSettings Source # | |
Defined in Patat.Presentation.Settings | |
| Show EvalSettings Source # | |
Defined in Patat.Presentation.Settings Methods showsPrec :: Int -> EvalSettings -> ShowS # show :: EvalSettings -> String # showList :: [EvalSettings] -> ShowS # | |
Constructors
| Slide | |
Fields
| |
data SlideContent Source #
Constructors
| ContentSlide (Instructions Block) | |
| TitleSlide Int [Inline] |
Instances
| Show SlideContent Source # | |
Defined in Patat.Presentation.Internal Methods showsPrec :: Int -> SlideContent -> ShowS # show :: SlideContent -> String # showList :: [SlideContent] -> ShowS # | |
numFragments :: Slide -> Int Source #
data ActiveFragment Source #
Constructors
| ActiveContent Fragment | |
| ActiveTitle Block |
Instances
| Show ActiveFragment Source # | |
Defined in Patat.Presentation.Internal Methods showsPrec :: Int -> ActiveFragment -> ShowS # show :: ActiveFragment -> String # showList :: [ActiveFragment] -> ShowS # | |
activeVars :: Presentation -> HashSet Var Source #
getSettings :: Int -> Presentation -> PresentationSettings Source #
getPresentationSize :: Presentation -> IO Size Source #
updateVar :: Var -> [Block] -> Presentation -> Presentation Source #