diagrams-contrib-1.4.5: Collection of user contributions to diagrams EDSL
Safe HaskellSafe-Inferred
LanguageHaskell2010

Diagrams.TwoD.Path.Metafont.Types

Synopsis

Documentation

data PathJoin d j Source #

A PathJoin specifies the directions at both ends of a segment, and a join which describes the control points explicitly or implicitly.

Constructors

PJ 

Fields

Instances

Instances details
Functor (PathJoin d) Source # 
Instance details

Defined in Diagrams.TwoD.Path.Metafont.Types

Methods

fmap :: (a -> b) -> PathJoin d a -> PathJoin d b #

(<$) :: a -> PathJoin d b -> PathJoin d a #

Monoid (PathJoin (Maybe (PathDir n)) (Maybe (BasicJoin n))) Source # 
Instance details

Defined in Diagrams.TwoD.Path.Metafont.Types

Semigroup (PathJoin (Maybe (PathDir n)) (Maybe (BasicJoin n))) Source # 
Instance details

Defined in Diagrams.TwoD.Path.Metafont.Types

(Show d, Show j) => Show (PathJoin d j) Source # 
Instance details

Defined in Diagrams.TwoD.Path.Metafont.Types

Methods

showsPrec :: Int -> PathJoin d j -> ShowS #

show :: PathJoin d j -> String #

showList :: [PathJoin d j] -> ShowS #

j :: forall d j j. Lens (PathJoin d j) (PathJoin d j) j j Source #

d2 :: forall d j. Lens' (PathJoin d j) d Source #

d1 :: forall d j. Lens' (PathJoin d j) d Source #

data PathDir n Source #

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) 

isCurl :: PathDir n -> Bool Source #

A predicate to determine the constructor used.

type Curl n = n Source #

type Dir n = Direction V2 n Source #

data Tension 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 

Instances

Instances details
Show n => Show (Tension n) Source # 
Instance details

Defined in Diagrams.TwoD.Path.Metafont.Types

Methods

showsPrec :: Int -> Tension n -> ShowS #

show :: Tension n -> String #

showList :: [Tension n] -> ShowS #

data TensionJoin n Source #

Two tensions and two directions completely determine the control points of a segment.

Constructors

TJ 

Fields

data ControlJoin n Source #

The two intermediate control points of a segment, specified directly.

Constructors

CJ 

Fields

t2 :: forall n. Lens' (TensionJoin n) (Tension n) Source #

t1 :: forall n. Lens' (TensionJoin n) (Tension n) Source #

c2 :: forall n. Lens' (ControlJoin n) (P2 n) Source #

c1 :: forall n. Lens' (ControlJoin n) (P2 n) Source #

data P Source #

data J Source #

data MFPathData a n where Source #

MFPathData is the type manipulated by the metafont combinators.

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.

Constructors

MFS 

Fields

Instances

Instances details
Functor (MetafontSegment d j) Source # 
Instance details

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 d, Show j) => Show (MetafontSegment d j n) Source # 
Instance details

Defined in Diagrams.TwoD.Path.Metafont.Types

data MFPath d j n Source #

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

Instances

Instances details
(Show n, Show d, Show j) => Show (MFPath d j n) Source # 
Instance details

Defined in Diagrams.TwoD.Path.Metafont.Types

Methods

showsPrec :: Int -> MFPath d j n -> ShowS #

show :: MFPath d j n -> String #

showList :: [MFPath d j n] -> ShowS #

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.

x2 :: forall d j n. Lens' (MetafontSegment d j n) (P2 n) Source #

x1 :: forall d j n. Lens' (MetafontSegment d j n) (P2 n) Source #

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 #

loop :: forall d j n. Lens' (MFPath d j n) Bool Source #