Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data Doc = Doc Options Blocks
- data Block
- data CodeAttr = CodeAttr {}
- data ListType
- data NumWrapper
- data HtmlTagType
- type Blocks = Seq Block
- data Inline
- type Inlines = Seq Inline
- type ReferenceMap = Map Text (Text, Text)
- data Options = Options {
- sanitize :: Bool
- allowRawHtml :: Bool
- preserveHardBreaks :: Bool
- debug :: Bool
Documentation
Structured representation of a document. The Options
affect
how the document is rendered by toHtml
.
Instances
Data Doc Source # | |
Defined in Cheapskate.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Doc -> c Doc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Doc # dataTypeOf :: Doc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Doc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc) # gmapT :: (forall b. Data b => b -> b) -> Doc -> Doc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r # gmapQ :: (forall d. Data d => d -> u) -> Doc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Doc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Doc -> m Doc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc -> m Doc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc -> m Doc # | |
Show Doc Source # | |
Generic Doc Source # | |
ToMarkup Doc Source # | |
Defined in Cheapskate | |
NFData Doc Source # | |
Defined in Cheapskate.Types | |
type Rep Doc Source # | |
Defined in Cheapskate.Types type Rep Doc = D1 (MetaData "Doc" "Cheapskate.Types" "cheapskate-0.1.1.1-GbI1rS1Zgbz6bzJ0uNVMzE" False) (C1 (MetaCons "Doc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Options) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Blocks))) |
Block-level elements.
Para Inlines | |
Header Int Inlines | |
Blockquote Blocks | |
List Bool ListType [Blocks] | |
CodeBlock CodeAttr Text | |
HtmlBlock Text | |
HRule |
Instances
Attributes for fenced code blocks. codeLang
is the
first word of the attribute line, codeInfo
is the rest.
Instances
Data CodeAttr Source # | |
Defined in Cheapskate.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CodeAttr -> c CodeAttr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CodeAttr # toConstr :: CodeAttr -> Constr # dataTypeOf :: CodeAttr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CodeAttr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CodeAttr) # gmapT :: (forall b. Data b => b -> b) -> CodeAttr -> CodeAttr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CodeAttr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CodeAttr -> r # gmapQ :: (forall d. Data d => d -> u) -> CodeAttr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CodeAttr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CodeAttr -> m CodeAttr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CodeAttr -> m CodeAttr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CodeAttr -> m CodeAttr # | |
Show CodeAttr Source # | |
Generic CodeAttr Source # | |
NFData CodeAttr Source # | |
Defined in Cheapskate.Types | |
type Rep CodeAttr Source # | |
Defined in Cheapskate.Types type Rep CodeAttr = D1 (MetaData "CodeAttr" "Cheapskate.Types" "cheapskate-0.1.1.1-GbI1rS1Zgbz6bzJ0uNVMzE" False) (C1 (MetaCons "CodeAttr" PrefixI True) (S1 (MetaSel (Just "codeLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "codeInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
Instances
Eq ListType Source # | |
Data ListType Source # | |
Defined in Cheapskate.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListType -> c ListType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListType # toConstr :: ListType -> Constr # dataTypeOf :: ListType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListType) # gmapT :: (forall b. Data b => b -> b) -> ListType -> ListType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListType -> r # gmapQ :: (forall d. Data d => d -> u) -> ListType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ListType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListType -> m ListType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListType -> m ListType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListType -> m ListType # | |
Show ListType Source # | |
Generic ListType Source # | |
NFData ListType Source # | |
Defined in Cheapskate.Types | |
type Rep ListType Source # | |
Defined in Cheapskate.Types type Rep ListType = D1 (MetaData "ListType" "Cheapskate.Types" "cheapskate-0.1.1.1-GbI1rS1Zgbz6bzJ0uNVMzE" False) (C1 (MetaCons "Bullet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) :+: C1 (MetaCons "Numbered" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NumWrapper) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) |
data NumWrapper Source #
Instances
Eq NumWrapper Source # | |
Defined in Cheapskate.Types (==) :: NumWrapper -> NumWrapper -> Bool # (/=) :: NumWrapper -> NumWrapper -> Bool # | |
Data NumWrapper Source # | |
Defined in Cheapskate.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NumWrapper -> c NumWrapper # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NumWrapper # toConstr :: NumWrapper -> Constr # dataTypeOf :: NumWrapper -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NumWrapper) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NumWrapper) # gmapT :: (forall b. Data b => b -> b) -> NumWrapper -> NumWrapper # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NumWrapper -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NumWrapper -> r # gmapQ :: (forall d. Data d => d -> u) -> NumWrapper -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NumWrapper -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NumWrapper -> m NumWrapper # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NumWrapper -> m NumWrapper # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NumWrapper -> m NumWrapper # | |
Show NumWrapper Source # | |
Defined in Cheapskate.Types showsPrec :: Int -> NumWrapper -> ShowS # show :: NumWrapper -> String # showList :: [NumWrapper] -> ShowS # | |
Generic NumWrapper Source # | |
Defined in Cheapskate.Types type Rep NumWrapper :: Type -> Type # from :: NumWrapper -> Rep NumWrapper x # to :: Rep NumWrapper x -> NumWrapper # | |
NFData NumWrapper Source # | |
Defined in Cheapskate.Types rnf :: NumWrapper -> () # | |
type Rep NumWrapper Source # | |
data HtmlTagType Source #
Simple representation of HTML tag.
Instances
Inline elements.
Str Text | |
Space | |
SoftBreak | |
LineBreak | |
Emph Inlines | |
Strong Inlines | |
Code Text | |
Link Inlines Text Text | |
Image Inlines Text Text | |
Entity Text | |
RawHtml Text |
Instances
Rendering and parsing options.
Options | |
|
Instances
Data Options Source # | |
Defined in Cheapskate.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Options -> c Options # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Options # toConstr :: Options -> Constr # dataTypeOf :: Options -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Options) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Options) # gmapT :: (forall b. Data b => b -> b) -> Options -> Options # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Options -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Options -> r # gmapQ :: (forall d. Data d => d -> u) -> Options -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Options -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Options -> m Options # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Options -> m Options # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Options -> m Options # | |
Show Options Source # | |
Generic Options Source # | |
Default Options Source # | |
Defined in Cheapskate.Types | |
NFData Options Source # | |
Defined in Cheapskate.Types | |
type Rep Options Source # | |
Defined in Cheapskate.Types type Rep Options = D1 (MetaData "Options" "Cheapskate.Types" "cheapskate-0.1.1.1-GbI1rS1Zgbz6bzJ0uNVMzE" False) (C1 (MetaCons "Options" PrefixI True) ((S1 (MetaSel (Just "sanitize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "allowRawHtml") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "preserveHardBreaks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "debug") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) |