| Safe Haskell | Safe-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
}
- data ReplaceDef = ReplaceDef {
- headerOrientation :: Orientation -> Orientation
- headerJustification :: Justification -> Justification
- headerUnits :: Units -> Units
- headerPapersize :: PaperSize -> PaperSize
- headerMagnification :: Double -> Double
- headerMultiplePage :: MultiplePage -> MultiplePage
- headerTransparentColor :: Transparent -> Transparent
- headerResolution :: Integer -> Integer
- textColor :: ColorSpec -> ColorSpec
- textFontSize :: Double -> Double
- textFont :: Font -> Font
- textFontFlags :: FontFlags -> FontFlags
- picFlipped :: Flipped -> Flipped
- picFile :: FilePath -> FilePath
- arrowType :: ArrowType -> ArrowType
- arrowStyle :: ArrowStyle -> ArrowStyle
- arrowThickness :: Double -> Double
- arrowWidth :: Double -> Double
- arrowHeight :: Double -> Double
- areaFill :: AreaFill -> AreaFill
- areaFillColor :: ColorSpec -> ColorSpec
- lineStyle :: LineStyle -> LineStyle
- lineThickness :: Integer -> Integer
- linePenColor :: ColorSpec -> ColorSpec
- lineStyleVal :: Double -> Double
- lineCapStyle :: CapStyle -> CapStyle
- lineJoinStyle :: JoinStyle -> JoinStyle
- emptyDef :: ReplaceDef
- applyReplaceDef :: ReplaceDef -> Fig -> Fig
- parse :: FilePath -> String -> Either String Fig
- pretty :: Fig -> String
- module Graphics.Fig.Syntax
Documentation
data ReplaceDef Source
Replacement operations for a figure.
A ReplaceDef value is a record of functions to apply to the leaf elements
of a Fig syntax tree (see applyReplaceDef).
Constructors
The empty replacement operation: All functions of the ReplaceDef record
are equal to the identity function.
Arguments
| :: ReplaceDef | The replacements to perform. |
| -> Fig | A figure. |
| -> Fig | The figure with replacements applied. |
Apply a replacement operation to a figure.
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.
Convert a figure to a string in the FIG format.
module Graphics.Fig.Syntax