{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 707
{-# LANGUAGE DeriveDataTypeable #-}
#endif
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveGeneric #-}
module Diagrams.Path
(
Path(..), pathTrails
, ToPath (..)
, pathFromTrail
, pathFromTrailAt
, pathFromLocTrail
, pathPoints
, pathVertices'
, pathVertices
, pathOffsets
, pathCentroid
, pathLocSegments, fixPath
, scalePath
, reversePath
, explodePath
, partitionPath
) where
import Control.Arrow ((***))
import Control.Lens hiding ((#), transform, at)
import qualified Data.Foldable as F
import Data.List (partition)
import Data.Semigroup
import Data.Typeable
import Diagrams.Align
import Diagrams.Core
import Diagrams.Located
import Diagrams.Points
import Diagrams.Segment
import Diagrams.Trail
import Diagrams.TrailLike
import Diagrams.Transform
import Linear.Metric
import Linear.Vector
import GHC.Generics (Generic)
import Data.Serialize (Serialize)
newtype Path v n = Path [Located (Trail v n)]
deriving (Semigroup, Monoid, Generic
#if __GLASGOW_HASKELL__ >= 707
, Typeable
#endif
)
instance (OrderedField n, Metric v, Serialize (v n), Serialize (V (v n) (N (v n)))) =>
Serialize (Path v n)
#if __GLASGOW_HASKELL__ < 707
instance forall v. Typeable1 v => Typeable1 (Path v) where
typeOf1 _ = mkTyConApp (mkTyCon3 "diagrams-lib" "Diagrams.Path" "Path") [] `mkAppTy`
typeOf1 (undefined :: v n)
#endif
instance Wrapped (Path v n) where
type Unwrapped (Path v n) = [Located (Trail v n)]
_Wrapped' = iso (\(Path x) -> x) Path
instance Rewrapped (Path v n) (Path v' n')
instance Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) where
each = _Wrapped . traverse
instance AsEmpty (Path v n) where
_Empty = _Wrapped' . _Empty
instance Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) where
_Cons = _Wrapped . _Cons . bimapping id _Unwrapped
{-# INLINE _Cons #-}
instance Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) where
_Snoc = _Wrapped . _Snoc . bimapping _Unwrapped id
{-# INLINE _Snoc #-}
pathTrails :: Path v n -> [Located (Trail v n)]
pathTrails = op Path
deriving instance Show (v n) => Show (Path v n)
deriving instance Eq (v n) => Eq (Path v n)
deriving instance Ord (v n) => Ord (Path v n)
type instance V (Path v n) = v
type instance N (Path v n) = n
instance (Additive v, Num n) => HasOrigin (Path v n) where
moveOriginTo = over _Wrapped' . map . moveOriginTo
instance (Metric v, OrderedField n) => TrailLike (Path v n) where
trailLike = Path . (:[])
instance (HasLinearMap v, Metric v, OrderedField n)
=> Transformable (Path v n) where
transform = over _Wrapped . map . transform
instance (Metric v, OrderedField n) => Enveloped (Path v n) where
getEnvelope = F.foldMap trailEnvelope . op Path
where trailEnvelope :: Located (Trail v n) -> Envelope v n
trailEnvelope (viewLoc -> (p, t)) = moveOriginTo ((-1) *. p) (getEnvelope t)
instance (Metric v, OrderedField n) => Juxtaposable (Path v n) where
juxtapose = juxtaposeDefault
instance (Metric v, OrderedField n) => Alignable (Path v n) where
defaultBoundary = envelopeBoundary
instance (HasLinearMap v, Metric v, OrderedField n)
=> Renderable (Path v n) NullBackend where
render _ _ = mempty
class ToPath t where
toPath :: (Metric (V t), OrderedField (N t)) => t -> Path (V t) (N t)
instance ToPath (Path v n) where
toPath = id
instance ToPath (Trail v n) where
toPath = pathFromTrail
instance ToPath (Trail' l v n) where
toPath t = Path [Trail t `at` origin]
instance ToPath (Located (Trail v n)) where
toPath = pathFromLocTrail
instance ToPath (Located (Trail' l v n)) where
toPath = pathFromLocTrail . mapLoc Trail
instance ToPath (Located (Segment Closed v n)) where
toPath (viewLoc -> (p,seg))
= Path [trailFromSegments [seg] `at` p]
instance ToPath (Located [Segment Closed v n]) where
toPath (viewLoc -> (p,segs))
= Path [trailFromSegments segs `at` p]
instance ToPath (FixedSegment v n) where
toPath = toPath . fromFixedSeg
instance ToPath a => ToPath [a] where
toPath = F.foldMap toPath
pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n
pathFromTrail = trailLike . (`at` origin)
pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n
pathFromTrailAt t p = trailLike (t `at` p)
pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n
pathFromLocTrail = trailLike
pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]]
pathVertices' toler = map (trailVertices' toler) . op Path
pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]]
pathVertices = map trailVertices . op Path
pathPoints :: (Metric v, OrderedField n) => Path v n -> [[Point v n]]
pathPoints = map trailPoints . op Path
pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n]
pathOffsets = map (trailOffset . unLoc) . op Path
pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n
pathCentroid = centroid . concat . pathVertices
pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]]
pathLocSegments = map trailLocSegments . op Path
fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]]
fixPath = map fixTrail . op Path
explodePath :: (V t ~ v, N t ~ n, TrailLike t) => Path v n -> [[t]]
explodePath = map explodeTrail . op Path
partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n)
partitionPath p = (view _Unwrapped' *** view _Unwrapped') . partition p . op Path
scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n
scalePath d p = under (movedFrom (pathCentroid p)) (scale d) p
reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n
reversePath = _Wrapped . mapped %~ reverseLocTrail
instance (Metric v, OrderedField n) => Reversing (Path v n) where
reversing = _Wrapped' . mapped %~ reversing