{-# LANGUAGE TypeFamilies #-}

-- | Combinators to allow writing Metafont-style paths embedded in
-- Haskell, with the usual Diagrams types for points and directions.

module Diagrams.TwoD.Path.Metafont.Combinators
       (
           (.-), (-.), (.--.)
       , endpt, cyclePath
       , simpleJoin -- is this actually needed?
       , tension, tensions, controls
       , leaving, arriving
       ) where

import           Diagrams.Prelude
import           Diagrams.TwoD.Path.Metafont.Types

-- internal alias to keep the signatures readable
type Join n = PathJoin (Maybe (PathDir n)) (Maybe (BasicJoin n))

-- | /point/ @.-@ /join/ @-.@ /path/ adds /point/ to the
-- left end of the metafont /path/, connected by /join/.
(.-) :: P2 n -> MFPathData J n -> MFPathData P n
.- :: forall n. P2 n -> MFPathData J n -> MFPathData P n
(.-) = forall n. P2 n -> MFPathData J n -> MFPathData P n
MFPathPt

-- | See @.-@ above.
(-.) :: Join n -> MFPathData P n -> MFPathData J n
-. :: forall n. Join n -> MFPathData P n -> MFPathData J n
(-.) = forall n. Join n -> MFPathData P n -> MFPathData J n
MFPathJoin

infixr 5 .-
infixr 5 -.

-- | Terminate the right-end of a Metafont path at the given point.
endpt :: P2 n -> MFPathData P n
endpt :: forall n. P2 n -> MFPathData P n
endpt = forall n. P2 n -> MFPathData P n
MFPathEnd

-- | Wrap the right-end of the Metafont path back to the left-end.
-- When converted to a Diagrams 'Trail'', this will be a Loop.
cyclePath :: MFPathData P n
cyclePath :: forall n. MFPathData P n
cyclePath = forall n. MFPathData P n
MFPathCycle

-- | Add a point to the left of a Metafont path using a simple join.
-- That is, neither direction is specified, and both tensions are 1.
(.--.) :: P2 n -> MFPathData P n -> MFPathData P n
P2 n
p .--. :: forall n. P2 n -> MFPathData P n -> MFPathData P n
.--. MFPathData P n
q = P2 n
p forall n. P2 n -> MFPathData J n -> MFPathData P n
.- forall a. Monoid a => a
mempty forall n. Join n -> MFPathData P n -> MFPathData J n
-. MFPathData P n
q

infixr 5 .--.

-- | simpleJoin is the same as mempty, with a more specific type.  It
-- is provided for convenience in situations where explicit type
-- signatures would otherwise be needed, such as when building up a
-- join using lenses.
simpleJoin :: Join n
simpleJoin :: forall n. Join n
simpleJoin = forall a. Monoid a => a
mempty

-- | A join with both tensions the same.
tension :: n -> Join n
tension :: forall n. n -> Join n
tension n
t = forall d j. d -> j -> d -> PathJoin d j
PJ forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall n. Tension n -> Tension n -> TensionJoin n
TJ (forall n. n -> Tension n
TensionAmt n
t) (forall n. n -> Tension n
TensionAmt n
t)) forall a. Maybe a
Nothing

-- | A join with two tension values.
tensions :: n -> n -> Join n
tensions :: forall n. n -> n -> Join n
tensions n
tl n
tr = forall d j. d -> j -> d -> PathJoin d j
PJ forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall n. Tension n -> Tension n -> TensionJoin n
TJ (forall n. n -> Tension n
TensionAmt n
tl) (forall n. n -> Tension n
TensionAmt n
tr)) forall a. Maybe a
Nothing

-- | A join with explicit control points.  Note that these are in the
-- same coordinate system as the endpoints, not relative to the latter.
controls :: P2 n -> P2 n -> Join n
controls :: forall n. P2 n -> P2 n -> Join n
controls P2 n
u P2 n
v = forall n. Join n
simpleJoin forall a b. a -> (a -> b) -> b
& forall d j1 j2. Lens (PathJoin d j1) (PathJoin d j2) j1 j2
jforall s t a b. ASetter s t a b -> b -> s -> t
.~ (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall n. P2 n -> P2 n -> ControlJoin n
CJ P2 n
u P2 n
v)

-- | A join with the left-end direction specified.
leaving :: V2 n -> Join n
leaving :: forall n. V2 n -> Join n
leaving V2 n
d = forall a. Monoid a => a
mempty forall a b. a -> (a -> b) -> b
& forall d j. Lens' (PathJoin d j) d
d1forall s t a b. ASetter s t a b -> b -> s -> t
.~ (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Dir n -> PathDir n
PathDirDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n. v n -> Direction v n
direction forall a b. (a -> b) -> a -> b
$ V2 n
d)

-- | A join with the right-end direction specified.
arriving :: V2 n -> Join n
arriving :: forall n. V2 n -> Join n
arriving V2 n
d = forall a. Monoid a => a
mempty forall a b. a -> (a -> b) -> b
& forall d j. Lens' (PathJoin d j) d
d2forall s t a b. ASetter s t a b -> b -> s -> t
.~ (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Dir n -> PathDir n
PathDirDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n. v n -> Direction v n
direction forall a b. (a -> b) -> a -> b
$ V2 n
d)