| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Diagrams.TwoD.Path.Metafont.Types
Synopsis
- data PathJoin d j = PJ {}
- j :: forall d j j. Lens (PathJoin d j) (PathJoin d j) j j
- d2 :: forall d j. Lens' (PathJoin d j) d
- d1 :: forall d j. Lens' (PathJoin d j) d
- data PathDir n- = PathDirCurl n
- | PathDirDir (Dir n)
 
- isCurl :: PathDir n -> Bool
- type Curl n = n
- type Dir n = Direction V2 n
- type BasicJoin n = Either (TensionJoin n) (ControlJoin n)
- data Tension n- = TensionAmt n
- | TensionAtLeast n
 
- getTension :: Tension n -> n
- data TensionJoin n = TJ {}
- data ControlJoin n = CJ {}
- t2 :: forall n. Lens' (TensionJoin n) (Tension n)
- t1 :: forall n. Lens' (TensionJoin n) (Tension n)
- c2 :: forall n. Lens' (ControlJoin n) (P2 n)
- c1 :: forall n. Lens' (ControlJoin n) (P2 n)
- data P
- data J
- data MFPathData a n where- MFPathCycle :: MFPathData P n
- MFPathEnd :: P2 n -> MFPathData P n
- MFPathPt :: P2 n -> MFPathData J n -> MFPathData P n
- MFPathJoin :: PathJoin (Maybe (PathDir n)) (Maybe (BasicJoin n)) -> MFPathData P n -> MFPathData J n
 
- data MetafontSegment d j n = MFS {}
- data MFPath d j n = MFP {- _loop :: Bool
- _segs :: [MetafontSegment d j n]
 
- type MFP n = MFPath (Maybe (PathDir n)) (BasicJoin n) n
- type MFS n = MetafontSegment (Maybe (PathDir n)) (BasicJoin n) n
- x2 :: forall d j n. Lens' (MetafontSegment d j n) (P2 n)
- x1 :: forall d j n. Lens' (MetafontSegment d j n) (P2 n)
- pj :: forall d j n d j. Lens (MetafontSegment d j n) (MetafontSegment d j n) (PathJoin d j) (PathJoin d j)
- segs :: forall d j n d j n. Lens (MFPath d j n) (MFPath d j n) [MetafontSegment d j n] [MetafontSegment d j n]
- loop :: forall d j n. Lens' (MFPath d j n) Bool
Documentation
A PathJoin specifies the directions at both ends of a segment,
 and a join which describes the control points explicitly or implicitly.
Instances
A direction can be specified at any point of a path. A curl should only be specified at the endpoints. The endpoints default to curl 1 if not set.
Constructors
| PathDirCurl n | |
| PathDirDir (Dir n) | 
Instances
type BasicJoin n = Either (TensionJoin n) (ControlJoin n) Source #
Higher Tension brings the path closer to a straight line
 between segments.  Equivalently, it brings the control points
 closer to the endpoints.  TensionAmt introduces a fixed tension.
 TensionAtLeast introduces a tension which will be increased if by
 so doing, an inflection point can be eliminated.
Constructors
| TensionAmt n | |
| TensionAtLeast n | 
getTension :: Tension n -> n Source #
data TensionJoin n Source #
Two tensions and two directions completely determine the control points of a segment.
Instances
data ControlJoin n Source #
The two intermediate control points of a segment, specified directly.
Instances
data MFPathData a n where Source #
MFPathData is the type manipulated by the metafont combinators.
Constructors
| MFPathCycle :: MFPathData P n | |
| MFPathEnd :: P2 n -> MFPathData P n | |
| MFPathPt :: P2 n -> MFPathData J n -> MFPathData P n | |
| MFPathJoin :: PathJoin (Maybe (PathDir n)) (Maybe (BasicJoin n)) -> MFPathData P n -> MFPathData J n | 
data MetafontSegment d j n Source #
MetafontSegment is used internally in solving the metafont
 equations.  It represents a segment with two known endpoints, and a
 join, which may be specified in various ways.
Instances
| Functor (MetafontSegment d j) Source # | |
| Defined in Diagrams.TwoD.Path.Metafont.Types Methods fmap :: (a -> b) -> MetafontSegment d j a -> MetafontSegment d j b # (<$) :: a -> MetafontSegment d j b -> MetafontSegment d j a # | |
| (Show n, Show j, Show d) => Show (MetafontSegment d j n) Source # | |
| Defined in Diagrams.TwoD.Path.Metafont.Types Methods showsPrec :: Int -> MetafontSegment d j n -> ShowS # show :: MetafontSegment d j n -> String # showList :: [MetafontSegment d j n] -> ShowS # | |
MFPath is the type used internally in solving the metafont
 equations.  The direction and join types are progressively refined
 until all control points are known.  The loop flag affects both
 the equations to be solved and the type of Trail in the result.
 If constructing an MFPath in new code, the responsibility rests
 on the user to ensure that successive MetafontSegments share an
 endpoint.  If this is not true, the result is undefined.
Constructors
| MFP | |
| Fields 
 | |
type MFP n = MFPath (Maybe (PathDir n)) (BasicJoin n) n Source #
MFP is a type synonym to clarify signatures in Metafont.Internal.
 Note that the type permits segments which are "overspecified",
 having one or both directions specified, and also a ControlJoin.
 In this case, Metafont.Internal ignores the directions.
type MFS n = MetafontSegment (Maybe (PathDir n)) (BasicJoin n) n Source #
MFS is a type synonym to clarify signatures in Metafont.Internal.
pj :: forall d j n d j. Lens (MetafontSegment d j n) (MetafontSegment d j n) (PathJoin d j) (PathJoin d j) Source #
segs :: forall d j n d j n. Lens (MFPath d j n) (MFPath d j n) [MetafontSegment d j n] [MetafontSegment d j n] Source #