yeamer-0.1.2.0: Yesod-based server for interactive presentation slides

Copyright(c) Justus Sagemüller 2017
LicenseGPL v3
Maintainer(@) jsag $ hvl.no
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Presentation.Yeamer

Contents

Description

 
Synopsis

Documentation

Running a presentation

yeamer :: Presentation -> IO () Source #

Run a Yesod/Warp web server that will allow the presentation to be viewed in a web browser, on port 14910. This is a shorthand for yeamer' def.

Primitives

tweakContent :: Sessionable r => (Html -> Html) -> IPresentation m r -> IPresentation m r Source #

serverSide :: Sessionable a => m a -> IPresentation m a Source #

Run a monadic action and use the result in the presentation. Note that the action may not be re-run even if it depends to other values chosen at another point in the presentation, so use with care.

Maths

($<>) :: (r ~ (), SymbolClass σ, SCConstraint σ LaTeX, Monad m) => CAS (Infix LaTeX) (Encapsulation LaTeX) (SymbolD σ LaTeX) -> IPresentation m r -> IPresentation m r infixr 6 Source #

Include a mathematical expression inline in the document.

maths :: (r ~ (), SymbolClass σ, SCConstraint σ LaTeX) => [[CAS (Infix LaTeX) (Encapsulation LaTeX) (SymbolD σ LaTeX)]] -> String -> IPresentation m r Source #

Include a mathematical expression as a “display” in the document, typically used for equations.

Example:

    "The constant "<>π$<>" fulfills "
      <>maths [[ sin π⩵0 ]]"."
  

The maths expressions use TeX-my-maths syntax (Math.LaTeX.Prelude). Note that TeX-my-maths has different syntax flavours (e.g. 𝑎×𝑒◝γ vs. a * exp gamma). Both can be used with $<> and maths, but the downside is type ambiguity in expressions that include no symbols at all (e.g. single numbers), which can lead to Could not deduce ‘SymbolClass σ’ compiler errors. To avoid this problem, you can add local type signatures or use the Presentation.Yeamer.Maths.Unicode.MathLatin_RomanGreek module.

Media content

imageFromFile :: FilePath -> IPresentation IO () Source #

Display an image that lies on the server as any ordinary static file. This is a special case of useFile, wrapping the file in an img tag.

mediaFromFile :: FilePath -> IPresentation IO () Source #

More general form of imageFromFile. Takes a guess based on the file extension, as to whether the media is a standing image or a video. In the latter case, simple HTML5 controls are added.

imageFromFileSupplier Source #

Arguments

:: String

File extension

-> (FilePath -> IO ())

File-writer function. This will be called every time a slide with the image is requested.

-> IPresentation IO () 

Display an image generated on-the-fly in the server. The image will be stored temporarily, in a content-indexed fashion.

Arbitrary file serving

useFile Source #

Arguments

:: FilePath

File that should be served to the client

-> (Url -> Html)

How it should be used in the presentation

-> IPresentation IO () 

useFileSupplier Source #

Arguments

:: String

File extension

-> (FilePath -> IO ())

Server-side file-providing action

-> (Url -> Html)

How to use the file client-side

-> IPresentation IO () 

Code / plaintext

verbatim Source #

Arguments

:: QuasiQuoter

Value -> IPresentation m ()

Include a piece of plaintext, preserving all formatting. To be used in an oxford bracket.

In practice, you probably want to use this for monospace plaintext, which should appear in a pre or textarea tag. Use the specialised quoters for that.

plaintext Source #

Arguments

:: QuasiQuoter

Value -> IPresentation m ()

A simple version of verbatim that gives the HTML wrapped in pre tags, so it will (by default) appear in a monospace font.

verbatimWithin Source #

Arguments

:: Name

A function Html -> Html that should be used for presenting the (pre-escaped) plaintext.

-> QuasiQuoter

A specialised version of verbatim that will always use the wrapper.

Convenience wrapper to generate quasi-quoters that will wrap code in any suitable HTML environment.

Haskell values

class InteractiveShow a where Source #

Minimal complete definition

Nothing

Methods

display :: a -> Presentation Source #

displayOriented :: DisplayOrientation -> a -> Presentation Source #

displayOriented :: (Generic a, GInteractiveShow (Rep a)) => DisplayOrientation -> a -> Presentation Source #

displayList :: DisplayOrientation -> [a] -> Presentation Source #

