rib-0.5.0.0: Static site generator using Shake

Safe HaskellNone
LanguageHaskell2010

Rib

Description

 
Synopsis

Documentation

module Rib.App

module Rib.Shake

serve Source #

Arguments

:: Int

Port number to bind to

-> FilePath

Directory to serve.

-> IO () 

Run a HTTP server to serve a directory of static files

Allow URLs of the form /foo/bar to serve ${path}/foo/bar.html

data Document repr meta Source #

A document written in a lightweight markup language (LML)

The type variable repr indicates the representation type of the Markup parser to be used.

Instances
(Show repr, Show meta) => Show (Document repr meta) Source # 
Instance details

Defined in Rib.Document

Methods

showsPrec :: Int -> Document repr meta -> ShowS #

show :: Document repr meta -> String #

showList :: [Document repr meta] -> ShowS #

Generic (Document repr meta) Source # 
Instance details

Defined in Rib.Document

Associated Types

type Rep (Document repr meta) :: Type -> Type #

Methods

from :: Document repr meta -> Rep (Document repr meta) x #

to :: Rep (Document repr meta) x -> Document repr meta #

type Rep (Document repr meta) Source # 
Instance details

Defined in Rib.Document

type Rep (Document repr meta) = D1 (MetaData "Document" "Rib.Document" "rib-0.5.0.0-inplace" False) (C1 (MetaCons "Document" PrefixI True) ((S1 (MetaSel (Just "_document_path") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Path Rel File)) :*: S1 (MetaSel (Just "_document_val") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 repr)) :*: (S1 (MetaSel (Just "_document_html") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Html ())) :*: S1 (MetaSel (Just "_document_meta") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 meta))))

documentVal :: Document repr meta -> repr Source #

documentHtml :: Document repr meta -> Html () Source #

documentMeta :: Document repr meta -> meta Source #

documentUrl :: Document repr meta -> Text Source #

Return the URL for the given .html file under serve directory

File path must be relative to the serve directory.

You may also pass source paths as long as they map directly to destination path except for file extension.

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 -> () #

renderMarkdown :: Text -> Html () Source #

Parse and render the markup directly to HTML

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-CRDWk7nUpqxLSahMa8Udqw" 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])))

renderPandoc :: Path Rel File -> Text -> Html () Source #

Parse and render the markup directly to HTML