{-# LANGUAGE ConstraintKinds     #-}
{-# LANGUAGE DeriveFunctor       #-}
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell     #-}
{-# LANGUAGE TypeFamilies        #-}
{-# LANGUAGE ViewPatterns        #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Diagrams.TwoD.Polygons
-- Copyright   :  (c) 2011 diagrams-lib team (see LICENSE)
-- License     :  BSD-style (see LICENSE)
-- Maintainer  :  diagrams-discuss@googlegroups.com
--
-- This module defines a general API for creating various types of
-- polygons.
--
-----------------------------------------------------------------------------

module Diagrams.TwoD.Polygons(
        -- * Polygons
          PolyType(..)
        , PolyOrientation(..)
        , PolygonOpts(..), polyType, polyOrient, polyCenter

        , polygon
        , polyTrail

        -- ** Generating polygon vertices

        , polyPolarTrail
        , polySidesTrail
        , polyRegularTrail

        , orient

        -- * Star polygons
        , StarOpts(..)
        , star

        -- ** Function graphs
        -- $graphs
        , GraphPart(..)
        , orbits, mkGraph

    ) where

import           Control.Lens         (Lens', generateSignatures, lensRules,
                                       makeLensesWith, view, (.~), (^.))
import           Control.Monad        (forM, liftM)
import           Control.Monad.ST     (ST, runST)
import           Data.Array.ST        (STUArray, newArray, readArray,
                                       writeArray)
import           Data.Default.Class
import           Data.List            (maximumBy, minimumBy)
import           Data.Maybe           (catMaybes)
import           Data.Ord             (comparing)

import           Diagrams.Angle
import           Diagrams.Core
import           Diagrams.Located
import           Diagrams.Path
import           Diagrams.Points      (centroid)
import           Diagrams.Trail
import           Diagrams.TrailLike
import           Diagrams.TwoD.Types
import           Diagrams.TwoD.Vector (leftTurn, unitX, unitY, unit_Y)
import           Diagrams.Util        (tau, ( # ))

import           Linear.Affine
import           Linear.Metric
import           Linear.Vector

-- | Method used to determine the vertices of a polygon.
data PolyType n = PolyPolar [Angle n] [n]
                -- ^ A \"polar\" polygon.
                --
                --   * The first argument is a list of /central/
                --     /angles/ from each vertex to the next.
                --
                --   * The second argument is a list of /radii/ from
                --     the origin to each successive vertex.
                --
                --   To construct an /n/-gon, use a list of /n-1/
                --   angles and /n/ radii.  Extra angles or radii
                --   are ignored.
                --
                --   Cyclic polygons (with all vertices lying on a
                --   circle) can be constructed using a second
                --   argument of @(repeat r)@.

              | PolySides [Angle n] [n]
                -- ^ A polygon determined by the distance between
                --   successive vertices and the external angles formed
                --   by each three successive vertices. In other
                --   words, a polygon specified by \"turtle
                --   graphics\": go straight ahead x1 units; turn by
                --   external angle a1; go straight ahead x2 units; turn by
                --   external angle a2; etc. The polygon will be centered
                --   at the /centroid/ of its vertices.
                --
                --   * The first argument is a list of /vertex/
                --     /angles/, giving the external angle at each vertex
                --     from the previous vertex to the next.  The
                --     first angle in the list is the external angle at
                --     the /second/ vertex; the first edge always starts
                --     out heading in the positive y direction from
                --     the first vertex.
                --
                --   * The second argument is a list of distances
                --     between successive vertices.
                --
                --   To construct an /n/-gon, use a list of /n-2/
                --   angles and /n-1/ edge lengths.  Extra angles or
                --   lengths are ignored.

              | PolyRegular Int n
                -- ^ A regular polygon with the given number of
                --   sides (first argument) and the given radius
                --   (second argument).

-- | Determine how a polygon should be oriented.
data PolyOrientation n = NoOrient        -- ^ No special orientation; the first
                                         --   vertex will be at (1,0).
                       | OrientH         -- ^ Orient /horizontally/, so the
                                         --   bottommost edge is parallel to
                                         --   the x-axis.
                                         --   This is the default.
                       | OrientV         -- ^ Orient /vertically/, so the
                                         --   leftmost edge is parallel to the
                                         --   y-axis.
                       | OrientTo (V2 n) -- ^ Orient so some edge is
                                         --   /facing/ /in/ /the/ /direction/
                                         --   /of/, that is, perpendicular
                                         --   to, the given vector.
                       deriving (PolyOrientation n -> PolyOrientation n -> Bool
forall n. Eq n => PolyOrientation n -> PolyOrientation n -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PolyOrientation n -> PolyOrientation n -> Bool
$c/= :: forall n. Eq n => PolyOrientation n -> PolyOrientation n -> Bool
== :: PolyOrientation n -> PolyOrientation n -> Bool
$c== :: forall n. Eq n => PolyOrientation n -> PolyOrientation n -> Bool
Eq, PolyOrientation n -> PolyOrientation n -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {n}. Ord n => Eq (PolyOrientation n)
forall n. Ord n => PolyOrientation n -> PolyOrientation n -> Bool
forall n.
Ord n =>
PolyOrientation n -> PolyOrientation n -> Ordering
forall n.
Ord n =>
PolyOrientation n -> PolyOrientation n -> PolyOrientation n
min :: PolyOrientation n -> PolyOrientation n -> PolyOrientation n
$cmin :: forall n.
Ord n =>
PolyOrientation n -> PolyOrientation n -> PolyOrientation n
max :: PolyOrientation n -> PolyOrientation n -> PolyOrientation n
$cmax :: forall n.
Ord n =>
PolyOrientation n -> PolyOrientation n -> PolyOrientation n
>= :: PolyOrientation n -> PolyOrientation n -> Bool
$c>= :: forall n. Ord n => PolyOrientation n -> PolyOrientation n -> Bool
> :: PolyOrientation n -> PolyOrientation n -> Bool
$c> :: forall n. Ord n => PolyOrientation n -> PolyOrientation n -> Bool
<= :: PolyOrientation n -> PolyOrientation n -> Bool
$c<= :: forall n. Ord n => PolyOrientation n -> PolyOrientation n -> Bool
< :: PolyOrientation n -> PolyOrientation n -> Bool
$c< :: forall n. Ord n => PolyOrientation n -> PolyOrientation n -> Bool
compare :: PolyOrientation n -> PolyOrientation n -> Ordering
$ccompare :: forall n.
Ord n =>
PolyOrientation n -> PolyOrientation n -> Ordering
Ord, Int -> PolyOrientation n -> ShowS
forall n. Show n => Int -> PolyOrientation n -> ShowS
forall n. Show n => [PolyOrientation n] -> ShowS
forall n. Show n => PolyOrientation n -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PolyOrientation n] -> ShowS
$cshowList :: forall n. Show n => [PolyOrientation n] -> ShowS
show :: PolyOrientation n -> String
$cshow :: forall n. Show n => PolyOrientation n -> String
showsPrec :: Int -> PolyOrientation n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> PolyOrientation n -> ShowS
Show, ReadPrec [PolyOrientation n]
ReadPrec (PolyOrientation n)
ReadS [PolyOrientation n]
forall n. Read n => ReadPrec [PolyOrientation n]
forall n. Read n => ReadPrec (PolyOrientation n)
forall n. Read n => Int -> ReadS (PolyOrientation n)
forall n. Read n => ReadS [PolyOrientation n]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PolyOrientation n]
$creadListPrec :: forall n. Read n => ReadPrec [PolyOrientation n]
readPrec :: ReadPrec (PolyOrientation n)
$creadPrec :: forall n. Read n => ReadPrec (PolyOrientation n)
readList :: ReadS [PolyOrientation n]
$creadList :: forall n. Read n => ReadS [PolyOrientation n]
readsPrec :: Int -> ReadS (PolyOrientation n)
$creadsPrec :: forall n. Read n => Int -> ReadS (PolyOrientation n)
Read)

-- | Options for specifying a polygon.
data PolygonOpts n = PolygonOpts
                   { forall n. PolygonOpts n -> PolyType n
_polyType   :: PolyType n
                   , forall n. PolygonOpts n -> PolyOrientation n
_polyOrient :: PolyOrientation n
                   , forall n. PolygonOpts n -> Point V2 n
_polyCenter :: Point V2 n
                   }

makeLensesWith (generateSignatures .~ False $ lensRules) ''PolygonOpts

-- | Specification for the polygon's vertices.
polyType :: Lens' (PolygonOpts n) (PolyType n)

-- | Should a rotation be applied to the polygon in order to orient it in a
--   particular way?
polyOrient :: Lens' (PolygonOpts n) (PolyOrientation n)

-- | Should a translation be applied to the polygon in order to place the center
--   at a particular location?
polyCenter :: Lens' (PolygonOpts n) (Point V2 n)

-- | The default polygon is a regular pentagon of radius 1, centered
--   at the origin, aligned to the x-axis.
instance Num n => Default (PolygonOpts n) where
    def :: PolygonOpts n
def = forall n.
PolyType n -> PolyOrientation n -> Point V2 n -> PolygonOpts n
PolygonOpts (forall n. Int -> n -> PolyType n
PolyRegular Int
5 n
1) forall n. PolyOrientation n
OrientH forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin

-- | Generate a polygon.  See 'PolygonOpts' for more information.
polyTrail :: OrderedField n => PolygonOpts n -> Located (Trail V2 n)
polyTrail :: forall n. OrderedField n => PolygonOpts n -> Located (Trail V2 n)
polyTrail PolygonOpts n
po = forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation V2 n
ori Located (Trail V2 n)
tr
    where
        tr :: Located (Trail V2 n)
tr = case PolygonOpts n
poforall s a. s -> Getting a s a -> a
^.forall n. Lens' (PolygonOpts n) (PolyType n)
polyType of
            PolyPolar [Angle n]
ans [n]
szs -> forall n.
OrderedField n =>
[Angle n] -> [n] -> Located (Trail V2 n)
polyPolarTrail [Angle n]
ans [n]
szs
            PolySides [Angle n]
ans [n]
szs -> forall n.
OrderedField n =>
[Angle n] -> [n] -> Located (Trail V2 n)
polySidesTrail [Angle n]
ans [n]
szs
            PolyRegular Int
n n
r   -> forall n. OrderedField n => Int -> n -> Located (Trail V2 n)
polyRegularTrail Int
n n
r
        ori :: Transformation V2 n
ori = case PolygonOpts n
poforall s a. s -> Getting a s a -> a
^.forall n. Lens' (PolygonOpts n) (PolyOrientation n)
polyOrient of
            PolyOrientation n
OrientH    -> forall n.
OrderedField n =>
V2 n -> Located (Trail V2 n) -> Transformation V2 n
orient forall (v :: * -> *) n. (R2 v, Additive v, Num n) => v n
unit_Y Located (Trail V2 n)
tr
            PolyOrientation n
OrientV    -> forall n.
OrderedField n =>
V2 n -> Located (Trail V2 n) -> Transformation V2 n
orient forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX  Located (Trail V2 n)
tr
            OrientTo V2 n
v -> forall n.
OrderedField n =>
V2 n -> Located (Trail V2 n) -> Transformation V2 n
orient V2 n
v      Located (Trail V2 n)
tr
            PolyOrientation n
NoOrient   -> forall a. Monoid a => a
mempty

-- | Generate the polygon described by the given options.
polygon :: (InSpace V2 n t, TrailLike t) => PolygonOpts n -> t
polygon :: forall n t. (InSpace V2 n t, TrailLike t) => PolygonOpts n -> t
polygon = forall t. TrailLike t => Located (Trail (V t) (N t)) -> t
trailLike forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. OrderedField n => PolygonOpts n -> Located (Trail V2 n)
polyTrail

-- | Generate the located trail of a polygon specified by polar data
--   (central angles and radii). See 'PolyPolar'.
polyPolarTrail :: OrderedField n =>  [Angle n] -> [n] -> Located (Trail V2 n)
polyPolarTrail :: forall n.
OrderedField n =>
[Angle n] -> [n] -> Located (Trail V2 n)
polyPolarTrail [] [n]
_ = forall (v :: * -> *) n. (Metric v, OrderedField n) => Trail v n
emptyTrail forall a. a -> Point (V a) (N a) -> Located a
`at` forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin
polyPolarTrail [Angle n]
_ [] = forall (v :: * -> *) n. (Metric v, OrderedField n) => Trail v n
emptyTrail forall a. a -> Point (V a) (N a) -> Located a
`at` forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin
polyPolarTrail [Angle n]
ans (n
r:[n]
rs) = Trail V2 n
tr forall a. a -> Point (V a) (N a) -> Located a
`at` Point V2 n
p1
  where
    p1 :: Point V2 n
p1 = forall n. (n, n) -> P2 n
p2 (n
1,n
0) forall a b. a -> (a -> b) -> b
# forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale n
r
    tr :: Trail V2 n
tr = forall (v :: * -> *) n. Trail v n -> Trail v n
closeTrail forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[Point v n] -> Trail v n
trailFromVertices forall a b. (a -> b) -> a -> b
$
           forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
             (\Angle n
a n
l -> forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate Angle n
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale n
l forall a b. (a -> b) -> a -> b
$ forall n. (n, n) -> P2 n
p2 (n
1,n
0))
             (forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
(^+^) forall (f :: * -> *) a. (Additive f, Num a) => f a
zero [Angle n]
ans)
             (n
rforall a. a -> [a] -> [a]
:[n]
rs)

-- | Generate the vertices of a polygon specified by side length and
--   angles, and a starting point for the trail such that the origin
--   is at the centroid of the vertices.  See 'PolySides'.
polySidesTrail :: OrderedField n =>  [Angle n] -> [n] -> Located (Trail V2 n)
polySidesTrail :: forall n.
OrderedField n =>
[Angle n] -> [n] -> Located (Trail V2 n)
polySidesTrail [Angle n]
ans [n]
ls = Trail V2 n
tr forall a. a -> Point (V a) (N a) -> Located a
`at` (forall (v :: * -> *) n.
(Additive v, Fractional n) =>
[Point v n] -> Point v n
centroid [Point V2 n]
ps forall a b. a -> (a -> b) -> b
# forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale (-n
1))
  where
    ans' :: [Angle n]
ans'    = forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
(^+^) forall (f :: * -> *) a. (Additive f, Num a) => f a
zero [Angle n]
ans
    offsets :: [V2 n]
offsets = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate [Angle n]
ans' (forall a b. (a -> b) -> [a] -> [b]
map (forall (v :: * -> *) n. (R2 v, Additive v, Num n) => v n
unitY forall (f :: * -> *) a. (Functor f, Num a) => f a -> a -> f a
^*) [n]
ls)
    ps :: [Point V2 n]
ps      = forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl forall (p :: * -> *) a. (Affine p, Num a) => p a -> Diff p a -> p a
(.+^) forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin [V2 n]
offsets
    tr :: Trail V2 n
tr      = forall (v :: * -> *) n. Trail v n -> Trail v n
closeTrail forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[v n] -> Trail v n
trailFromOffsets forall a b. (a -> b) -> a -> b
$ [V2 n]
offsets

-- | Generate the vertices of a regular polygon.  See 'PolyRegular'.
polyRegularTrail :: OrderedField n =>  Int -> n -> Located (Trail V2 n)
polyRegularTrail :: forall n. OrderedField n => Int -> n -> Located (Trail V2 n)
polyRegularTrail Int
n n
r = forall n.
OrderedField n =>
[Angle n] -> [n] -> Located (Trail V2 n)
polyPolarTrail
                         (forall a. Int -> a -> [a]
replicate (Int
n forall a. Num a => a -> a -> a
- Int
1) forall a b. (a -> b) -> a -> b
$ forall v. Floating v => Angle v
fullTurn forall (f :: * -> *) a.
(Functor f, Fractional a) =>
f a -> a -> f a
^/ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
                         (forall a. a -> [a]
repeat n
r)

-- | Generate a transformation to orient a trail.  @orient v t@
--   generates the smallest rotation such that one of the segments
--   adjacent to the vertex furthest in the direction of @v@ is
--   perpendicular to @v@.
orient :: OrderedField n => V2 n -> Located (Trail V2 n) -> Transformation V2 n
orient :: forall n.
OrderedField n =>
V2 n -> Located (Trail V2 n) -> Transformation V2 n
orient V2 n
v = forall n.
OrderedField n =>
V2 n -> [Point V2 n] -> Transformation V2 n
orientPoints V2 n
v forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Located (Trail v n) -> [Point v n]
trailVertices

orientPoints :: OrderedField n => V2 n -> [Point V2 n] -> Transformation V2 n
orientPoints :: forall n.
OrderedField n =>
V2 n -> [Point V2 n] -> Transformation V2 n
orientPoints V2 n
_ [] = forall a. Monoid a => a
mempty
orientPoints V2 n
_ [Point V2 n
_] = forall a. Monoid a => a
mempty
orientPoints V2 n
v [Point V2 n]
xs = forall n. Floating n => Angle n -> Transformation V2 n
rotation Angle n
a
  where
    (Point V2 n
n1,Point V2 n
x,Point V2 n
n2) = forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
maximumBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (forall {f :: * -> *} {a}.
(Metric f, Floating a) =>
f a -> Point f a -> a
distAlong V2 n
v forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a} {b} {c}. (a, b, c) -> b
sndOf3))
                  (forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 (forall a. [a] -> [a]
tail (forall a. [a] -> [a]
cycle [Point V2 n]
xs)) [Point V2 n]
xs (forall a. [a] -> a
last [Point V2 n]
xs forall a. a -> [a] -> [a]
: forall a. [a] -> [a]
init [Point V2 n]
xs))
    distAlong :: f a -> Point f a -> a
distAlong f a
w ((forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin) -> Diff (Point f) a
p) = forall a. Num a => a -> a
signum (f a
w forall (f :: * -> *) a. (Metric f, Num a) => f a -> f a -> a
`dot` Diff (Point f) a
p) forall a. Num a => a -> a -> a
* forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm (forall (v :: * -> *) a.
(Metric v, Fractional a) =>
v a -> v a -> v a
project f a
w Diff (Point f) a
p)
    sndOf3 :: (a, b, c) -> b
sndOf3 (a
_,b
b,c
_) = b
b
    -- a :: Angle (Scalar v)
    a :: Angle n
a = forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
minimumBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
abs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall n. Iso' (Angle n) n
rad)
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (V2 n -> Angle n
angleFromNormal forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. Point V2 n
x)) forall a b. (a -> b) -> a -> b
$ [Point V2 n
n1,Point V2 n
n2]
    v' :: V2 n
v' = forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm V2 n
v
    -- angleFromNormal :: v -> Angle (Scalar v)
    angleFromNormal :: V2 n -> Angle n
angleFromNormal V2 n
o
      | forall n. (Num n, Ord n) => V2 n -> V2 n -> Bool
leftTurn V2 n
o' V2 n
v' = Angle n
phi
      | Bool
otherwise      = forall (f :: * -> *) a. (Functor f, Num a) => f a -> f a
negated Angle n
phi
      where
        o' :: V2 n
o' = forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm V2 n
o
        theta :: n
theta = forall a. Floating a => a -> a
acos (V2 n
v' forall (f :: * -> *) a. (Metric f, Num a) => f a -> f a -> a
`dot` V2 n
o')
        -- phi :: Angle (Scalar v)
        phi :: Angle n
phi
          | n
theta forall a. Ord a => a -> a -> Bool
<= forall a. Floating a => a
tauforall a. Fractional a => a -> a -> a
/n
4 = forall a. Floating a => a
tauforall a. Fractional a => a -> a -> a
/n
4 forall a. Num a => a -> a -> a
- n
theta forall b a. b -> AReview a b -> a
@@ forall n. Iso' (Angle n) n
rad
          | Bool
otherwise      = n
theta forall a. Num a => a -> a -> a
- forall a. Floating a => a
tauforall a. Fractional a => a -> a -> a
/n
4 forall b a. b -> AReview a b -> a
@@ forall n. Iso' (Angle n) n
rad

------------------------------------------------------------
-- Function graphs
------------------------------------------------------------

-- $graphs
-- These functions are used to implement 'star', but are exported on
-- the offchance that someone else finds them useful.

-- | Pieces of a function graph can either be cycles or \"hairs\".
data GraphPart a = Cycle [a]
                 | Hair  [a]
  deriving (Int -> GraphPart a -> ShowS
forall a. Show a => Int -> GraphPart a -> ShowS
forall a. Show a => [GraphPart a] -> ShowS
forall a. Show a => GraphPart a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GraphPart a] -> ShowS
$cshowList :: forall a. Show a => [GraphPart a] -> ShowS
show :: GraphPart a -> String
$cshow :: forall a. Show a => GraphPart a -> String
showsPrec :: Int -> GraphPart a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> GraphPart a -> ShowS
Show, forall a b. a -> GraphPart b -> GraphPart a
forall a b. (a -> b) -> GraphPart a -> GraphPart b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> GraphPart b -> GraphPart a
$c<$ :: forall a b. a -> GraphPart b -> GraphPart a
fmap :: forall a b. (a -> b) -> GraphPart a -> GraphPart b
$cfmap :: forall a b. (a -> b) -> GraphPart a -> GraphPart b
Functor)