Instances
InteractiveShow Char Source # 
Instance details

Defined in Presentation.Yeamer

Methods

display :: Char -> Presentation Source #

displayOriented :: DisplayOrientation -> Char -> Presentation Source #

displayList :: DisplayOrientation -> [Char] -> Presentation Source #

InteractiveShow Double Source # 
Instance details

Defined in Presentation.Yeamer

Methods

display :: Double -> Presentation Source #

displayOriented :: DisplayOrientation -> Double -> Presentation Source #

displayList :: DisplayOrientation -> [Double] -> Presentation Source #

InteractiveShow Int Source # 
Instance details

Defined in Presentation.Yeamer

Methods

display :: Int -> Presentation Source #

displayOriented :: DisplayOrientation -> Int -> Presentation Source #

displayList :: DisplayOrientation -> [Int] -> Presentation Source #

InteractiveShow Int16 Source # 
Instance details

Defined in Presentation.Yeamer

Methods

display :: Int16 -> Presentation Source #

displayOriented :: DisplayOrientation -> Int16 -> Presentation Source #

displayList :: DisplayOrientation -> [Int16] -> Presentation Source #

InteractiveShow Int32 Source # 
Instance details

Defined in Presentation.Yeamer

Methods

display :: Int32 -> Presentation Source #

displayOriented :: DisplayOrientation -> Int32 -> Presentation Source #

displayList :: DisplayOrientation -> [Int32] -> Presentation Source #

InteractiveShow Int64 Source # 
Instance details

Defined in Presentation.Yeamer

Methods

display :: Int64 -> Presentation Source #

displayOriented :: DisplayOrientation -> Int64 -> Presentation Source #

displayList :: DisplayOrientation -> [Int64] -> Presentation Source #

InteractiveShow a => InteractiveShow [a] Source # 
Instance details

Defined in Presentation.Yeamer

Methods

display :: [a] -> Presentation Source #

displayOriented :: DisplayOrientation -> [a] -> Presentation Source #

displayList :: DisplayOrientation -> [[a]] -> Presentation Source #

Interactive parameters

inputBox :: forall i m. (Inputtable i, FromJSON i) => i -> IPresentation m i Source #

dropdownSelect :: forall a m. (a -> String) -> [a] -> Int -> IPresentation m a Source #

feedback_ :: Sessionable a => (Maybe a -> IPresentation m a) -> IPresentation m () Source #

Structure / composition

addHeading :: Sessionable r => Html -> IPresentation m r -> IPresentation m r Source #

(======) :: Sessionable r => Html -> IPresentation m r -> IPresentation m r infixr 6 Source #

Infix synonym of addHeading. Intended to be used in do blocks, for headings of presentation slides.

(→│) :: Sessionable a => IPresentation m a -> IPresentation m b -> IPresentation m a infix 6 Source #

(↘──) :: Sessionable a => IPresentation m a -> IPresentation m b -> IPresentation m a infix 5 Source #

(│←) :: Sessionable b => IPresentation m a -> IPresentation m b -> IPresentation m b infix 6 Source #

(──↖) :: Sessionable b => IPresentation m a -> IPresentation m b -> IPresentation m b infix 5 Source #

(→│←) :: (Sessionable a, Sessionable b) => IPresentation m a -> IPresentation m b -> IPresentation m (a, b) infix 6 Source #

(↘──↖) :: (Sessionable a, Sessionable b) => IPresentation m a -> IPresentation m b -> IPresentation m (a, b) infix 5 Source #

(→│→) :: (Sessionable a, Monad m) => IPresentation m a -> (a -> IPresentation m ()) -> IPresentation m a infix 6 Source #

(↘──↘) :: (Sessionable a, Monad m) => IPresentation m a -> (a -> IPresentation m ()) -> IPresentation m a infix 5 Source #

CSS

divClass :: Sessionable r => Text -> IPresentation m r -> IPresentation m r Source #

divClasses :: Sessionable r => [(Text, IPresentation m r)] -> IPresentation m r Source #

spanClass :: Sessionable r => Text -> IPresentation m r -> IPresentation m r Source #

