funcmp-1.0: Functional MetaPostContentsIndex
FMP.Picture
Documentation
(|-|) :: (IsPicture a, IsPicture b) => a -> b -> Picture
(|||) :: (IsPicture a, IsPicture b) => a -> b -> Picture
(|=|) :: (IsPicture a, IsPicture b) => a -> b -> Picture
(||||) :: (IsPicture a, IsPicture b) => a -> b -> Picture
(#) :: a -> (a -> b) -> b
(.&.) :: (IsPath a, IsPath b) => a -> b -> Path
(...) :: (IsPath a, IsPath b) => a -> b -> Path
(.-.) :: (IsPath a, IsPath b) => a -> b -> Path
(....) :: (IsPath a, IsPath b) => a -> b -> Path
(.--.) :: (IsPath a, IsPath b) => a -> b -> Path
class Show a => IsPicture a where
Methods
toPicture :: a -> Picture
toPictureList :: [a] -> Picture
show/hide Instances
class IsPath a where
Methods
toPath :: a -> Path
toPathList :: [a] -> Path
show/hide Instances
class IsArea a where
Methods
toArea :: a -> Area
show/hide Instances
class HasPicture a where
Methods
fromPicture :: IsPicture b => b -> a
show/hide Instances
class HasName a where
Methods
setName :: IsName b => b -> a -> a
getNames :: a -> [Name]
show/hide Instances
class HasDXY a where
Methods
setDX :: Numeric -> a -> a
getDX :: a -> Maybe Numeric
setDY :: Numeric -> a -> a
getDY :: a -> Maybe Numeric
show/hide Instances
class HasExtent a where
Methods
setWidth :: Numeric -> a -> a
removeWidth :: a -> a
getWidth :: a -> Maybe Numeric
setHeight :: Numeric -> a -> a
removeHeight :: a -> a
getHeight :: a -> Maybe Numeric
show/hide Instances
class HasLabel a where
Methods
setLabel :: IsPicture b => Double -> Dir -> b -> a -> a
removeLabel :: a -> a
show/hide Instances
class HasPattern a where
Methods
setPattern :: Pattern -> a -> a
setDefaultPattern :: a -> a
getPattern :: a -> Pattern
show/hide Instances
class HasPen a where
Methods
setPen :: Pen -> a -> a
setDefaultPen :: a -> a
getPen :: a -> Pen
show/hide Instances
class HasArrowHead a where
Methods
setArrowHead :: ArrowHead -> a -> a
removeArrowHead :: a -> a
getArrowHead :: a -> Maybe ArrowHead
setStartArrowHead :: ArrowHead -> a -> a
removeStartArrowHead :: a -> a
getStartArrowHead :: a -> Maybe ArrowHead
show/hide Instances
class HasStartEndCut a where
Methods
setStartCut :: IsName b => b -> a -> a
removeStartCut :: a -> a
setEndCut :: IsName b => b -> a -> a
removeEndCut :: a -> a
show/hide Instances
class HasStartEndDir a where
Methods
setStartAngle :: Numeric -> a -> a
setEndAngle :: Numeric -> a -> a
setStartCurl :: Numeric -> a -> a
setEndCurl :: Numeric -> a -> a
setStartVector :: Point -> a -> a
setEndVector :: Point -> a -> a
removeStartDir :: a -> a
removeEndDir :: a -> a
show/hide Instances
class HasJoin a where
Methods
setJoin :: BasicJoin -> a -> a
getJoin :: a -> BasicJoin
show/hide Instances
class HasShadow a where
Methods
setShadow :: (Numeric, Numeric) -> a -> a
clearShadow :: a -> a
getShadow :: a -> Maybe (Numeric, Numeric)
show/hide Instances
class HasLayer a where
Methods
setBack :: a -> a
setFront :: a -> a
getLayer :: a -> Layer
show/hide Instances
class HasConcat a where
Methods
(&) :: a -> a -> a
show/hide Instances
class IsHideable a where
Methods
hide :: a -> a
show/hide Instances
joinCat :: BasicJoin
joinFree :: BasicJoin
joinBounded :: BasicJoin
joinStraight :: BasicJoin
joinTense :: BasicJoin
joinTension :: Tension -> BasicJoin
joinTensions :: Tension -> Tension -> BasicJoin
joinControl :: Point -> BasicJoin
joinControls :: Point -> Point -> BasicJoin
tension :: Numeric -> Tension
tensionAtLeast :: Numeric -> Tension
buildCycle :: Path -> Path -> Path
transformPath :: Transformation -> Path -> Path
mm :: Numeric
pt :: Numeric
dd :: Numeric
bp :: Numeric
cm :: Numeric
pc :: Numeric
cc :: Numeric
inch :: Numeric
up :: Point
down :: Point
left :: Point
right :: Point
fullcircle :: Path
halfcircle :: Path
quartercircle :: Path
unitsquare :: Path
enumPics :: HasName a => [a] -> [a]
image :: BitDepth -> [String] -> Picture
data Picture
Constructors
Attributes Attrib Picture
Overlay [Equation] (Maybe Int) [Picture]
Define [Equation] Picture
Frame FrameAttrib [Equation] Path Picture
Draw [Path] Picture
Fill [Area] Picture
Clip Path Picture
Empty Numeric Numeric
Tex String
Text String
BitLine Point BitDepth String
PTransform Transformation Picture
TrueBox Picture
show/hide Instances
data Layer
Constructors
Front
Back
show/hide Instances
data Transformation
Constructors
Transformation Numeric Numeric Numeric Numeric Numeric Numeric
show/hide Instances
data BitDepth
Constructors
Depth1
Depth8
Depth24
show/hide Instances
row :: IsPicture a => [a] -> Picture
column :: IsPicture a => [a] -> Picture
rowSepBy :: IsPicture a => Numeric -> [a] -> Picture
columnSepBy :: IsPicture a => Numeric -> [a] -> Picture
vspace :: Numeric -> Picture
hspace :: Numeric -> Picture
space :: Numeric -> Numeric -> Picture
fill :: (IsPicture a, IsArea b) => [b] -> a -> Picture
clip :: IsPicture a => Path -> a -> Picture
draw :: IsPicture a => [Path] -> a -> Picture
at :: (IsPicture a, IsPicture b) => Dir -> a -> b -> Picture
label :: (IsPicture a, IsPicture b) => Dir -> a -> b -> Picture
overlay :: IsPicture a => [Equation] -> [a] -> Picture
overlay' :: IsPicture a => [Equation] -> Maybe Int -> [a] -> Picture
ooalign :: IsPicture a => [a] -> Picture
class HasDefine a where
Methods
define :: [Equation] -> a -> a
show/hide Instances
text :: String -> Picture
tex :: String -> Picture
math :: String -> Picture
empty :: Picture
setTrueBoundingBox :: IsPicture a => a -> Picture
scale :: IsPicture a => Numeric -> a -> Picture
rotate :: IsPicture a => Numeric -> a -> Picture
transform :: IsPicture a => Transformation -> a -> Picture
affine :: (Numeric, Numeric, Numeric, Numeric, Numeric, Numeric) -> Transformation
shifted :: (Numeric, Numeric) -> Transformation
rotated :: Numeric -> Transformation
reflectedX :: Transformation
reflectedY :: Transformation
reflectX :: IsPicture a => a -> Picture
reflectY :: IsPicture a => a -> Picture
scaledX :: Numeric -> Transformation
scaledY :: Numeric -> Transformation
scaled :: Numeric -> Transformation
skewedX :: Numeric -> Transformation
skewX :: IsPicture a => Numeric -> a -> Picture
skewedY :: Numeric -> Transformation
skewY :: IsPicture a => Numeric -> a -> Picture
line :: (IsPath a, IsPath b) => a -> b -> Path
curve :: (IsPath a, IsPath b) => a -> b -> Path
arrow :: (IsPath b, IsPath a) => a -> b -> Path
cycle' :: Path
lastNameIsDir :: Name -> Bool
defaultArrowHead :: ArrowHead
arrowHeadBig :: ArrowHead
arrowHeadSize :: Double -> Double -> ArrowHead
setArrowHeadStyle :: ArrowHeadStyle -> ArrowHead -> ArrowHead
getArrowHeadStyle :: ArrowHead -> ArrowHeadStyle
ahFilled :: ArrowHeadStyle
ahLine :: ArrowHeadStyle
data Attrib
Constructors
Attrib
aNames :: [Name]
aColor :: Color
aBGColor :: Color
show/hide Instances
stdAttrib :: Attrib
data FrameAttrib
Constructors
FrameAttrib
faNames :: [Name]
faColor, faBGColor :: Color
faPen :: Pen
faPattern :: Pattern
faShadow :: (Maybe (Numeric, Numeric))
faVisible :: Bool
show/hide Instances
stdFrameAttrib :: FrameAttrib
data PathElemDescr
Constructors
PathElemDescr
peColor :: Color
pePen :: Pen
peArrowHead :: (Maybe ArrowHead)
peSArrowHead :: (Maybe ArrowHead)
pePattern :: Pattern
peVisible :: Bool
peStartCut, peEndCut :: (Maybe CutPic)
peStartDir, peEndDir :: Dir'
peJoin :: BasicJoin
peLabels :: [PathLabel]
show/hide Instances
stdPathElemDescr :: PathElemDescr
data Path
Constructors
PathBuildCycle Path Path
PathTransform Transformation Path
PathPoint Point
PathCycle
PathJoin Path PathElemDescr Path
PathEndDir Point Dir'
PathDefine [Equation] Path
show/hide Instances
data PathLabel
Constructors
PathLabel Picture Double Dir
show/hide Instances
data ArrowHead
Constructors
DefaultArrowHead
ArrowHead (Maybe Double) (Maybe Double) ArrowHeadStyle
show/hide Instances
data ArrowHeadStyle
Constructors
AHFilled
AHLine
show/hide Instances
data CutPic
Constructors
CutPicTrans CutPic [Int]
CutPic Name
CutPic' String
show/hide Instances
pathLength :: Num a => Path -> a
forEachPath :: (PathElemDescr -> PathElemDescr) -> Path -> Path
data Dir'
Constructors
DirEmpty
DirCurl Numeric
DirDir Numeric
DirVector Point
show/hide Instances
data BasicJoin
Constructors
BJCat
BJFree
BJBounded
BJStraight
BJTense
BJTension Tension
BJTension2 Tension Tension
BJControls Point
BJControls2 Point Point
show/hide Instances
data Tension
Constructors
Tension Numeric
TensionAtLeast Numeric
show/hide Instances
data Area
Constructors
Area AreaDescr Path
show/hide Instances
data AreaDescr
Constructors
AreaDescr
arColor :: Color
arLayer :: Layer
arPen :: Pen
show/hide Instances
stdAreaDescr :: AreaDescr
getDefault :: Maybe a -> a -> a
data Frame
Constructors
Frame' FrameAttrib ExtentAttrib Path Picture
show/hide Instances
data AbsOrRel
Constructors
AORAbs Numeric
AORRel Numeric
AORDefault
show/hide Instances
data ExtentAttrib
Constructors
ExtentAttrib
eaX, eaY :: AbsOrRel
eaEqsDX :: [Equation]
eaEqsDY :: [Equation]
eaEqsWidth :: [Equation]
eaEqsHeight :: [Equation]
eaEqs :: [Equation]
show/hide Instances
stdExtentAttrib :: ExtentAttrib
dot :: Frame
bullet :: Frame
box :: IsPicture a => a -> Frame
triangle :: IsPicture a => a -> Frame
triAngle :: IsPicture a => Numeric -> a -> Frame
rbox :: IsPicture a => Numeric -> a -> Frame
oval :: IsPicture a => a -> Frame
circle :: IsPicture a => a -> Frame
Produced by Haddock version 0.8