-- | @orbits f n@ computes the graph of @f@ on the integers mod @n@.
orbits :: (Int -> Int) -> Int -> [GraphPart Int]
orbits :: (Int -> Int) -> Int -> [GraphPart Int]
orbits Int -> Int
f Int
n = forall a. (forall s. ST s a) -> a
runST forall s. ST s [GraphPart Int]
genOrbits
  where
    f_n :: Int -> Int
f_n Int
i = Int -> Int
f Int
i forall a. Integral a => a -> a -> a
`mod` Int
n

    genOrbits :: ST s [GraphPart Int]
    genOrbits :: forall s. ST s [GraphPart Int]
genOrbits = forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (Int
0,Int
nforall a. Num a => a -> a -> a
-Int
1) Bool
False forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall s. STUArray s Int Bool -> ST s [GraphPart Int]
genOrbits'

    genOrbits' :: STUArray s Int Bool -> ST s [GraphPart Int]
    genOrbits' :: forall s. STUArray s Int Bool -> ST s [GraphPart Int]
genOrbits' STUArray s Int Bool
marks = forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Maybe a] -> [a]
catMaybes) (forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0 .. Int
nforall a. Num a => a -> a -> a
-Int
1] (forall s.
STUArray s Int Bool -> Int -> ST s (Maybe [GraphPart Int])
genPart STUArray s Int Bool
marks))

    genPart :: STUArray s Int Bool -> Int -> ST s (Maybe [GraphPart Int])
    genPart :: forall s.
