funcmp-1.8: Functional MetaPost

Copyright(c) 2003-2010 Peter Simons (c) 2002-2003 Ferenc Wágner (c) 2002-2003 Meik Hellmund (c) 1998-2002 Ralf Hinze (c) 1998-2002 Joachim Korittky (c) 1998-2002 Marco Kuhlmann
LicenseGPLv3
Maintainersimons@cryp.to
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell98

FMP.Picture

Description

 

Documentation

(|-|) :: (IsPicture a, IsPicture b) => a -> b -> Picture infixl 5 Source

(|||) :: (IsPicture a, IsPicture b) => a -> b -> Picture infixl 6 Source

(|=|) :: (IsPicture a, IsPicture b) => a -> b -> Picture infixl 5 Source

(||||) :: (IsPicture a, IsPicture b) => a -> b -> Picture infixl 6 Source

(#) :: a -> (a -> b) -> b infixl 0 Source

(.&.) :: (IsPath a, IsPath b) => a -> b -> Path infixr 1 Source

(...) :: (IsPath a, IsPath b) => a -> b -> Path infixr 1 Source

(.-.) :: (IsPath a, IsPath b) => a -> b -> Path infixr 1 Source

(....) :: (IsPath a, IsPath b) => a -> b -> Path infixr 1 Source

(.--.) :: (IsPath a, IsPath b) => a -> b -> Path infixr 1 Source

class IsPath a where Source

Minimal complete definition

toPath

Methods

toPath :: a -> Path Source

toPathList :: [a] -> Path Source

Instances

IsPath Char 
IsPath Point 
IsPath Name 
IsPath Path 
IsPath a => IsPath [a] 
(Real a, Real b) => IsPath (a, b) 

class IsArea a where Source

Methods

toArea :: a -> Area Source

Instances

class HasPicture a where Source

Methods

fromPicture :: IsPicture b => b -> a Source

Instances

class HasName a where Source

Methods

setName :: IsName b => b -> a -> a Source

getNames :: a -> [Name] Source

class HasDXY a where Source

Methods

setDX :: Numeric -> a -> a Source

getDX :: a -> Maybe Numeric Source

setDY :: Numeric -> a -> a Source

getDY :: a -> Maybe Numeric Source

Instances

class HasExtent a where Source

Instances

class HasLabel a where Source

Methods

setLabel :: IsPicture b => Double -> Dir -> b -> a -> a Source

removeLabel :: a -> a Source

class HasStartEndCut a where Source

Methods

setStartCut :: IsName b => b -> a -> a Source

removeStartCut :: a -> a Source

setEndCut :: IsName b => b -> a -> a Source

removeEndCut :: a -> a Source

class HasJoin a where Source

Methods

setJoin :: BasicJoin -> a -> a Source

getJoin :: a -> BasicJoin Source

class HasLayer a where Source

Methods

setBack :: a -> a Source

setFront :: a -> a Source

getLayer :: a -> Layer Source

Instances

enumPics :: HasName a => [a] -> [a] Source

data Layer Source

Constructors

Front 
Back 

Instances

row :: IsPicture a => [a] -> Picture Source

fill :: (IsPicture a, IsArea b) => [b] -> a -> Picture Source

clip :: IsPicture a => Path -> a -> Picture Source

draw :: IsPicture a => [Path] -> a -> Picture Source

at :: (IsPicture a, IsPicture b) => Dir -> a -> b -> Picture Source

label :: (IsPicture a, IsPicture b) => Dir -> a -> b -> Picture Source

class HasDefine a where Source

Methods

define :: [Equation] -> a -> a Source

line :: (IsPath a, IsPath b) => a -> b -> Path Source

curve :: (IsPath a, IsPath b) => a -> b -> Path Source

arrow :: (IsPath b, IsPath a) => a -> b -> Path Source

data Attrib Source

Constructors

Attrib 

Fields

aNames :: [Name]
 
aColor :: Color
 
aBGColor :: Color
 

pathLength :: Num a => Path -> a Source

data AreaDescr Source

Constructors

AreaDescr 

Fields

arColor :: Color
 
arLayer :: Layer
 
arPen :: Pen
 

getDefault :: Maybe a -> a -> a Source

box :: IsPicture a => a -> Frame Source

oval :: IsPicture a => a -> Frame Source