Shpadoinkle-disembodied-0.0.0.1: Shpadoinkle as a static site.

Safe HaskellNone
LanguageHaskell2010

Shpadoinkle.Disembodied

Contents

Description

Static sites are the opposite of headless applications, they are disembodied. Shpadoinkle Disembodied is a static site generator for Shpadoinkle applications.

Synopsis

Site Reification

data Site ctx where Source #

The reification of a static site based on Servant routes. Site takes a context ctx which is universal for the static site. This is useful for storing commonly used valus like the site name, site url, copyright date, ect.

Constructors

SPath

A path segment in the URI

Fields

  • :: String

    The current URI path segment

  • -> Site ctx

    The site to be rendered at the path

  • -> Site ctx
     
SIndex

Html to be rendered as index.html

Fields

  • :: (ctx -> Html m a)

    Given a context, how can we render a page?

  • -> Site ctx
     
SCapture

Capture is the one Servant combinator that can be meaningful in static site generation, and only if we can generate all possible instances.

Fields

SChoice :: Site ctx -> Site ctx -> Site ctx

Branch the site at a given point in generation.

Class

class Disembodied ctx a where Source #

Type class induction for building the site out of a specification

Associated Types

type SiteSpec ctx a :: Type Source #

A type family to represent the relationship between a Servant API and the Html views to render.

type SPA m = "about" :> Html m ()
        :<|> Html m ()

site :: SiteSpec () (SPA m)
site = const (h1_ [ text "about" ])
  :<|> const (h1_ [ text "home" ])

Methods

buildSite :: SiteSpec ctx a -> Site ctx Source #

Construct the site structure out of the associated API

Instances
Disembodied ctx (View m a) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (View m a) :: Type Source #

Methods

buildSite :: SiteSpec ctx (View m a) -> Site ctx Source #

Disembodied ctx (f (HTML ': ([] :: [Type])) (Html m a)) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (f (HTML ': []) (Html m a)) :: Type Source #

Methods

buildSite :: SiteSpec ctx (f (HTML ': []) (Html m a)) -> Site ctx Source #

(Disembodied ctx x, Disembodied ctx y) => Disembodied ctx (x :<|> y) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (x :<|> y) :: Type Source #

Methods

buildSite :: SiteSpec ctx (x :<|> y) -> Site ctx Source #

Disembodied ctx sub => Disembodied ctx (QueryFlag sym :> sub) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (QueryFlag sym :> sub) :: Type Source #

Methods

buildSite :: SiteSpec ctx (QueryFlag sym :> sub) -> Site ctx Source #

Disembodied ctx sub => Disembodied ctx (QueryParams sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (QueryParams sym x :> sub) :: Type Source #

Methods

buildSite :: SiteSpec ctx (QueryParams sym x :> sub) -> Site ctx Source #

Disembodied ctx sub => Disembodied ctx (QueryParam' ms sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (QueryParam' ms sym x :> sub) :: Type Source #

Methods

buildSite :: SiteSpec ctx (QueryParam' ms sym x :> sub) -> Site ctx Source #

Disembodied ctx sub => Disembodied ctx (QueryParam sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (QueryParam sym x :> sub) :: Type Source #

Methods

buildSite :: SiteSpec ctx (QueryParam sym x :> sub) -> Site ctx Source #

(Disembodied ctx sub, FromHttpApiData x, ToHttpApiData x, Bounded x, Enum x) => Disembodied ctx (Capture sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (Capture sym x :> sub) :: Type Source #

Methods

buildSite :: SiteSpec ctx (Capture sym x :> sub) -> Site ctx Source #

(Disembodied ctx sub, KnownSymbol path) => Disembodied ctx (path :> sub) Source # 
Instance details

Defined in Shpadoinkle.Disembodied

Associated Types

type SiteSpec ctx (path :> sub) :: Type Source #

Methods

buildSite :: SiteSpec ctx (path :> sub) -> Site ctx Source #

Write Files

writeSite Source #

Arguments

:: Disembodied ctx layout 
=> FilePath

Out path

-> ctx

Universal context for the static site.

-> SiteSpec ctx layout

Specification for the pages of the site relative to a Servant API.

-> IO () 

Actually write the site to disk. Branches are written in parallel.