STUArray s Int Bool -> Int -> ST s (Maybe [GraphPart Int])
genPart STUArray s Int Bool
marks Int
i = do
      [Int]
tr <- forall s. Int -> STUArray s Int Bool -> ST s [Int]
markRho Int
i STUArray s Int Bool
marks
      case [Int]
tr of
        [] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
        [Int]
_  -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [GraphPart Int]
splitParts forall a b. (a -> b) -> a -> b
$ [Int]
tr

    markRho :: Int -> STUArray s Int Bool -> ST s [Int]
    markRho :: forall s. Int -> STUArray s Int Bool -> ST s [Int]
markRho Int
i STUArray s Int Bool
marks = do
      Bool
isMarked <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Bool
marks Int
i
      if Bool
isMarked
        then forall (m :: * -> *) a. Monad m => a -> m a
return []
        else forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Bool
marks Int
i Bool
True forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
               forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int
iforall a. a -> [a] -> [a]
:) (forall s. Int -> STUArray s Int Bool -> ST s [Int]
markRho (Int -> Int
f_n Int
i) STUArray s Int Bool
marks)

    splitParts :: [Int] -> [GraphPart Int]
    splitParts :: [Int] -> [GraphPart Int]
splitParts [Int]
tr = [GraphPart Int]
hair forall a. [a] -> [a] -> [a]
++ [GraphPart Int]
cyc
      where hair :: [GraphPart Int]