(#%) :: Sessionable r => Text -> IPresentation m r -> IPresentation m r infix 8 Source #

Assign this content a CSS class attribute. If the content is inline, this will be a span, else a div.

data Css #

Instances
HasContentType Css 
Instance details

Defined in Yesod.Core.Content

Methods

getContentType :: Monad m => m Css -> ContentType

ToContent Css 
Instance details

Defined in Yesod.Core.Content

Methods

toContent :: Css -> Content

ToTypedContent Css 
Instance details

Defined in Yesod.Core.Content

Methods

toTypedContent :: Css -> TypedContent

ToWidget site Css 
Instance details

Defined in Yesod.Core.Widget

Methods

toWidget :: (MonadWidget m, HandlerSite m ~ site) => Css -> m ()

ToWidgetHead site Css 
Instance details

Defined in Yesod.Core.Widget

Methods

toWidgetHead :: (MonadWidget m, HandlerSite m ~ site) => Css -> m ()

ToWidgetMedia site Css 
Instance details

Defined in Yesod.Core.Widget

Methods

toWidgetMedia :: (MonadWidget m, HandlerSite m ~ site) => Text -> Css -> m ()

render ~ RY site => ToWidget site (render -> Css) 
Instance details

Defined in Yesod.Core.Widget

Methods

toWidget :: (MonadWidget m, HandlerSite m ~ site) => (render -> Css) -> m ()

render ~ RY site => ToWidgetHead site (render -> Css) 
Instance details

Defined in Yesod.Core.Widget

Methods

toWidgetHead :: (MonadWidget m, HandlerSite m ~ site) => (render -> Css) -> m ()

render ~ RY site => ToWidgetMedia site (render -> Css) 
Instance details

Defined in Yesod.Core.Widget

Methods

toWidgetMedia :: (MonadWidget m, HandlerSite m ~ site) => Text -> (render -> Css) -> m ()

Server configuration

data YeamerServerConfig Source #

Instances
Default YeamerServerConfig Source # 
Instance details

Defined in Presentation.Yeamer

Default port is 14910

Internals

data IPresentation m r Source #

Instances
SemigroupNo 0 (IPresentation m ()) Source # 
Instance details

Defined in Presentation.Yeamer

Methods

sappendN :: proxy 0 -> IPresentation m () -> IPresentation m () -> IPresentation m () #

sconcatN :: proxy 0 -> NonEmpty (IPresentation m ()) -> IPresentation m () #

stimesN :: (Integral b, HasCallStack) => proxy 0 -> b -> IPresentation m () -> IPresentation m () #

SemigroupNo 1 (IPresentation m ()) Source # 
Instance details

Defined in Presentation.Yeamer

Methods

sappendN :: proxy 1 -> IPresentation m () -> IPresentation m () -> IPresentation m () #

sconcatN :: proxy 1 -> NonEmpty (IPresentation m ()) -> IPresentation m () #

stimesN :: (Integral b, HasCallStack) => proxy 1 -> b -> IPresentation m () -> IPresentation m () #

Monad (IPresentation m) Source # 
Instance details

Defined in Presentation.Yeamer

Methods

(>>=) :: IPresentation m a -> (a -> IPresentation m b) -> IPresentation m b #

(>>) :: IPresentation m a -> IPresentation m b -> IPresentation m b #

return :: a -> IPresentation m a #

fail :: String -> IPresentation m a #

Functor (IPresentation m) Source # 
Instance details

Defined in Presentation.Yeamer

Methods

fmap :: (a -> b) -> IPresentation m a -> IPresentation m b #

(<$) :: a -> IPresentation m b -> IPresentation m a #

Applicative (IPresentation m) Source # 
Instance details

Defined in Presentation.Yeamer

Methods

pure :: a -> IPresentation m a #

(<*>) :: IPresentation m (a -> b) -> IPresentation m a -> IPresentation m b #

liftA2 :: (a -> b -> c) -> IPresentation m a -> IPresentation m b -> IPresentation m c #

(*>) :: IPresentation m a -> IPresentation m b -> IPresentation m b #

(<*) :: IPresentation m a -> IPresentation m b -> IPresentation m a #

r ~ () => IsString (IPresentation m r) Source # 
Instance details

Defined in Presentation.Yeamer

Methods

fromString :: String -> IPresentation m r #

(Monad m, Monoid r, Sessionable r) => Semigroup (IPresentation m r) Source # 
Instance details

Defined in Presentation.Yeamer

Monad m => Monoid (IPresentation m ()) Source # 
Instance details

Defined in Presentation.Yeamer