Copyright | (c) Justus Sagemüller 2017 |
---|---|
License | GPL v3 |
Maintainer | (@) jsag $ hvl.no |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Presentation.Yeamer
Contents
Description
Synopsis
- type Presentation = IPresentation IO ()
- yeamer :: Presentation -> IO ()
- staticContent :: Monoid r => Html -> IPresentation m r
- tweakContent :: Sessionable r => (Html -> Html) -> IPresentation m r -> IPresentation m r
- serverSide :: Sessionable a => m a -> IPresentation m a
- ($<>) :: (r ~ (), SymbolClass σ, SCConstraint σ LaTeX, Monad m) => CAS (Infix LaTeX) (Encapsulation LaTeX) (SymbolD σ LaTeX) -> IPresentation m r -> IPresentation m r
- maths :: (r ~ (), SymbolClass σ, SCConstraint σ LaTeX) => [[CAS (Infix LaTeX) (Encapsulation LaTeX) (SymbolD σ LaTeX)]] -> String -> IPresentation m r
- imageFromFile :: FilePath -> IPresentation IO ()
- mediaFromFile :: FilePath -> IPresentation IO ()
- imageFromFileSupplier :: String -> (FilePath -> IO ()) -> IPresentation IO ()
- useFile :: FilePath -> (Url -> Html) -> IPresentation IO ()
- useFileSupplier :: String -> (FilePath -> IO ()) -> (Url -> Html) -> IPresentation IO ()
- verbatim :: QuasiQuoter
- plaintext :: QuasiQuoter
- verbatimWithin :: Name -> QuasiQuoter
- class InteractiveShow a where
- display :: a -> Presentation
- displayOriented :: DisplayOrientation -> a -> Presentation
- displayList :: DisplayOrientation -> [a] -> Presentation
- inputBox :: forall i m. (Inputtable i, FromJSON i) => i -> IPresentation m i
- dropdownSelect :: forall a m. (a -> String) -> [a] -> Int -> IPresentation m a
- feedback_ :: Sessionable a => (Maybe a -> IPresentation m a) -> IPresentation m ()
- addHeading :: Sessionable r => Html -> IPresentation m r -> IPresentation m r
- (======) :: Sessionable r => Html -> IPresentation m r -> IPresentation m r
- discardResult :: IPresentation m r -> IPresentation m ()
- module Data.Monoid
- (→│) :: Sessionable a => IPresentation m a -> IPresentation m b -> IPresentation m a
- (↘──) :: Sessionable a => IPresentation m a -> IPresentation m b -> IPresentation m a
- (│←) :: Sessionable b => IPresentation m a -> IPresentation m b -> IPresentation m b
- (──↖) :: Sessionable b => IPresentation m a -> IPresentation m b -> IPresentation m b
- (→│←) :: (Sessionable a, Sessionable b) => IPresentation m a -> IPresentation m b -> IPresentation m (a, b)
- (↘──↖) :: (Sessionable a, Sessionable b) => IPresentation m a -> IPresentation m b -> IPresentation m (a, b)
- (→│→) :: (Sessionable a, Monad m) => IPresentation m a -> (a -> IPresentation m ()) -> IPresentation m a
- (↘──↘) :: (Sessionable a, Monad m) => IPresentation m a -> (a -> IPresentation m ()) -> IPresentation m a
- divClass :: Sessionable r => Text -> IPresentation m r -> IPresentation m r
- divClasses :: Sessionable r => [(Text, IPresentation m r)] -> IPresentation m r
- spanClass :: Sessionable r => Text -> IPresentation m r -> IPresentation m r
- (#%) :: Sessionable r => Text -> IPresentation m r -> IPresentation m r
- styling :: Css -> IPresentation m r -> IPresentation m r
- data Css
- yeamer' :: YeamerServerConfig -> Presentation -> IO ()
- data YeamerServerConfig
- yeamerTcpPort :: Lens' YeamerServerConfig Int
- data IPresentation m r
Documentation
type Presentation = IPresentation IO () Source #
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
staticContent :: Monoid r => Html -> IPresentation m r Source #
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 #
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
Arguments
:: FilePath | File that should be served to the client |
-> (Url -> Html) | How it should be used in the presentation |
-> IPresentation IO () |
Arguments
:: String | File extension |
-> (FilePath -> IO ()) | Server-side file-providing action |
-> (Url -> Html) | How to use the file client-side |
-> IPresentation IO () |
Code / plaintext
Arguments
:: QuasiQuoter | ≈ |
Arguments
:: QuasiQuoter | ≈ |
Arguments
:: Name | A function |
-> QuasiQuoter | A specialised version of |
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
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.
discardResult :: IPresentation m r -> IPresentation m () Source #
module Data.Monoid
(→│) :: 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 #
styling :: Css -> IPresentation m r -> IPresentation m r Source #
Instances
HasContentType Css | |
Defined in Yesod.Core.Content Methods getContentType :: Monad m => m Css -> ContentType | |
ToContent Css | |
Defined in Yesod.Core.Content | |
ToTypedContent Css | |
Defined in Yesod.Core.Content Methods toTypedContent :: Css -> TypedContent | |
ToWidget site Css | |
Defined in Yesod.Core.Widget | |
ToWidgetHead site Css | |
Defined in Yesod.Core.Widget Methods toWidgetHead :: (MonadWidget m, HandlerSite m ~ site) => Css -> m () | |
ToWidgetMedia site Css | |
Defined in Yesod.Core.Widget Methods toWidgetMedia :: (MonadWidget m, HandlerSite m ~ site) => Text -> Css -> m () | |
render ~ RY site => ToWidget site (render -> Css) | |
Defined in Yesod.Core.Widget | |
render ~ RY site => ToWidgetHead site (render -> Css) | |
Defined in Yesod.Core.Widget Methods toWidgetHead :: (MonadWidget m, HandlerSite m ~ site) => (render -> Css) -> m () | |
render ~ RY site => ToWidgetMedia site (render -> Css) | |
Defined in Yesod.Core.Widget Methods toWidgetMedia :: (MonadWidget m, HandlerSite m ~ site) => Text -> (render -> Css) -> m () |
Server configuration
yeamer' :: YeamerServerConfig -> Presentation -> IO () Source #
data YeamerServerConfig Source #
Instances
Default YeamerServerConfig Source # | |
Defined in Presentation.Yeamer Methods |
Default port is 14910
yeamerTcpPort :: Lens' YeamerServerConfig Int Source #
Internals
data IPresentation m r Source #