hair | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
tl)   = [forall a. [a] -> GraphPart a
Hair forall a b. (a -> b) -> a -> b
$ [Int]
tl forall a. [a] -> [a] -> [a]
++ [Int -> Int
f_n (forall a. [a] -> a
last [Int]
tl)]]
                 | Bool
otherwise       = []
            cyc :: [GraphPart Int]
cyc  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
body) = [forall a. [a] -> GraphPart a
Cycle [Int]
body]
                 | Bool
otherwise       = []
            l :: Int
l            = forall a. [a] -> a
last [Int]
tr
            ([Int]
tl, [Int]
body) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Int -> Int
f_n Int
l) [Int]
tr

-- | Generate a function graph from the given function and labels.
mkGraph :: (Int -> Int) -> [a] -> [GraphPart a]
mkGraph :: forall a. (Int -> Int) -> [a] -> [GraphPart a]
mkGraph Int -> Int
f [a]
xs = (forall a b. (a -> b) -> [a] -> [b]
map forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) ([a]
xsforall a. [a] -> Int -> a
!!) forall a b. (a -> b) -> a -> b
$ (Int -> Int) -> Int -> [GraphPart Int]
orbits Int -> Int
f (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs)

------------------------------------------------------------
--  Star polygons
------------------------------------------------------------

