fig-1.4.0: Manipulation of FIG files

Safe HaskellSafe-Inferred

Graphics.Fig

Description

The example below illustrates the typical use of the Fig library. The program parses a FIG file read from stdin, applies a transformation to the figure, and emits the result to stdout.

module Main where

import Graphics.Fig

main = do
     input <- getContents
     either fail succeed
         (parse "stdin" input)
     where
     succeed = putStr . pretty . process

process = applyReplaceDef replaceDef

replaceDef =
     emptyDef
         { linePenColor = const Magenta
         , arrowWidth = (* 1.5)
         , areaFillColor = x ->
             case x of
                 Green4 -> LtBlue
                 LtBlue -> Green4
                 _ -> x
         }

Synopsis

Documentation

emptyDef :: ReplaceDefSource

The empty replacement operation: All functions of the ReplaceDef record are equal to the identity function.

applyReplaceDefSource

Arguments

:: ReplaceDef

The replacements to perform.

-> Fig

A figure.

-> Fig

The figure with replacements applied.

Apply a replacement operation to a figure.

parseSource

Arguments

:: FilePath

Name of the input file (to use in error messages).

-> String

String in FIG format.

-> Either String Fig

Error message if failed parse; figure if successful parse.

Parse a string in the FIG format.

prettySource

Arguments

:: Fig

A figure.

-> String

The figure in FIG format.

Convert a figure to a string in the FIG format.