{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Diagrams.Core.Style
(
AttributeClass
, Attribute(..)
, _Attribute
, _MAttribute
, _TAttribute
, unwrapAttribute
, unmeasureAttribute
, attributeType
, Style(..)
, attributeToStyle
, getAttr
, unmeasureAttrs
, atAttr
, atMAttr
, atTAttr
, applyAttr
, applyMAttr
, applyTAttr
, HasStyle(..)
) where
import Control.Applicative
import Control.Arrow ((***))
import Control.Lens hiding (transform)
import qualified Data.HashMap.Strict as HM
import qualified Data.Map as M
import Data.Monoid.Action as A
import Data.Semigroup
import qualified Data.Set as S
import Data.Typeable
import Diagrams.Core.Measure
import Diagrams.Core.Transform
import Diagrams.Core.V
import Linear.Vector
class (Typeable a, Semigroup a) => AttributeClass a
data Attribute (v :: * -> *) n :: * where
Attribute :: AttributeClass a => a -> Attribute v n
MAttribute :: AttributeClass a => Measured n a -> Attribute v n
TAttribute :: (AttributeClass a, Transformable a, V a ~ v, N a ~ n) => a -> Attribute v n
type instance V (Attribute v n) = v
type instance N (Attribute v n) = n
instance Typeable n => Semigroup (Attribute v n) where
(Attribute a1) <> (preview _Attribute -> Just a2) = Attribute (a1 <> a2)
(MAttribute a1) <> (preview _MAttribute -> Just a2) = MAttribute (a1 <> a2)
(TAttribute a1) <> (preview _TAttribute -> Just a2) = TAttribute (a1 <> a2)
_ <> a2 = a2
instance (Additive v, Traversable v, Floating n) => Transformable (Attribute v n) where
transform _ (Attribute a) = Attribute a
transform t (MAttribute a) = MAttribute $ scaleLocal (avgScale t) a
transform t (TAttribute a) = TAttribute $ transform t a
instance Show (Attribute v n) where
showsPrec d attr = showParen (d > 10) $ case attr of
Attribute a -> showString "Attribute " . showsPrec 11 (typeOf a)
MAttribute a -> showString "MAttribute " . showsPrec 11 (mType a)
TAttribute a -> showString "TAttribute " . showsPrec 11 (typeOf a)
unwrapAttribute :: AttributeClass a => Attribute v n -> Maybe a
unwrapAttribute (Attribute a) = cast a
unwrapAttribute (MAttribute _) = Nothing
unwrapAttribute (TAttribute a) = cast a
{-# INLINE unwrapAttribute #-}
_Attribute :: AttributeClass a => Prism' (Attribute v n) a
_Attribute = prism' Attribute $ \t -> case t of Attribute a -> cast a; _ -> Nothing
{-# INLINE _Attribute #-}
_MAttribute :: (AttributeClass a, Typeable n) => Prism' (Attribute v n) (Measured n a)
_MAttribute = prism' MAttribute $ \t -> case t of MAttribute a -> cast a; _ -> Nothing
{-# INLINE _MAttribute #-}
_TAttribute :: (V a ~ v, N a ~ n, AttributeClass a, Transformable a)
=> Prism' (Attribute v n) a
_TAttribute = prism' TAttribute $ \t -> case t of TAttribute a -> cast a; _ -> Nothing
{-# INLINE _TAttribute #-}
unmeasureAttribute :: (Num n)
=> n -> n -> Attribute v n -> Attribute v n
unmeasureAttribute g n (MAttribute m) = Attribute (fromMeasured g n m)
unmeasureAttribute _ _ a = a
attributeType :: Attribute v n -> TypeRep
attributeType (Attribute a) = typeOf a
attributeType (MAttribute a) = mType a
attributeType (TAttribute a) = typeOf a
mType :: forall n a. Typeable a => Measured n a -> TypeRep
mType _ = typeOf (undefined :: a)
newtype Style v n = Style (HM.HashMap TypeRep (Attribute v n))
type instance V (Style v n) = v
type instance N (Style v n) = n
instance Rewrapped (Style v n) (Style v' n')
instance Wrapped (Style v n) where
type Unwrapped (Style v n) = HM.HashMap TypeRep (Attribute v n)
_Wrapped' = iso (\(Style m) -> m) Style
{-# INLINE _Wrapped' #-}
instance Each (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') where
each = _Wrapped . each
{-# INLINE each #-}
type instance Index (Style v n) = TypeRep
type instance IxValue (Style v n) = Attribute v n
instance Ixed (Style v n) where
ix k = _Wrapped' . ix k
{-# INLINE ix #-}
instance At (Style v n) where
at k = _Wrapped' . at k
{-# INLINE at #-}
instance Typeable n => Semigroup (Style v n) where
Style s1 <> Style s2 = Style $ HM.unionWith (<>) s1 s2
instance Typeable n => Monoid (Style v n) where
mempty = Style HM.empty
mappend = (<>)
instance (Additive v, Traversable v, Floating n) => Transformable (Style v n) where
transform t = over each (transform t)
instance A.Action (Style v n) m
instance Show (Style v n) where
showsPrec d sty = showParen (d > 10) $
showString "Style " . showsPrec d (sty ^.. each)
attributeToStyle :: Attribute v n -> Style v n
attributeToStyle a = Style $ HM.singleton (attributeType a) a
getAttr :: forall a v n. AttributeClass a => Style v n -> Maybe a
getAttr (Style s) = HM.lookup ty s >>= unwrapAttribute
where ty = typeOf (undefined :: a)
unmeasureAttrs :: (Num n) => n -> n -> Style v n -> Style v n
unmeasureAttrs g n = over each (unmeasureAttribute g n)
mkAttrLens :: forall v n a. Typeable a
=> (a -> TypeRep)
-> Prism' (Attribute v n) a
-> Lens' (Style v n) (Maybe a)
mkAttrLens tyF p f sty =
f (sty ^? ix ty . p) <&> \mAtt -> sty & at ty .~ (review p <$> mAtt)
where ty = tyF (undefined :: a)
{-# INLINE mkAttrLens #-}
atAttr :: AttributeClass a
=> Lens' (Style v n) (Maybe a)
atAttr = mkAttrLens typeOf _Attribute
{-# INLINE atAttr #-}
atMAttr :: (AttributeClass a, Typeable n)
=> Lens' (Style v n) (Maybe (Measured n a))
atMAttr = mkAttrLens mType _MAttribute
{-# INLINE atMAttr #-}
atTAttr :: (V a ~ v, N a ~ n, AttributeClass a, Transformable a)
=> Lens' (Style v n) (Maybe a)
atTAttr = mkAttrLens typeOf _TAttribute
{-# INLINE atTAttr #-}
class HasStyle a where
applyStyle :: Style (V a) (N a) -> a -> a
instance Typeable n => HasStyle (Style v n) where
applyStyle = mappend
instance (HasStyle a, HasStyle b, V a ~ V b, N a ~ N b) => HasStyle (a,b) where
applyStyle s = applyStyle s *** applyStyle s
instance HasStyle a => HasStyle [a] where
applyStyle = fmap . applyStyle
instance HasStyle b => HasStyle (a -> b) where
applyStyle = fmap . applyStyle
instance HasStyle a => HasStyle (M.Map k a) where
applyStyle = fmap . applyStyle
instance (HasStyle a, Ord a) => HasStyle (S.Set a) where
applyStyle = S.map . applyStyle
instance HasStyle b => HasStyle (Measured n b) where
applyStyle = fmap . applyStyle
applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d
applyAttr = applyStyle . attributeToStyle . Attribute
applyMAttr :: (AttributeClass a, N d ~ n, HasStyle d) => Measured n a -> d -> d
applyMAttr = applyStyle . attributeToStyle . MAttribute
applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, N a ~ N d, HasStyle d) => a -> d -> d
applyTAttr = applyStyle . attributeToStyle . TAttribute