-- | Options for creating \"star\" polygons, where the edges connect
--   possibly non-adjacent vertices.
data StarOpts = StarFun (Int -> Int)
                -- ^ Specify the order in which the vertices should be
                --   connected by a function that maps each vertex
                --   index to the index of the vertex that should come
                --   next.  Indexing of vertices begins at 0.

              | StarSkip Int
                -- ^ Specify a star polygon by a \"skip\".  A skip of
                --   1 indicates a normal polygon, where edges go
                --   between successive vertices.  A skip of 2 means
                --   that edges will connect every second vertex,
                --   skipping one in between.  Generally, a skip of
                --   /n/ means that edges will connect every /n/th
                --   vertex.

-- | Create a generalized /star/ /polygon/.  The 'StarOpts' are used
--   to determine in which order the given vertices should be
--   connected.  The intention is that the second argument of type
--   @[Point v]@ could be generated by a call to 'polygon', 'regPoly', or
--   the like, since a list of vertices is 'TrailLike'.  But of course
--   the list can be generated any way you like.  A @'Path' 'v'@ is
--   returned (instead of any 'TrailLike') because the resulting path
--   may have more than one component, for example if the vertices are
--   to be connected in several disjoint cycles.
star :: OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n
star :: forall n. OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n
star StarOpts
sOpts [Point V2 n]
vs = [GraphPart (Point V2 n)] -> Path V2 n
graphToPath forall a b. (a -> b) -> a -> b
$ forall a. (Int -> Int) -> [a] -> [GraphPart a]
mkGraph Int -> Int
f [Point V2 n]
vs
  where f :: Int -> Int
f = case StarOpts
sOpts of
              StarFun Int -> Int
g  -> Int -> Int
g
              StarSkip Int
k -> (forall a. Num a => a -> a -> a
+Int
k)
        graphToPath :: [GraphPart (Point V2 n)] -> Path V2 n
graphToPath = forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall {v :: * -> *} {n}.
(Metric v, Floating n, Ord n) =>
GraphPart (Point v n) -> Path v n
partToPath

        partToPath :: GraphPart (Point v n) -> Path v n
partToPath (Cycle [Point v n]
ps) = forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Located (Trail v n) -> Path v n
pathFromLocTrail
                              forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. SameSpace a b => (a -> b) -> Located a -> Located b
mapLoc forall (v :: * -> *) n. Trail v n -> Trail v n
closeTrail
                              forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TrailLike t => [Point (V t) (N t)] -> t
fromVertices
                              forall a b. (a -> b) -> a -> b
$ [Point v n]
ps

        partToPath (Hair [Point v n]
ps)  = forall t. TrailLike t => [Point (V t) (N t)] -> t
fromVertices [Point v n]
ps