{-# LANGUAGE UnicodeSyntax, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
module GraphRewriting.Layout.Wrapper
(Wrapper (..), wrapGraph, wrappee, updateWrappee,
module Data.View,
module GraphRewriting.Graph.Types,
module GraphRewriting.Layout.Position,
module GraphRewriting.Layout.PortSpec,
module GraphRewriting.Layout.Rotation,
module GraphRewriting.Layout.RotPortSpec,
module Data.Vector.V2)
where
import Data.View
import GraphRewriting.Graph
import GraphRewriting.Graph.Types
import GraphRewriting.Layout.Position
import GraphRewriting.Layout.PortSpec
import GraphRewriting.Layout.Rotation
import GraphRewriting.Layout.RotPortSpec
import Data.Vector.Class
import Data.Vector.V2
data Wrapper w = Wrapper {forall w. Wrapper w -> Rotation
wRot ∷ Rotation, forall w. Wrapper w -> Position
wPos ∷ Position, forall w. Wrapper w -> w
wrappee ∷ w}
instance View v n ⇒ View v (Wrapper n) where
inspect :: Wrapper n -> v
inspect = n -> v
forall v n. View v n => n -> v
inspect (n -> v) -> (Wrapper n -> n) -> Wrapper n -> v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Wrapper n -> n
forall w. Wrapper w -> w
wrappee
adjust :: (v -> v) -> Wrapper n -> Wrapper n
adjust v -> v
f Wrapper n
w = Wrapper n
w {wrappee = adjust f $ wrappee w}
instance PortSpec n ⇒ PortSpec (Wrapper n) where portSpec :: Wrapper n -> [(Vector2, Vector2)]
portSpec = n -> [(Vector2, Vector2)]
forall n. PortSpec n => n -> [(Vector2, Vector2)]
portSpec (n -> [(Vector2, Vector2)])
-> (Wrapper n -> n) -> Wrapper n -> [(Vector2, Vector2)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Wrapper n -> n
forall w. Wrapper w -> w
wrappee
instance {-# OVERLAPPING #-} View Rotation (Wrapper n) where
inspect :: Wrapper n -> Rotation
inspect = Wrapper n -> Rotation
forall w. Wrapper w -> Rotation
wRot
update :: Rotation -> Wrapper n -> Wrapper n
update Rotation
v Wrapper n
w = Wrapper n
w {wRot = v}
instance {-# OVERLAPPING #-} View Position (Wrapper n) where
inspect :: Wrapper n -> Position
inspect = Wrapper n -> Position
forall w. Wrapper w -> Position
wPos
update :: Position -> Wrapper n -> Wrapper n
update Position
v Wrapper n
w = Wrapper n
w {wPos = v}
updateWrappee :: w -> Wrapper w -> Wrapper w
updateWrappee w
v Wrapper w
n = Wrapper w
n {wrappee = v}
wrapGraph ∷ Graph n → Graph (Wrapper n)
wrapGraph :: forall n. Graph n -> Graph (Wrapper n)
wrapGraph = (Int -> n -> Wrapper n) -> Graph n -> Graph (Wrapper n)
forall n n'. (Int -> n -> n') -> Graph n -> Graph n'
unsafeMapNodesUnique Int -> n -> Wrapper n
forall {a} {w}. Integral a => a -> w -> Wrapper w
wrapNode where
wrapNode :: a -> w -> Wrapper w
wrapNode a
k w
n = Wrapper {wRot :: Rotation
wRot = Angle -> Rotation
Rotation Angle
0, wPos :: Position
wPos = Vector2 -> Position
Position (Vector2 -> Position) -> Vector2 -> Position
forall a b. (a -> b) -> a -> b
$ a -> Vector2
forall {a}. Integral a => a -> Vector2
genPos a
k, wrappee :: w
wrappee = w
n}
genPos :: a -> Vector2
genPos a
k = Angle -> Vector2 -> Vector2
rotate (a -> Angle
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
k) (Angle -> Vector2
forall v. BasicVector v => Angle -> v
vpromote Angle
f)
where f :: Angle
f = a -> Angle
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Angle) -> a -> Angle
forall a b. (a -> b) -> a -> b
$ a
k a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
3