rib-0.6.0.0: Static site generator using Shake

Safe HaskellNone
LanguageHaskell2010

Rib

Description

 
Synopsis

Documentation

module Rib.App

module Rib.Shake

data Source repr Source #

A source file on disk

Instances
Functor Source Source # 
Instance details

Defined in Rib.Source

Methods

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

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

Generic (Source repr) Source # 
Instance details

Defined in Rib.Source

Associated Types

type Rep (Source repr) :: Type -> Type #

Methods

from :: Source repr -> Rep (Source repr) x #

to :: Rep (Source repr) x -> Source repr #

type Rep (Source repr) Source # 
Instance details

Defined in Rib.Source

type Rep (Source repr) = D1 (MetaData "Source" "Rib.Source" "rib-0.6.0.0-inplace" False) (C1 (MetaCons "Source" PrefixI True) (S1 (MetaSel (Just "_source_path") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Path Rel File)) :*: (S1 (MetaSel (Just "_source_builtPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Path Rel File)) :*: S1 (MetaSel (Just "_source_val") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 repr))))

type SourceReader repr = forall b. Path b File -> Action (Either Text repr) Source #

A function that parses a source representation out of the given file

sourcePath :: Source repr -> Path Rel File Source #

Path to the source file (relative to ribInputDir)

sourceVal :: Source repr -> repr Source #

Parsed representation of the source.

sourceUrl :: Source repr -> Text Source #

Relative URL to the generated source HTML.

data MMark #

Representation of complete markdown document. You can't look inside of MMark on purpose. The only way to influence an MMark document you obtain as a result of parsing is via the extension mechanism.

Instances
Show MMark

Dummy instance.

Since: mmark-0.0.5.0

Instance details

Defined in Text.MMark.Type

Methods

showsPrec :: Int -> MMark -> ShowS #

show :: MMark -> String #

showList :: [MMark] -> ShowS #

NFData MMark 
Instance details

Defined in Text.MMark.Type

Methods

rnf :: MMark -> () #

data Pandoc #

Instances
Eq Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

Data Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

toConstr :: Pandoc -> Constr #

dataTypeOf :: Pandoc -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Read Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Show Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Generic Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Pandoc :: Type -> Type #

Methods

from :: Pandoc -> Rep Pandoc x #

to :: Rep Pandoc x -> Pandoc #

Semigroup Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Monoid Pandoc 
Instance details

Defined in Text.Pandoc.Definition

ToJSON Pandoc 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Pandoc 
Instance details

Defined in Text.Pandoc.Definition

NFData Pandoc 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Pandoc -> () #

HasMeta Pandoc 
Instance details

Defined in Text.Pandoc.Builder

Methods

setMeta :: ToMetaValue b => String -> b -> Pandoc -> Pandoc #

deleteMeta :: String -> Pandoc -> Pandoc #

Walkable Block Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Block -> Block) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Block -> m Block) -> Pandoc -> m Pandoc #

query :: Monoid c => (Block -> c) -> Pandoc -> c #

Walkable Inline Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Inline -> Inline) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Pandoc -> m Pandoc #

query :: Monoid c => (Inline -> c) -> Pandoc -> c #

Walkable Pandoc Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: (Pandoc -> Pandoc) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc #

query :: Monoid c => (Pandoc -> c) -> Pandoc -> c #

Walkable [Block] Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Block] -> [Block]) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => ([Block] -> m [Block]) -> Pandoc -> m Pandoc #

query :: Monoid c => ([Block] -> c) -> Pandoc -> c #

Walkable [Inline] Pandoc 
Instance details

Defined in Text.Pandoc.Walk

Methods

walk :: ([Inline] -> [Inline]) -> Pandoc -> Pandoc #

walkM :: (Monad m, Applicative m, Functor m) => ([Inline] -> m [Inline]) -> Pandoc -> m Pandoc #

query :: Monoid c => ([Inline] -> c) -> Pandoc -> c #

type Rep Pandoc 
Instance details

Defined in Text.Pandoc.Definition

type Rep Pandoc = D1 (MetaData "Pandoc" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-BxsfEhPlr7TDcfSzVyDfbp" False) (C1 (MetaCons "Pandoc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Meta) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])))