module Data.PlanarGraph.AdjRep where
import Control.Lens (Bifunctor (..))
import Data.Aeson
import Data.Bifunctor (second)
import GHC.Generics (Generic)
data Gr v f = Gr { Gr v f -> [v]
adjacencies :: [v]
, Gr v f -> [f]
faces :: [f]
} deriving ((forall x. Gr v f -> Rep (Gr v f) x)
-> (forall x. Rep (Gr v f) x -> Gr v f) -> Generic (Gr v f)
forall x. Rep (Gr v f) x -> Gr v f
forall x. Gr v f -> Rep (Gr v f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v f x. Rep (Gr v f) x -> Gr v f
forall v f x. Gr v f -> Rep (Gr v f) x
$cto :: forall v f x. Rep (Gr v f) x -> Gr v f
$cfrom :: forall v f x. Gr v f -> Rep (Gr v f) x
Generic)
instance Bifunctor Gr where
bimap :: (a -> b) -> (c -> d) -> Gr a c -> Gr b d
bimap a -> b
f c -> d
g (Gr [a]
vs [c]
fs) = [b] -> [d] -> Gr b d
forall v f. [v] -> [f] -> Gr v f
Gr ((a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f [a]
vs) ((c -> d) -> [c] -> [d]
forall a b. (a -> b) -> [a] -> [b]
map c -> d
g [c]
fs)
instance (ToJSON v, ToJSON f) => ToJSON (Gr v f) where
toEncoding :: Gr v f -> Encoding
toEncoding = Options -> Gr v f -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions
instance (FromJSON v, FromJSON f) => FromJSON (Gr v f)
data Vtx v e = Vtx { Vtx v e -> Int
id :: Int
, Vtx v e -> [(Int, e)]
adj :: [(Int,e)]
, Vtx v e -> v
vData :: v
} deriving ((forall x. Vtx v e -> Rep (Vtx v e) x)
-> (forall x. Rep (Vtx v e) x -> Vtx v e) -> Generic (Vtx v e)
forall x. Rep (Vtx v e) x -> Vtx v e
forall x. Vtx v e -> Rep (Vtx v e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v e x. Rep (Vtx v e) x -> Vtx v e
forall v e x. Vtx v e -> Rep (Vtx v e) x
$cto :: forall v e x. Rep (Vtx v e) x -> Vtx v e
$cfrom :: forall v e x. Vtx v e -> Rep (Vtx v e) x
Generic)
instance Bifunctor Vtx where
bimap :: (a -> b) -> (c -> d) -> Vtx a c -> Vtx b d
bimap a -> b
f c -> d
g (Vtx Int
i [(Int, c)]
as a
x) = Int -> [(Int, d)] -> b -> Vtx b d
forall v e. Int -> [(Int, e)] -> v -> Vtx v e
Vtx Int
i (((Int, c) -> (Int, d)) -> [(Int, c)] -> [(Int, d)]
forall a b. (a -> b) -> [a] -> [b]
map ((c -> d) -> (Int, c) -> (Int, d)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second c -> d
g) [(Int, c)]
as) (a -> b
f a
x)
instance (ToJSON v, ToJSON e) => ToJSON (Vtx v e) where
toEncoding :: Vtx v e -> Encoding
toEncoding = Options -> Vtx v e -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions
instance (FromJSON v, FromJSON e) => FromJSON (Vtx v e)
data Face f = Face { Face f -> (Int, Int)
incidentEdge :: (Int,Int)
, Face f -> f
fData :: f
} deriving ((forall x. Face f -> Rep (Face f) x)
-> (forall x. Rep (Face f) x -> Face f) -> Generic (Face f)
forall x. Rep (Face f) x -> Face f
forall x. Face f -> Rep (Face f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall f x. Rep (Face f) x -> Face f
forall f x. Face f -> Rep (Face f) x
$cto :: forall f x. Rep (Face f) x -> Face f
$cfrom :: forall f x. Face f -> Rep (Face f) x
Generic,a -> Face b -> Face a
(a -> b) -> Face a -> Face b
(forall a b. (a -> b) -> Face a -> Face b)
-> (forall a b. a -> Face b -> Face a) -> Functor Face
forall a b. a -> Face b -> Face a
forall a b. (a -> b) -> Face a -> Face b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Face b -> Face a
$c<$ :: forall a b. a -> Face b -> Face a
fmap :: (a -> b) -> Face a -> Face b
$cfmap :: forall a b. (a -> b) -> Face a -> Face b
Functor)
instance ToJSON f => ToJSON (Face f) where
toEncoding :: Face f -> Encoding
toEncoding = Options -> Face f -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions
instance FromJSON f => FromJSON (Face f)