funcmp-1.9: Functional MetaPost is a Haskell frontend to the MetaPost language

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
LanguageHaskell98

FMP.Picture

Contents

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 Show a => IsPicture a where Source #

Instances

IsPicture Char Source # 
IsPicture Int Source # 
IsPicture Integer Source # 
IsPicture () Source # 
IsPicture Numeric Source # 
IsPicture Frame Source # 
IsPicture Area Source # 
IsPicture Path Source # 
IsPicture Picture Source # 
IsPicture Tree Source # 
IsPicture Canvas Source # 
IsPicture Turtle Source # 
IsPicture a => IsPicture [a] Source # 

Methods

toPicture :: [a] -> Picture Source #

toPictureList :: [[a]] -> Picture Source #

(IsPicture a, IsPicture b) => IsPicture (a, b) Source # 

Methods

toPicture :: (a, b) -> Picture Source #

toPictureList :: [(a, b)] -> Picture Source #

(IsPicture a, IsPicture b, IsPicture c) => IsPicture (a, b, c) Source # 

Methods

toPicture :: (a, b, c) -> Picture Source #

toPictureList :: [(a, b, c)] -> Picture Source #

class IsPath a where Source #

Minimal complete definition

toPath

Methods

toPath :: a -> Path Source #

toPathList :: [a] -> Path Source #

Instances

IsPath Char Source # 
IsPath Point Source # 
IsPath Name Source # 
IsPath Path Source # 
IsPath a => IsPath [a] Source # 

Methods

toPath :: [a] -> Path Source #

toPathList :: [[a]] -> Path Source #

(Real a, Real b) => IsPath (a, b) Source # 

Methods

toPath :: (a, b) -> Path Source #

toPathList :: [(a, b)] -> Path Source #

class IsArea a where Source #

Minimal complete definition

toArea

Methods

toArea :: a -> Area Source #

Instances

IsArea Area Source # 

Methods

toArea :: Area -> Area Source #

IsArea Path Source # 

Methods

toArea :: Path -> Area Source #

IsPath a => IsArea [a] Source # 

Methods

toArea :: [a] -> Area Source #

class HasPicture a where Source #

Minimal complete definition

fromPicture

Methods

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

Instances

class HasName a where Source #

Minimal complete definition

setName, getNames

Methods

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

getNames :: a -> [Name] Source #

class HasDXY a where Source #

Minimal complete definition

setDX, getDX, setDY, getDY

Methods

setDX :: Numeric -> a -> a Source #

getDX :: a -> Maybe Numeric Source #

setDY :: Numeric -> a -> a Source #

getDY :: a -> Maybe Numeric Source #

class HasLabel a where Source #

Minimal complete definition

setLabel, removeLabel

Methods

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

removeLabel :: a -> a Source #

class HasArrowHead a where Source #

class HasStartEndDir a where Source #

class HasLayer a where Source #

Minimal complete definition

setBack, setFront, getLayer

Methods

setBack :: a -> a Source #

setFront :: a -> a Source #

getLayer :: a -> Layer Source #

class HasConcat a where Source #

Minimal complete definition

(&)

Methods

(&) :: a -> a -> a infixr 1 Source #

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

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 #

Minimal complete definition

define

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 FrameAttrib Source #

Instances

Eq FrameAttrib Source # 
Read FrameAttrib Source # 
Show FrameAttrib Source # 
HasBGColor FrameAttrib Source # 
HasColor FrameAttrib Source # 
HasShadow FrameAttrib Source # 
IsHideable FrameAttrib Source # 
HasPen FrameAttrib Source # 
HasPattern FrameAttrib Source # 
HasName FrameAttrib Source # 

data PathElemDescr Source #

Instances

Eq PathElemDescr Source # 
Read PathElemDescr Source # 
Show PathElemDescr Source # 
HasColor PathElemDescr Source # 
IsHideable PathElemDescr Source # 
HasJoin PathElemDescr Source # 
HasStartEndDir PathElemDescr Source # 
HasStartEndCut PathElemDescr Source # 
HasArrowHead PathElemDescr Source # 
HasPen PathElemDescr Source # 
HasPattern PathElemDescr Source # 
HasLabel PathElemDescr Source # 

data Path Source #

Instances

Eq Path Source # 

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Read Path Source # 
Show Path Source # 

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

HasColor Path Source # 
IsArea Path Source # 

Methods

toArea :: Path -> Area Source #

IsPath Path Source # 
IsHideable Path Source # 

Methods

hide :: Path -> Path Source #

HasDefine Path Source # 

Methods

define :: [Equation] -> Path -> Path Source #

HasJoin Path Source # 
HasStartEndDir Path Source # 
HasStartEndCut Path Source # 
HasArrowHead Path Source # 
HasPen Path Source # 
HasPattern Path Source # 
HasLabel Path Source # 

Methods

setLabel :: IsPicture b => Double -> Dir -> b -> Path -> Path Source #

removeLabel :: Path -> Path Source #

IsPicture Path Source # 
HasConcat Path Source # 

Methods

(&) :: Path -> Path -> Path Source #

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

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

data Frame Source #

Instances

Show Frame Source # 

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

HasBGColor Frame Source # 
HasColor Frame Source # 
HasRelax Frame Source # 

Methods

relax :: Frame Source #

HasShadow Frame Source # 
IsHideable Frame Source # 

Methods

hide :: Frame -> Frame Source #

HasPen Frame Source # 
HasPattern Frame Source # 
HasExtent Frame Source # 
HasDXY Frame Source # 
HasName Frame Source # 

Methods

setName :: IsName b => b -> Frame -> Frame Source #

getNames :: Frame -> [Name] Source #

IsPicture Frame Source # 

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

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

Orphan instances