{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Diagrams.Attributes.Compile (
SplitAttribute(..), splitAttr
) where
import Data.Typeable
import Control.Arrow (second)
import Control.Lens ((%~), (&), _Wrapping')
import Data.Kind (Type)
import qualified Data.HashMap.Strict as HM
import Data.Semigroup
import Data.Tree (Tree (..))
import Diagrams.Core
import Diagrams.Core.Style (Style (..), attributeToStyle)
import Diagrams.Core.Types (RNode (..), RTree)
class (AttributeClass (AttrType code), Typeable (PrimType code)) => SplitAttribute code where
type AttrType code :: Type
type PrimType code :: Type
primOK :: code -> PrimType code -> Bool
splitAttr :: forall code b v n a. SplitAttribute code => code -> RTree b v n a -> RTree b v n a
splitAttr :: forall code b (v :: * -> *) n a.
SplitAttribute code =>
code -> RTree b v n a -> RTree b v n a
splitAttr code
code = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (AttrType code) -> RTree b v n a -> (RTree b v n a, Bool)
splitAttr' forall a. Maybe a
Nothing
where
splitAttr' :: Maybe (AttrType code) -> RTree b v n a -> (RTree b v n a, Bool)
splitAttr' :: Maybe (AttrType code) -> RTree b v n a -> (RTree b v n a, Bool)
splitAttr' Maybe (AttrType code)
mattr (Node (RStyle Style v n
sty) [RTree b v n a]
cs) = (RTree b v n a
t', Bool
ok)
where
mattr' :: Maybe (AttrType code)
mattr' = Maybe (AttrType code)
mattr forall a. Semigroup a => a -> a -> a
<> forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr Style v n
sty
sty' :: Style v n
sty' = Style v n
sty forall a b. a -> (a -> b) -> b
& forall s. Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s)
_Wrapping' forall (v :: * -> *) n.
HashMap TypeRep (Attribute v n) -> Style v n
Style forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
HM.delete TypeRep
ty
ty :: TypeRep
ty = forall a. Typeable a => a -> TypeRep
typeOf (forall a. HasCallStack => a
undefined :: AttrType code)
([RTree b v n a]
cs', Bool
ok) = Maybe (AttrType code) -> [RTree b v n a] -> ([RTree b v n a], Bool)
splitAttr'Forest Maybe (AttrType code)
mattr' [RTree b v n a]
cs
t' :: RTree b v n a
t' | Bool
ok = Maybe (AttrType code)
-> Bool -> RNode b v n a -> [RTree b v n a] -> RTree b v n a
rebuildNode forall a. Maybe a
Nothing Bool
ok (forall b (v :: * -> *) n a. Style v n -> RNode b v n a
RStyle Style v n
sty) [RTree b v n a]
cs'
| Bool
otherwise = Maybe (AttrType code)
-> Bool -> RNode b v n a -> [RTree b v n a] -> RTree b v n a
rebuildNode Maybe (AttrType code)
mattr Bool
ok (forall b (v :: * -> *) n a. Style v n -> RNode b v n a
RStyle Style v n
sty') [RTree b v n a]
cs'
splitAttr' Maybe (AttrType code)
mattr (Node rp :: RNode b v n a
rp@(RPrim (Prim p
prm)) [RTree b v n a]
_) =
case forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast p
prm :: Maybe (PrimType code) of
Maybe (PrimType code)
Nothing -> (forall a. a -> [Tree a] -> Tree a
Node RNode b v n a
rp [], Bool
True)
Just PrimType code
p ->
if forall code. SplitAttribute code => code -> PrimType code -> Bool
primOK code
code PrimType code
p
then (Maybe (AttrType code)
-> Bool -> RNode b v n a -> [RTree b v n a] -> RTree b v n a
rebuildNode Maybe (AttrType code)
mattr Bool
True RNode b v n a
rp [], Bool
True)
else (forall a. a -> [Tree a] -> Tree a
Node RNode b v n a
rp [], Bool
False)
splitAttr' Maybe (AttrType code)
mattr (Node RNode b v n a
nd [RTree b v n a]
cs) = (RTree b v n a
t', Bool
ok)
where
([RTree b v n a]
cs', Bool
ok) = Maybe (AttrType code) -> [RTree b v n a] -> ([RTree b v n a], Bool)
splitAttr'Forest Maybe (AttrType code)
mattr [RTree b v n a]
cs
t' :: RTree b v n a
t' = Maybe (AttrType code)
-> Bool -> RNode b v n a -> [RTree b v n a] -> RTree b v n a
rebuildNode Maybe (AttrType code)
mattr Bool
ok RNode b v n a
nd [RTree b v n a]
cs'
splitAttr'Forest :: Maybe (AttrType code) -> [RTree b v n a] -> ([RTree b v n a], Bool)
splitAttr'Forest :: Maybe (AttrType code) -> [RTree b v n a] -> ([RTree b v n a], Bool)
splitAttr'Forest Maybe (AttrType code)
mattr [RTree b v n a]
cs = ([RTree b v n a]
cs', Bool
ok)
where
([RTree b v n a]
cs', Bool
ok) = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall (t :: * -> *). Foldable t => t Bool -> Bool
and forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [(a, b)] -> ([a], [b])
unzip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (Maybe (AttrType code) -> RTree b v n a -> (RTree b v n a, Bool)
splitAttr' Maybe (AttrType code)
mattr) forall a b. (a -> b) -> a -> b
$ [RTree b v n a]
cs
rebuildNode :: Maybe (AttrType code) -> Bool -> RNode b v n a -> [RTree b v n a] -> RTree b v n a
rebuildNode :: Maybe (AttrType code)
-> Bool -> RNode b v n a -> [RTree b v n a] -> RTree b v n a
rebuildNode Maybe (AttrType code)
mattr Bool
ok RNode b v n a
nd [RTree b v n a]
cs
| Bool
ok = Maybe (AttrType code) -> RTree b v n a -> RTree b v n a
applyMattr Maybe (AttrType code)
mattr (forall a. a -> [Tree a] -> Tree a
Node RNode b v n a
nd [RTree b v n a]
cs)
| Bool
otherwise = forall a. a -> [Tree a] -> Tree a
Node RNode b v n a
nd [RTree b v n a]
cs
applyMattr :: Maybe (AttrType code) -> RTree b v n a -> RTree b v n a
applyMattr :: Maybe (AttrType code) -> RTree b v n a -> RTree b v n a
applyMattr Maybe (AttrType code)
Nothing RTree b v n a
t = RTree b v n a
t
applyMattr (Just AttrType code
a) RTree b v n a
t = forall a. a -> [Tree a] -> Tree a
Node (forall b (v :: * -> *) n a. Style v n -> RNode b v n a
RStyle forall a b. (a -> b) -> a -> b
$ forall (v :: * -> *) n. Attribute v n -> Style v n
attributeToStyle (forall a (v :: * -> *) n. AttributeClass a => a -> Attribute v n
Attribute AttrType code
a)) [RTree b v n a
t]