{-# LANGUAGE TemplateHaskell  #-}
{-# LANGUAGE DeriveFunctor  #-}
{-# LANGUAGE UndecidableInstances  #-}
module Data.Geometry.PolyLine where
import           Control.Lens
import           Data.Aeson
import           Data.Bifoldable
import           Data.Bifunctor
import           Data.Bitraversable
import           Data.Ext
import qualified Data.Foldable as F
import           Data.Geometry.Box
import           Data.Geometry.LineSegment
import           Data.Geometry.Point
import           Data.Geometry.Properties
import           Data.Geometry.Transformation
import           Data.Geometry.Vector
import           Data.LSeq (LSeq, pattern (:<|))
import qualified Data.LSeq as LSeq
import qualified Data.List.NonEmpty as NE
import           GHC.Generics (Generic)
import           GHC.TypeLits
newtype PolyLine d p r = PolyLine { _points :: LSeq 2 (Point d r :+ p) } deriving (Generic)
makeLenses ''PolyLine
deriving instance (Show r, Show p, Arity d) => Show    (PolyLine d p r)
deriving instance (Eq r, Eq p, Arity d)     => Eq      (PolyLine d p r)
deriving instance (Ord r, Ord p, Arity d)   => Ord     (PolyLine d p r)
instance Arity d => Functor (PolyLine d p) where
  fmap f (PolyLine ps) = PolyLine $ fmap (first (fmap f)) ps
type instance Dimension (PolyLine d p r) = d
type instance NumType   (PolyLine d p r) = r
instance Semigroup (PolyLine d p r) where
  (PolyLine pts) <> (PolyLine pts') = PolyLine $ pts <> pts'
instance Arity d => IsBoxable (PolyLine d p r) where
  boundingBox = boundingBoxList . NE.fromList . toListOf (points.traverse.core)
instance (Fractional r, Arity d, Arity (d + 1)) => IsTransformable (PolyLine d p r) where
  transformBy = transformPointFunctor
instance PointFunctor (PolyLine d p) where
  pmap f = over points (fmap (first f))
instance Arity d => Bifunctor (PolyLine d) where
  bimap = bimapDefault
instance Arity d => Bifoldable (PolyLine d) where
  bifoldMap = bifoldMapDefault
instance Arity d => Bitraversable (PolyLine d) where
  bitraverse f g (PolyLine pts) = PolyLine <$> traverse (bitraverse (traverse g) f) pts
instance (ToJSON p, ToJSON r, Arity d) => ToJSON (PolyLine d p r) where
    toEncoding = genericToEncoding defaultOptions
instance (FromJSON p, FromJSON r, Arity d, KnownNat d) => FromJSON (PolyLine d p r)
fromPoints :: [Point d r :+ p] -> Maybe (PolyLine d p r)
fromPoints = fmap PolyLine . LSeq.eval (C @ 2) . LSeq.fromList
fromPointsUnsafe :: [Point d r :+ p] -> PolyLine d p r
fromPointsUnsafe = PolyLine . LSeq.forceLSeq (C @ 2) . LSeq.fromList
fromPointsUnsafe' :: (Monoid p) => [Point d r] -> PolyLine d p r
fromPointsUnsafe' = fromPointsUnsafe . map (\p -> p :+ mempty)
fromLineSegment                     :: LineSegment d p r -> PolyLine d p r
fromLineSegment ~(LineSegment' p q) = fromPointsUnsafe [p,q]
asLineSegment                            :: PolyLine d p r -> LineSegment d p r
asLineSegment (PolyLine (p :<| q :<| _)) = ClosedLineSegment p q
asLineSegment'                :: PolyLine d p r -> Maybe (LineSegment d p r)
asLineSegment' (PolyLine pts) = case F.toList pts of
                                  [p,q] -> Just $ ClosedLineSegment p q
                                  _     -> Nothing
edgeSegments    :: Arity d => PolyLine d p r -> LSeq 1 (LineSegment d p r)
edgeSegments pl = let vs = pl^.points
                  in LSeq.zipWith ClosedLineSegment (LSeq.init vs) (LSeq.tail vs)
interpolatePoly      :: (RealFrac r, Arity d) => r -> PolyLine d p r -> Point d r
interpolatePoly t pl = let i = floor t in case edgeSegments pl^?ix i of
                         Nothing -> pl^.points.to LSeq.last.core
                         Just e  -> interpolate (t-fromIntegral i) e