funcmp-1.0: Functional MetaPostContentsIndex
FMP.Types
Documentation
class HasMed a where
Methods
med :: Numeric -> a -> a -> a
show/hide Instances
class HasDefault a where
Methods
default' :: a
show/hide Instances
data Dir
Constructors
C
N
NE
E
SE
S
SW
W
NW
show/hide Instances
data Pen
Constructors
DefaultPen
PenSquare (Numeric, Numeric) Numeric
PenCircle (Numeric, Numeric) Numeric
show/hide Instances
data Pattern
Constructors
DefaultPattern
DashPattern [Double]
show/hide Instances
data Equation
Constructors
NEquations [Numeric]
PEquations [Point]
Equations [Equation]
EquationCond Boolean Equation Equation
show/hide Instances
data Boolean
Constructors
Boolean Bool
BoolNum Numeric BoolRelat Numeric
BoolPnt Point BoolRelat Point
BoolOr Boolean Boolean
BoolAnd Boolean Boolean
BoolNot Boolean
show/hide Instances
data BoolRelat
Constructors
BoolEQ
BoolL
BoolLE
BoolNE
show/hide Instances
data Point
Constructors
PointPic' Int Dir
PointVar' Int Int
PointVarArray' Int Int
PointTrans' Point [Int]
PointVar Name
PointVec (Numeric, Numeric)
PointMediate Numeric Point Point
PointDirection Numeric
PointWhatever
PointPPP FunPPP Point Point
PointNMul Numeric Point
PointNeg Point
PointCond Boolean Point Point
show/hide Instances
data Numeric
Constructors
NumericVar' Int Int
NumericArray' Int Int
NumericVar Name
Numeric Double
NumericWhatever
NumericDist Point Point
NumericMediate Numeric Numeric Numeric
NumericPN FunPN Point
NumericNN FunNN Numeric
NumericNNN FunNNN Numeric Numeric
NumericNsN FunNsN [Numeric]
NumericCond Boolean Numeric Numeric
show/hide Instances
data FunPPP
Constructors
PPPAdd
PPPSub
PPPDiv
show/hide Instances
data FunPN
Constructors
PNXPart
PNYPart
PNAngle
show/hide Instances
data FunNN
Constructors
NNSinD
NNCosD
NNSqrt
NNExp
NNLog
NNRound
NNCeil
NNFloor
NNNeg
show/hide Instances
data FunNNN
Constructors
NNNAdd
NNNSub
NNNMul
NNNDiv
NNNPyth
NNNPower
show/hide Instances
data FunNsN
Constructors
NsNMin
NsNMax
show/hide Instances
class HasRelax a where
Methods
relax :: a
show/hide Instances
class HasCond a where
Methods
cond :: Boolean -> a -> a -> a
show/hide Instances
penSquare :: (Numeric, Numeric) -> Numeric -> Pen
penCircle :: (Numeric, Numeric) -> Numeric -> Pen
dashed :: Pattern
dotted :: Pattern
dashPattern :: [Double] -> Pattern
dashPattern' :: [Double] -> Pattern
boolean :: Bool -> Boolean
equations :: [Equation] -> Equation
vec :: (Numeric, Numeric) -> Point
dir :: Numeric -> Point
xy :: Point -> Point -> Point
(.*) :: Numeric -> Point -> Point
pi
exp
log
sqrt
**
sin
cos
tan
asin
acos
atan
sinh
cosh
tanh
asinh
acosh
atanh
pythAdd :: Numeric -> Numeric -> Numeric
xpart :: Point -> Numeric
ypart :: Point -> Numeric
angle :: Point -> Numeric
minimum' :: [Numeric] -> Numeric
maximum' :: [Numeric] -> Numeric
width :: IsName a => a -> Numeric
height :: IsName a => a -> Numeric
xdist :: Point -> Point -> Numeric
ydist :: Point -> Point -> Numeric
dist :: Point -> Point -> Numeric
(.=) :: IsEquation a => a -> a -> Equation
(.==) :: IsBoolean a => a -> a -> Boolean
(./=) :: IsBoolean a => a -> a -> Boolean
(.<) :: IsBoolean a => a -> a -> Boolean
(.<=) :: IsBoolean a => a -> a -> Boolean
equal :: IsEquation a => [a] -> Equation
whatever :: HasWhatever a => a
data Name
Constructors
NameInt Int
NameStr String
NameDir Dir
Hier Name Name
Global Name
show/hide Instances
global :: IsName a => a -> Name
ref :: IsName a => a -> Point
var :: IsName a => a -> Numeric
(<+) :: (IsName a, IsName b) => a -> b -> Name
(<*) :: IsName a => Int -> a -> Name
class IsName a where
Methods
toName :: a -> Name
toNameList :: [a] -> Name
show/hide Instances
Produced by Haddock version 0.8