{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Diagrams.ThreeD.Attributes where
import Control.Lens
import Data.Semigroup
import Data.Typeable
import Data.Colour
import Diagrams.Core
newtype SurfaceColor = SurfaceColor (Last (Colour Double))
deriving (Typeable, Semigroup, Show)
instance AttributeClass SurfaceColor
_SurfaceColor :: Iso' SurfaceColor (Colour Double)
_SurfaceColor = iso (\(SurfaceColor (Last c)) -> c) (SurfaceColor . Last)
sc :: HasStyle d => Colour Double -> d -> d
sc = applyAttr . review _SurfaceColor
_sc :: Lens' (Style v n) (Maybe (Colour Double))
_sc = atAttr . mapping _SurfaceColor
newtype Diffuse = Diffuse (Last Double)
deriving (Typeable, Semigroup, Show)
instance AttributeClass Diffuse
_Diffuse :: Iso' Diffuse Double
_Diffuse = iso (\(Diffuse (Last d)) -> d) (Diffuse . Last)
diffuse :: HasStyle d => Double -> d -> d
diffuse = applyAttr . review _Diffuse
_diffuse :: Lens' (Style v n) (Maybe Double)
_diffuse = atAttr . mapping _Diffuse
newtype Ambient = Ambient (Last Double)
deriving (Typeable, Semigroup, Show)
instance AttributeClass Ambient
_Ambient :: Iso' Ambient Double
_Ambient = iso (\(Ambient (Last d)) -> d) (Ambient . Last)
ambient :: HasStyle d => Double -> d -> d
ambient = applyAttr . review _Ambient
_ambient :: Lens' (Style v n) (Maybe Double)
_ambient = atAttr . mapping _Ambient
data Specular = Specular
{ _specularIntensity :: Double
, _specularSize :: Double
} deriving Show
makeLenses ''Specular
newtype Highlight = Highlight (Last Specular)
deriving (Typeable, Semigroup, Show)
instance AttributeClass Highlight
_Highlight :: Iso' Highlight Specular
_Highlight = iso (\(Highlight (Last s)) -> s) (Highlight . Last)
-- | Set the specular highlight.
highlight :: HasStyle d => Specular -> d -> d
highlight = applyAttr . review _Highlight
-- | Lens onto the possible specular highlight in a style
_highlight :: Lens' (Style v n) (Maybe Specular)
_highlight = atAttr . mapping _Highlight
-- | Traversal over the highlight intensity of a style. If the style has
-- no 'Specular', setting this will do nothing.
highlightIntensity :: Traversal' (Style v n) Double
highlightIntensity = _highlight . _Just . specularSize
-- | Traversal over the highlight size in a style. If the style has no
-- 'Specular', setting this will do nothing.
highlightSize :: Traversal' (Style v n) Double
highlightSize = _highlight . _Just . specularSize