HaTeX-3.17.0.0: The Haskell LaTeX library.

Safe HaskellSafe
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. On other slides, the text still occupies space and it is still typeset, but it is not shown or only shown as if transparent.

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

With only the text is inserted only into the specified slides. For other slides, the text is simply thrown away (it occupies no space).

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

The behavior of the onslide command depends on whether the optional argument text is given or not. If a text argument is present, onslide (without a ⟨modifier⟩) is mapped to uncover.

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

The visible command does almost the same as uncover. The only difference is that if the text is not shown, it is never shown in a transparent way, but rather it is not shown at all. Thus for this command the transparency settings have no effect.

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

The invisible is the opposite of visible.

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

beamercolor works like color, but allows you to specify the slides where the text will be bold.

overprint :: LaTeXC l => l -> l Source

Inside the overprint environment, use onslide commands to specify different things that should be shown for this environment on different slides. Everything within the environment will be placed in a rectangular area of the specified width. The height and depth of the area are chosen large enough to acoommodate the largest contents of this area.

Transparency Effects

data CoverOption Source

Options for covering text

Constructors

Invisible

Causes covered text to completely disappear

Transparent (Maybe Float)

Causes covered text to be typset in a transparent way

Dynamic

Makes all covered text quite transparent, but in a dynamic way. The longer it will take till the text is uncovered, the stronger the transparency.

HighlyDynamic

Has the same effect as dynamic, but the effect is stronger. | StillCovered [Opaqueness] -- ^ Specifies how to render covered items -- that have not yet been uncovered. | AgainCovered [Opaqueness] -- ^ Specifies how to render covered items -- that have once more been covered, that -- is, that had been shown before but are -- now covered again.

data Opaqueness Source

Percentage of opaqueness for the specified overlays. In 'Opaqueness overlaySpecification percentageOfOpaqueness' the overlaySpecification specifies on which slides covered text should have which percentageOfOpaqueness. Unlike other overlay specifications, this overlaySpecification is a relative overlay specification.

Constructors

Opaqueness [OverlaySpec] Float 

setbeamercovered :: LaTeXC l => [CoverOption] -> l Source

The command setbeamercovered allows you to specify in a quite general way how a covered item should be rendered.

Themes

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

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