HaTeX-3.14.0.0: The Haskell LaTeX library.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.LaTeX.Packages.Beamer

Contents

Description

Beamer is a LaTeX package for the creation of slides.

Each frame is contained within the frame function. Here is an example:

{-# LANGUAGE OverloadedStrings #-}

import Text.LaTeX
import Text.LaTeX.Packages.Beamer

mySlides :: Monad m => LaTeXT m ()
mySlides = do
  frame $ do
    frametitle "First frame"
    "Content of the first frame."
  frame $ do
    frametitle "Second frame"
    "Content of the second frame." 
    pause
    " And actually a little more."

The pause command in the second frame makes the second part of the text to appear one screen later.

Synopsis

Beamer package

beamer :: ClassName Source

The beamer document class. Importing a package is not required. Example:

documentclass [] beamer

Beamer commands

frame :: LaTeXC l => l -> l Source

A presentation is composed of a sequence of frames. Each frame is created with this function.

frametitle :: LaTeXC l => l -> l Source

Set the title of the current frame. Use it within a frame.

framesubtitle :: LaTeXC l => l -> l Source

Set the subtitle of the current frame. Use it within a frame.

alert :: LaTeXC l => [OverlaySpec] -> l -> l Source

Highlight in red a piece of text. With the OverlaySpecs, you can specify the slides where the text will be highlighted.

pause :: LaTeXC l => l Source

Introduces a pause in a slide.

block Source

Arguments

:: LaTeXC l 
=> l

Title for the block

-> l

Content of the block

-> l

Result

A block will be displayed surrounding a text.

Overlay Specifications

data OverlaySpec Source

Specifications for beamer functions.

beameritem :: LaTeXC l => [OverlaySpec] -> l Source

beameritem works like item, but allows you to specify the slides where the item will be displayed.

uncover :: LaTeXC l => [OverlaySpec] -> l -> l Source

With uncover, show a piece of text only in the slides you want.

only :: LaTeXC l => [OverlaySpec] -> l -> l Source

Similar to uncover.

Themes

usetheme :: LaTeXC l => Theme -> l Source

Set the Theme employed in your presentation (in the preamble).