{-# LANGUAGE CPP                    #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE OverloadedStrings      #-}
{-# LANGUAGE RankNTypes             #-}
{-# LANGUAGE TemplateHaskell        #-}
module Graphics.SvgTree.Types
    ( 
      Coord
    , Origin( .. )
    , Point
    , RPoint
    , PathCommand( .. )
    , Transformation( .. )
    , ElementRef( .. )
    , CoordinateUnits( .. )
      
    , toPoint
    , serializeNumber
    , serializeTransformation
    , serializeTransformations
      
    , Cap( .. )
    , LineJoin( .. )
    , Tree( .. )
    , Number( .. )
    , Spread( .. )
    , Texture( .. )
    , Element( .. )
    , FillRule( .. )
    , FontStyle( .. )
    , Dpi
    , WithDefaultSvg( .. )
      
    , Document( .. )
    , HasDocument( .. )
    , documentSize
      
    , DrawAttributes( .. )
    , HasDrawAttributes( .. )
      
    , FilterElement(..)
    , FilterAttributes(..)
    , HasFilterAttributes(..)
    , FilterSource(..)
    , ColorMatrixType(..)
    , HasColorMatrix(..)
    , ColorMatrix(..)
    , HasComposite(..)
    , Composite(..)
    , CompositeOperator(..)
    , EdgeMode(..)
    , HasGaussianBlur(..)
    , GaussianBlur(..)
    , HasTurbulence(..)
    , Turbulence(..)
    , TurbulenceType(..)
    , StitchTiles(..)
    , HasDisplacementMap(..)
    , DisplacementMap(..)
    , ChannelSelector(..)
      
      
    , Rectangle( .. )
    , HasRectangle( .. )
      
    , Line( .. )
    , HasLine( .. )
      
    , Polygon( .. )
    , HasPolygon( .. )
      
    , PolyLine( .. )
    , HasPolyLine( .. )
      
    , Path( .. )
    , HasPath( .. )
      
    , Circle( .. )
    , HasCircle( .. )
      
    , Ellipse( .. )
    , HasEllipse( .. )
      
    , GradientPathCommand( .. )
    , MeshGradientType( .. )
    , MeshGradient( .. )
    , HasMeshGradient( .. )
    , MeshGradientRow( .. )
    , HasMeshGradientRow( .. )
    , MeshGradientPatch( .. )
    , HasMeshGradientPatch( .. )
      
    , Image( .. )
    , HasImage( .. )
      
    , Use( .. )
    , HasUse( .. )
      
      
    , Group( .. )
    , HasGroup( .. )
      
    , Symbol( .. )
    , groupOfSymbol
      
    , Definitions( .. )
    , groupOfDefinitions
    
    , Filter( .. )
    , filterChildren
      
      
    , Text( .. )
    , HasText( .. )
    , TextAnchor( .. )
    , textAt
      
    , TextPath( .. )
    , HasTextPath( .. )
    , TextPathSpacing( .. )
    , TextPathMethod( .. )
      
    , TextSpanContent( .. )
    , TextSpan( .. )
    , HasTextSpan( .. )
    , TextInfo( .. )
    , HasTextInfo( .. )
    , TextAdjust( .. )
      
    , Marker( .. )
    , Overflow( .. )
    , MarkerOrientation( .. )
    , MarkerUnit( .. )
    , HasMarker( .. )
      
    , GradientStop( .. )
    , HasGradientStop( .. )
      
    , LinearGradient( .. )
    , HasLinearGradient( .. )
      
    , RadialGradient( .. )
    , HasRadialGradient( .. )
      
    , Pattern( .. )
    , HasPattern( .. )
      
    , Mask( .. )
    , HasMask( .. )
      
    , ClipPath( .. )
    , HasClipPath( .. )
      
    , PreserveAspectRatio( .. )
    , Alignment( .. )
    , MeetSlice( .. )
    , HasPreserveAspectRatio( .. )
      
    , isPathArc
    , isPathWithArc
    , nameOfTree
    , zipTree
    , mapTree
    , foldTree
    , toUserUnit
    , mapNumber
    ) where
#if !MIN_VERSION_base(4,8,0)
import           Data.Foldable             (Foldable)
import           Data.Monoid               (Monoid (..))
#endif
import           Codec.Picture             (PixelRGBA8 (..))
import           Control.Lens              (Lens, Lens', lens, view, (&), (.~),
                                            (^.))
import           Control.Lens.TH
import qualified Data.Foldable             as F
import           Data.Function             (on)
import           Data.List                 (inits)
import           Data.Monoid               (Last (..))
import           Data.Semigroup            (Semigroup (..))
import qualified Data.Text                 as T
import           Graphics.SvgTree.CssTypes
import           Graphics.SvgTree.Misc
import           Linear                    hiding (angle)
import           Text.Printf
type Coord = Double
type RPoint = V2 Coord
type Point = (Number, Number)
data Origin
  = OriginAbsolute 
  | OriginRelative 
  deriving (Eq, Show)
data MeshGradientType
  = GradientBilinear
  | GradientBicubic
  deriving (Eq, Show)
data PathCommand
      
    = MoveTo !Origin ![RPoint]
      
    | LineTo !Origin ![RPoint]
      
    | HorizontalTo  !Origin ![Coord]
      
    | VerticalTo    !Origin ![Coord]
    
    | CurveTo  !Origin ![(RPoint, RPoint, RPoint)]
    
    | SmoothCurveTo  !Origin ![(RPoint, RPoint)]
    
    | QuadraticBezier !Origin ![(RPoint, RPoint)]
    
    | SmoothQuadraticBezierCurveTo  !Origin ![RPoint]
      
    | EllipticalArc !Origin ![(Coord, Coord, Coord, Bool, Bool, RPoint)]
      
    | EndPath
    deriving (Eq, Show)
data GradientPathCommand
      
    = GLine !Origin !(Maybe RPoint)
      
    | GCurve !Origin !RPoint !RPoint !(Maybe RPoint)
      
    | GClose
    deriving (Eq, Show)
toPoint :: Number -> Number -> Point
toPoint = (,)
isPathArc :: PathCommand -> Bool
isPathArc (EllipticalArc _ _) = True
isPathArc _                   = False
isPathWithArc :: Foldable f => f PathCommand -> Bool
isPathWithArc = F.any isPathArc
data CoordinateUnits
    = CoordUserSpace   
    | CoordBoundingBox 
    deriving (Eq, Show)
data Alignment
  = AlignNone 
  | AlignxMinYMin 
  | AlignxMidYMin 
  | AlignxMaxYMin 
  | AlignxMinYMid 
  | AlignxMidYMid 
  | AlignxMaxYMid 
  | AlignxMinYMax 
  | AlignxMidYMax 
  | AlignxMaxYMax 
  deriving (Eq, Show)
data MeetSlice = Meet | Slice
    deriving (Eq, Show)
data PreserveAspectRatio = PreserveAspectRatio
  { _aspectRatioDefer     :: !Bool
  , _aspectRatioAlign     :: !Alignment
  , _aspectRatioMeetSlice :: !(Maybe MeetSlice)
  }
  deriving (Eq, Show)
instance WithDefaultSvg PreserveAspectRatio where
  defaultSvg = PreserveAspectRatio
    { _aspectRatioDefer     = False
    , _aspectRatioAlign     = AlignxMidYMid
    , _aspectRatioMeetSlice = Nothing
    }
data Cap
  = CapRound 
  | CapButt  
  | CapSquare 
  deriving (Eq, Show)
data LineJoin
    = JoinMiter 
    | JoinBevel 
    | JoinRound 
    deriving (Eq, Show)
data Texture
  = ColorRef   PixelRGBA8 
  | TextureRef String     
  | FillNone              
  deriving (Eq, Show)
data FillRule
    = FillEvenOdd 
    | FillNonZero 
    deriving (Eq, Show)
data Transformation
    = 
      TransformMatrix !Coord !Coord !Coord
                      !Coord !Coord !Coord
      
    | Translate !Double !Double
      
    | Scale !Double !(Maybe Double)
      
      
    | Rotate !Double !(Maybe (Double, Double))
      
    | SkewX !Double
      
    | SkewY !Double
      
    | TransformUnknown
    deriving (Eq, Show)
serializeTransformation :: Transformation -> String
serializeTransformation t = case t of
  TransformUnknown -> ""
  TransformMatrix a b c d e f ->
      printf "matrix(%s, %s, %s, %s, %s, %s)"
        (ppD a) (ppD b) (ppD c) (ppD d) (ppD e) (ppD f)
  Translate x y -> printf "translate(%s, %s)" (ppD x) (ppD y)
  Scale x Nothing -> printf "scale(%s)" (ppD x)
  Scale x (Just y) -> printf "scale(%s, %s)" (ppD x) (ppD y)
  Rotate angle Nothing -> printf "rotate(%s)" (ppD angle)
  Rotate angle (Just (x, y))-> printf "rotate(%s, %s, %s)"
    (ppD angle) (ppD x) (ppD y)
  SkewX x -> printf "skewX(%s)" (ppD x)
  SkewY y -> printf "skewY(%s)" (ppD y)
serializeTransformations :: [Transformation] -> String
serializeTransformations =
    unwords . fmap serializeTransformation
class WithDefaultSvg a where
    
    defaultSvg :: a
data FontStyle
  = FontStyleNormal
  | FontStyleItalic
  | FontStyleOblique
  deriving (Eq, Show)
data TextAnchor
    
    
    
    
    
    
    
  = TextAnchorStart
    
    
    
    
    
    
  | TextAnchorMiddle
    
    
    
    
    
  | TextAnchorEnd
  deriving (Eq, Show)
data ElementRef
  = RefNone  
  | Ref String 
  deriving (Eq, Show)
data FilterSource
  = SourceGraphic
  | SourceAlpha
  | BackgroundImage
  | BackgroundAlpha
  | FillPaint
  | StrokePaint
  | SourceRef String
  deriving (Eq, Show)
data FilterAttributes = FilterAttributes
  { _filterHeight :: !(Last Number)
  , _filterResult :: !(Maybe String)
  , _filterWidth  :: !(Last Number)
  , _filterX      :: !(Last Number)
  , _filterY      :: !(Last Number)
  } deriving (Eq, Show)
instance WithDefaultSvg FilterAttributes where
  defaultSvg = FilterAttributes
    { _filterHeight = Last Nothing
    , _filterResult = Nothing
    , _filterWidth  = Last Nothing
    , _filterX      = Last Nothing
    , _filterY      = Last Nothing }
data DrawAttributes = DrawAttributes
    { 
      
      _strokeWidth      :: !(Last Number)
      
    , _strokeColor      :: !(Last Texture)
      
      
    , _strokeOpacity    :: !(Maybe Float)
      
      
    , _strokeLineCap    :: !(Last Cap)
      
      
    , _strokeLineJoin   :: !(Last LineJoin)
      
      
    , _strokeMiterLimit :: !(Last Double)
      
      
    , _fillColor        :: !(Last Texture)
      
      
    , _fillOpacity      :: !(Maybe Float)
      
    , _groupOpacity     :: !(Maybe Float)
      
    , _transform        :: !(Maybe [Transformation])
      
    , _fillRule         :: !(Last FillRule)
      
    , _maskRef          :: !(Last ElementRef)
      
    , _clipPathRef      :: !(Last ElementRef)
      
    , _clipRule         :: !(Last FillRule)
      
      
    , _attrClass        :: ![T.Text]
      
      
    , _attrId           :: !(Maybe String)
      
      
    , _strokeOffset     :: !(Last Number)
      
      
    , _strokeDashArray  :: !(Last [Number])
      
      
    , _fontSize         :: !(Last Number)
      
      
    , _fontFamily       :: !(Last [String])
      
    , _fontStyle        :: !(Last FontStyle)
      
      
    , _textAnchor       :: !(Last TextAnchor)
      
      
    , _markerStart      :: !(Last ElementRef)
      
      
      
    , _markerMid        :: !(Last ElementRef)
      
      
    , _markerEnd        :: !(Last ElementRef)
    , _filterRef        :: !(Last ElementRef)
    , _preRendered      :: !(Maybe String)
    }
    deriving (Eq, Show)
makeClassy ''DrawAttributes
data PolyLine = PolyLine
  { 
    _polyLineDrawAttributes :: !DrawAttributes
    
    
  , _polyLinePoints         :: ![RPoint]
  }
  deriving (Eq, Show)
instance WithDefaultSvg PolyLine where
  defaultSvg = PolyLine
    { _polyLineDrawAttributes = mempty
    , _polyLinePoints = []
    }
class HasPolyLine a where
  polyLine :: Lens' a PolyLine
  polyLineDrawAttributes :: Lens' a DrawAttributes
  {-# INLINE polyLineDrawAttributes #-}
  polyLineDrawAttributes = polyLine . polyLineDrawAttributes
  polyLinePoints :: Lens' a [RPoint]
  {-# INLINE polyLinePoints #-}
  polyLinePoints = polyLine . polyLinePoints
instance HasPolyLine PolyLine where
  polyLine = id
  {-# INLINE polyLineDrawAttributes #-}
  polyLineDrawAttributes f p =
    fmap (\y -> p { _polyLineDrawAttributes = y }) (f $ _polyLineDrawAttributes p)
  {-# INLINE polyLinePoints #-}
  polyLinePoints f p =
    fmap (\y -> p { _polyLinePoints = y }) (f $ _polyLinePoints p)
instance HasDrawAttributes PolyLine where
    drawAttributes = polyLineDrawAttributes
data Polygon = Polygon
  { 
    _polygonDrawAttributes :: !DrawAttributes
    
    
  , _polygonPoints         :: ![RPoint]
  }
  deriving (Eq, Show)
class HasPolygon a where
  polygon :: Lens' a Polygon
  polygonDrawAttributes :: Lens' a DrawAttributes
  {-# INLINE polygonDrawAttributes #-}
  polygonPoints :: Lens' a [RPoint]
  {-# INLINE polygonPoints #-}
  polygonDrawAttributes = polygon . polygonDrawAttributes
  polygonPoints = polygon . polygonPoints
instance HasPolygon Polygon where
  polygon = id
  {-# INLINE polygonDrawAttributes #-}
  polygonDrawAttributes f p =
    fmap (\y -> p { _polygonDrawAttributes = y }) (f $ _polygonDrawAttributes p)
  {-# INLINE polygonPoints #-}
  polygonPoints f p =
    fmap (\y -> p { _polygonPoints = y }) (f $ _polygonPoints p)
instance HasDrawAttributes Polygon where
    drawAttributes = polygonDrawAttributes
instance WithDefaultSvg Polygon where
  defaultSvg = Polygon
    { _polygonDrawAttributes = mempty
    , _polygonPoints = []
    }
data Line = Line
  { 
    _lineDrawAttributes :: !DrawAttributes
    
    
  , _linePoint1         :: !Point
    
    
  , _linePoint2         :: !Point
  }
  deriving (Eq, Show)
class HasLine a where
  line :: Lens' a Line
  lineDrawAttributes :: Lens' a DrawAttributes
  lineDrawAttributes = line . lineDrawAttributes
  {-# INLINE lineDrawAttributes #-}
  linePoint1 :: Lens' a Point
  linePoint1 = line . linePoint1
  {-# INLINE linePoint1 #-}
  linePoint2 :: Lens' a Point
  linePoint2 = line . linePoint2
  {-# INLINE linePoint2 #-}
instance HasLine Line where
  line = id
  {-# INLINE lineDrawAttributes #-}
  lineDrawAttributes f l =
      fmap (\y -> l { _lineDrawAttributes = y }) (f (_lineDrawAttributes l))
  {-# INLINE linePoint1 #-}
  linePoint1 f l =
      fmap (\y -> l { _linePoint1 = y }) (f (_linePoint1 l))
  {-# INLINE linePoint2 #-}
  linePoint2 f l =
      fmap (\y -> l { _linePoint2 = y }) (f (_linePoint2 l))
instance HasDrawAttributes Line where
    drawAttributes = lineDrawAttributes
instance WithDefaultSvg Line where
  defaultSvg = Line
    { _lineDrawAttributes = mempty
    , _linePoint1 = zeroPoint
    , _linePoint2 = zeroPoint
    }
    where zeroPoint = (Num 0, Num 0)
data Rectangle = Rectangle
  { 
    _rectDrawAttributes  :: !DrawAttributes
    
    
  , _rectUpperLeftCorner :: !Point
    
    
  , _rectWidth           :: !(Maybe Number)
    
    
  , _rectHeight          :: !(Maybe Number)
    
    
    
  , _rectCornerRadius    :: !(Maybe Number, Maybe Number)
  }
  deriving (Eq, Show)
class HasRectangle a where
  rectangle :: Lens' a Rectangle
  rectCornerRadius :: Lens' a (Maybe Number, Maybe Number)
  {-# INLINE rectCornerRadius #-}
  rectCornerRadius = rectangle . rectCornerRadius
  rectDrawAttributes :: Lens' a DrawAttributes
  {-# INLINE rectDrawAttributes #-}
  rectDrawAttributes = rectangle . rectDrawAttributes
  rectHeight :: Lens' a (Maybe Number)
  {-# INLINE rectHeight #-}
  rectHeight = rectangle . rectHeight
  rectUpperLeftCorner :: Lens' a Point
  {-# INLINE rectUpperLeftCorner #-}
  rectUpperLeftCorner = rectangle . rectUpperLeftCorner
  rectWidth :: Lens' a (Maybe Number)
  {-# INLINE rectWidth #-}
  rectWidth = rectangle . rectWidth
instance HasRectangle Rectangle where
  rectangle = id
  {-# INLINE rectCornerRadius #-}
  rectCornerRadius f attr =
    fmap (\y -> attr { _rectCornerRadius = y }) (f $ _rectCornerRadius attr)
  {-# INLINE rectDrawAttributes #-}
  rectDrawAttributes f attr =
    fmap (\y -> attr { _rectDrawAttributes = y }) (f $ _rectDrawAttributes attr)
  {-# INLINE rectHeight #-}
  rectHeight f attr =
    fmap (\y -> attr { _rectHeight = y }) (f $ _rectHeight attr)
  {-# INLINE rectUpperLeftCorner #-}
  rectUpperLeftCorner f attr =
    fmap (\y -> attr { _rectUpperLeftCorner = y }) (f $ _rectUpperLeftCorner attr)
  {-# INLINE rectWidth #-}
  rectWidth f attr =
    fmap (\y -> attr { _rectWidth = y }) (f $ _rectWidth attr)
instance HasDrawAttributes Rectangle where
    drawAttributes = rectDrawAttributes
instance WithDefaultSvg Rectangle where
  defaultSvg = Rectangle
    { _rectDrawAttributes  = mempty
    , _rectUpperLeftCorner = (Num 0, Num 0)
    , _rectWidth           = Nothing
    , _rectHeight          = Nothing
    , _rectCornerRadius    = (Nothing, Nothing)
    }
data Path = Path
  { 
    _pathDrawAttributes :: !DrawAttributes
    
    
  , _pathDefinition     :: ![PathCommand]
  }
  deriving (Eq, Show)
class HasPath c_alhy where
  path :: Lens' c_alhy Path
  pathDefinition :: Lens' c_alhy [PathCommand]
  {-# INLINE pathDefinition #-}
  pathDefinition = path . pathDefinition
  pathDrawAttributes :: Lens' c_alhy DrawAttributes
  {-# INLINE pathDrawAttributes #-}
  pathDrawAttributes = path . pathDrawAttributes
instance HasPath Path where
  path = id
  {-# INLINE pathDefinition #-}
  pathDefinition f attr =
    fmap (\y -> attr { _pathDefinition = y }) (f $ _pathDefinition attr)
  {-# INLINE pathDrawAttributes #-}
  pathDrawAttributes f attr =
    fmap (\y -> attr { _pathDrawAttributes = y }) (f $ _pathDrawAttributes attr)
instance HasDrawAttributes Path where
  drawAttributes = pathDrawAttributes
instance WithDefaultSvg Path where
  defaultSvg = Path
    { _pathDrawAttributes = mempty
    , _pathDefinition = []
    }
data Group a = Group
  { 
    
    _groupDrawAttributes :: !DrawAttributes
    
    
  , _groupChildren       :: ![a]
    
  , _groupViewBox        :: !(Maybe (Double, Double, Double, Double))
    
  , _groupAspectRatio    :: !PreserveAspectRatio
  }
  deriving (Eq, Show)
class HasGroup g a | g -> a where
  group :: Lens' g (Group a)
  groupAspectRatio :: Lens' g PreserveAspectRatio
  {-# INLINE groupAspectRatio #-}
  groupAspectRatio = group . groupAspectRatio
  groupChildren :: Lens' g [a]
  {-# INLINE groupChildren #-}
  groupChildren = group . groupChildren
  groupDrawAttributes :: Lens' g DrawAttributes
  {-# INLINE groupDrawAttributes #-}
  groupDrawAttributes = group . groupDrawAttributes
  groupViewBox :: Lens' g (Maybe (Double, Double, Double, Double))
  {-# INLINE groupViewBox #-}
  groupViewBox = group . groupViewBox
instance HasGroup (Group a) a where
  group = id
  {-# INLINE groupAspectRatio #-}
  groupAspectRatio f attr =
    fmap (\y -> attr { _groupAspectRatio = y }) (f $ _groupAspectRatio attr)
  {-# INLINE groupChildren #-}
  groupChildren f attr =
    fmap (\y -> attr { _groupChildren = y }) (f $ _groupChildren attr)
  {-# INLINE groupDrawAttributes #-}
  groupDrawAttributes f attr =
    fmap (\y -> attr { _groupDrawAttributes = y }) (f $ _groupDrawAttributes attr)
  {-# INLINE groupViewBox #-}
  groupViewBox f attr =
    fmap (\y -> attr { _groupViewBox = y }) (f $ _groupViewBox attr)
instance HasDrawAttributes (Group a) where
  drawAttributes = groupDrawAttributes
instance WithDefaultSvg (Group a) where
  defaultSvg = Group
    { _groupDrawAttributes = mempty
    , _groupChildren  = []
    , _groupViewBox = Nothing
    , _groupAspectRatio = defaultSvg
    }
newtype Symbol a =
    Symbol { _groupOfSymbol :: Group a }
  deriving (Eq, Show)
instance HasGroup (Symbol a) a where
  group = groupOfSymbol
groupOfSymbol :: Lens (Symbol s) (Symbol t) (Group s) (Group t)
{-# INLINE groupOfSymbol #-}
groupOfSymbol f = fmap Symbol . f . _groupOfSymbol
instance HasDrawAttributes (Symbol a) where
  drawAttributes = groupOfSymbol . drawAttributes
instance WithDefaultSvg (Symbol a) where
  defaultSvg = Symbol defaultSvg
newtype Definitions a =
    Definitions { _groupOfDefinitions :: Group a }
  deriving (Eq, Show)
instance HasGroup (Definitions a) a where
  group = groupOfDefinitions
groupOfDefinitions :: Lens (Definitions s) (Definitions t) (Group s) (Group t)
{-# INLINE groupOfDefinitions #-}
groupOfDefinitions f = fmap Definitions . f . _groupOfDefinitions
instance HasDrawAttributes (Definitions a) where
  drawAttributes = groupOfDefinitions . drawAttributes
instance WithDefaultSvg (Definitions a) where
  defaultSvg = Definitions defaultSvg
data Filter = Filter
  { _filterDrawAttributes :: !DrawAttributes
  , _filterSelfAttributes :: !FilterAttributes
  , _filterChildren       :: ![FilterElement]
  }
  deriving (Eq, Show)
instance WithDefaultSvg Filter where
  defaultSvg = Filter
    { _filterDrawAttributes = defaultSvg
    , _filterSelfAttributes     = defaultSvg
    , _filterChildren       = []
    }
data Circle = Circle
  { 
    _circleDrawAttributes :: !DrawAttributes
    
    
  , _circleCenter         :: !Point
    
    
  , _circleRadius         :: !Number
  }
  deriving (Eq, Show)
class HasCircle a where
  circle :: Lens' a Circle
  circleCenter :: Lens' a Point
  {-# INLINE circleCenter #-}
  circleCenter = circle . circleCenter
  circleDrawAttributes :: Lens' a DrawAttributes
  {-# INLINE circleDrawAttributes #-}
  circleDrawAttributes = circle . circleDrawAttributes
  circleRadius :: Lens' a Number
  {-# INLINE circleRadius #-}
  circleRadius = circle . circleRadius
instance HasCircle Circle where
  circle = id
  {-# INLINE circleCenter #-}
  circleCenter f attr =
    fmap (\y -> attr { _circleCenter = y }) (f $ _circleCenter attr)
  {-# INLINE circleDrawAttributes #-}
  circleDrawAttributes f attr =
    fmap (\y -> attr { _circleDrawAttributes = y }) (f $ _circleDrawAttributes attr)
  {-# INLINE circleRadius #-}
  circleRadius f attr =
    fmap (\y -> attr { _circleRadius = y }) (f $ _circleRadius attr)
instance HasDrawAttributes Circle where
    drawAttributes = circleDrawAttributes
instance WithDefaultSvg Circle where
  defaultSvg = Circle
    { _circleDrawAttributes = mempty
    , _circleCenter = (Num 0, Num 0)
    , _circleRadius = Num 0
    }
data Ellipse = Ellipse
  {  
    _ellipseDrawAttributes :: !DrawAttributes
    
    
  , _ellipseCenter         :: !Point
    
    
  , _ellipseXRadius        :: !Number
    
    
  , _ellipseYRadius        :: !Number
  }
  deriving (Eq, Show)
class HasEllipse c_amWt where
  ellipse :: Lens' c_amWt Ellipse
  ellipseCenter :: Lens' c_amWt Point
  {-# INLINE ellipseCenter #-}
  ellipseDrawAttributes :: Lens' c_amWt DrawAttributes
  {-# INLINE ellipseDrawAttributes #-}
  ellipseXRadius :: Lens' c_amWt Number
  {-# INLINE ellipseXRadius #-}
  ellipseYRadius :: Lens' c_amWt Number
  {-# INLINE ellipseYRadius #-}
  ellipseCenter = ((.) ellipse) ellipseCenter
  ellipseDrawAttributes = ((.) ellipse) ellipseDrawAttributes
  ellipseXRadius = ((.) ellipse) ellipseXRadius
  ellipseYRadius = ((.) ellipse) ellipseYRadius
instance HasEllipse Ellipse where
  {-# INLINE ellipseCenter #-}
  {-# INLINE ellipseDrawAttributes #-}
  {-# INLINE ellipseXRadius #-}
  {-# INLINE ellipseYRadius #-}
  ellipse = id
  ellipseCenter f attr =
    fmap (\y -> attr { _ellipseCenter = y }) (f $ _ellipseCenter attr)
  ellipseDrawAttributes f attr =
    fmap (\y -> attr { _ellipseDrawAttributes = y }) (f $ _ellipseDrawAttributes attr)
  ellipseXRadius f attr =
    fmap (\y -> attr { _ellipseXRadius = y }) (f $ _ellipseXRadius attr)
  ellipseYRadius f attr =
    fmap (\y -> attr { _ellipseYRadius = y }) (f $ _ellipseYRadius attr)
instance HasDrawAttributes Ellipse where
  drawAttributes = ellipseDrawAttributes
instance WithDefaultSvg Ellipse where
  defaultSvg = Ellipse
    { _ellipseDrawAttributes = mempty
    , _ellipseCenter = (Num 0, Num 0)
    , _ellipseXRadius = Num 0
    , _ellipseYRadius = Num 0
    }
data GradientStop = GradientStop
    { 
      
      _gradientOffset  :: !Float
      
      
    , _gradientColor   :: !PixelRGBA8
      
    , _gradientPath    :: !(Maybe GradientPathCommand)
      
    , _gradientOpacity :: !(Maybe Float)
    }
    deriving (Eq, Show)
class HasGradientStop c_anhM where
  gradientStop :: Lens' c_anhM GradientStop
  gradientColor :: Lens' c_anhM PixelRGBA8
  {-# INLINE gradientColor #-}
  gradientOffset :: Lens' c_anhM Float
  {-# INLINE gradientOffset #-}
  gradientOpacity :: Lens' c_anhM (Maybe Float)
  {-# INLINE gradientOpacity #-}
  gradientPath :: Lens' c_anhM (Maybe GradientPathCommand)
  {-# INLINE gradientPath #-}
  gradientColor = ((.) gradientStop) gradientColor
  gradientOffset = ((.) gradientStop) gradientOffset
  gradientOpacity = ((.) gradientStop) gradientOpacity
  gradientPath = ((.) gradientStop) gradientPath
instance HasGradientStop GradientStop where
  {-# INLINE gradientColor #-}
  {-# INLINE gradientOffset #-}
  {-# INLINE gradientOpacity #-}
  {-# INLINE gradientPath #-}
  gradientStop = id
  gradientColor f attr =
    fmap (\y -> attr { _gradientColor = y }) (f $ _gradientColor attr)
  gradientOffset f attr =
    fmap (\y -> attr { _gradientOffset = y }) (f $ _gradientOffset attr)
  gradientOpacity f attr =
    fmap (\y -> attr { _gradientOpacity = y }) (f $ _gradientOpacity attr)
  gradientPath f attr =
    fmap (\y -> attr { _gradientPath = y }) (f $ _gradientPath attr)
instance WithDefaultSvg GradientStop where
  defaultSvg = GradientStop
    { _gradientOffset = 0.0
    , _gradientColor  = PixelRGBA8 0 0 0 255
    , _gradientPath   = Nothing
    , _gradientOpacity = Nothing
    }
data MeshGradientPatch = MeshGradientPatch
  { 
    _meshGradientPatchStops :: ![GradientStop]
  }
  deriving (Eq, Show)
class HasMeshGradientPatch c_annx where
  meshGradientPatch :: Lens' c_annx MeshGradientPatch
  meshGradientPatchStops :: Lens' c_annx [GradientStop]
  {-# INLINE meshGradientPatchStops #-}
  meshGradientPatchStops =  meshGradientPatch . meshGradientPatchStops
instance HasMeshGradientPatch MeshGradientPatch where
  {-# INLINE meshGradientPatchStops #-}
  meshGradientPatch = id
  meshGradientPatchStops f m =
    fmap (\y -> m { _meshGradientPatchStops = y }) . f $ _meshGradientPatchStops m
instance WithDefaultSvg MeshGradientPatch where
  defaultSvg = MeshGradientPatch []
data MeshGradientRow = MeshGradientRow
  { 
    _meshGradientRowPatches :: ![MeshGradientPatch]
  }
  deriving (Eq, Show)
class HasMeshGradientRow c_antr where
  meshGradientRow :: Lens' c_antr MeshGradientRow
  meshGradientRowPatches :: Lens' c_antr [MeshGradientPatch]
  {-# INLINE meshGradientRowPatches #-}
  meshGradientRowPatches = meshGradientRow . meshGradientRowPatches
instance HasMeshGradientRow MeshGradientRow where
  {-# INLINE meshGradientRowPatches #-}
  meshGradientRow = id
  meshGradientRowPatches f m =
      fmap (\y -> m { _meshGradientRowPatches = y }) . f $ _meshGradientRowPatches m
instance WithDefaultSvg MeshGradientRow where
  defaultSvg = MeshGradientRow []
data MeshGradient = MeshGradient
  { _meshGradientDrawAttributes :: !DrawAttributes
    
  , _meshGradientX              :: !Number
    
  , _meshGradientY              :: !Number
    
  , _meshGradientType           :: !MeshGradientType
    
  , _meshGradientUnits          :: !CoordinateUnits
    
  , _meshGradientTransform      :: ![Transformation]
    
  , _meshGradientRows           :: ![MeshGradientRow]
  }
  deriving (Eq, Show)
class HasMeshGradient c_anxG where
  meshGradient :: Lens' c_anxG MeshGradient
  meshGradientDrawAttributes :: Lens' c_anxG DrawAttributes
  {-# INLINE meshGradientDrawAttributes #-}
  meshGradientRows :: Lens' c_anxG [MeshGradientRow]
  {-# INLINE meshGradientRows #-}
  meshGradientTransform :: Lens' c_anxG [Transformation]
  {-# INLINE meshGradientTransform #-}
  meshGradientType :: Lens' c_anxG MeshGradientType
  {-# INLINE meshGradientType #-}
  meshGradientUnits :: Lens' c_anxG CoordinateUnits
  {-# INLINE meshGradientUnits #-}
  meshGradientX :: Lens' c_anxG Number
  {-# INLINE meshGradientX #-}
  meshGradientY :: Lens' c_anxG Number
  {-# INLINE meshGradientY #-}
  meshGradientDrawAttributes
    = ((.) meshGradient) meshGradientDrawAttributes
  meshGradientRows = ((.) meshGradient) meshGradientRows
  meshGradientTransform = ((.) meshGradient) meshGradientTransform
  meshGradientType = ((.) meshGradient) meshGradientType
  meshGradientUnits = ((.) meshGradient) meshGradientUnits
  meshGradientX = ((.) meshGradient) meshGradientX
  meshGradientY = ((.) meshGradient) meshGradientY
instance HasMeshGradient MeshGradient where
  {-# INLINE meshGradientDrawAttributes #-}
  {-# INLINE meshGradientRows #-}
  {-# INLINE meshGradientTransform #-}
  {-# INLINE meshGradientType #-}
  {-# INLINE meshGradientUnits #-}
  {-# INLINE meshGradientX #-}
  {-# INLINE meshGradientY #-}
  meshGradient = id
  meshGradientDrawAttributes f attr =
    fmap (\y -> attr { _meshGradientDrawAttributes = y }) (f $ _meshGradientDrawAttributes attr)
  meshGradientRows f attr =
    fmap (\y -> attr { _meshGradientRows = y }) (f $ _meshGradientRows attr)
  meshGradientTransform f attr =
    fmap (\y -> attr { _meshGradientTransform = y }) (f $ _meshGradientTransform attr)
  meshGradientType f attr =
    fmap (\y -> attr { _meshGradientType = y }) (f $ _meshGradientType attr)
  meshGradientUnits f attr =
    fmap (\y -> attr { _meshGradientUnits = y }) (f $ _meshGradientUnits attr)
  meshGradientX f attr =
    fmap (\y -> attr { _meshGradientX = y }) (f $ _meshGradientX attr)
  meshGradientY f attr =
    fmap (\y -> attr { _meshGradientY = y }) (f $ _meshGradientY attr)
instance HasDrawAttributes MeshGradient where
  drawAttributes = meshGradientDrawAttributes
instance WithDefaultSvg MeshGradient where
  defaultSvg = MeshGradient
    { _meshGradientDrawAttributes = mempty
    , _meshGradientX              = Percent 0
    , _meshGradientY              = Percent 0
    , _meshGradientType           = GradientBilinear
    , _meshGradientUnits          = CoordBoundingBox
    , _meshGradientTransform      = mempty
    , _meshGradientRows           = mempty
    }
data Image = Image
  { 
    _imageDrawAttributes  :: !DrawAttributes
    
    
  , _imageCornerUpperLeft :: !Point
    
  , _imageWidth           :: !Number
    
  , _imageHeight          :: !Number
    
  , _imageHref            :: !String
    
  , _imageAspectRatio     :: !PreserveAspectRatio
  }
  deriving (Eq, Show)
class HasImage c_anI7 where
  image :: Lens' c_anI7 Image
  imageAspectRatio :: Lens' c_anI7 PreserveAspectRatio
  {-# INLINE imageAspectRatio #-}
  imageCornerUpperLeft :: Lens' c_anI7 Point
  {-# INLINE imageCornerUpperLeft #-}
  imageDrawAttributes :: Lens' c_anI7 DrawAttributes
  {-# INLINE imageDrawAttributes #-}
  imageHeight :: Lens' c_anI7 Number
  {-# INLINE imageHeight #-}
  imageHref :: Lens' c_anI7 String
  {-# INLINE imageHref #-}
  imageWidth :: Lens' c_anI7 Number
  {-# INLINE imageWidth #-}
  imageAspectRatio = ((.) image) imageAspectRatio
  imageCornerUpperLeft = ((.) image) imageCornerUpperLeft
  imageDrawAttributes = ((.) image) imageDrawAttributes
  imageHeight = ((.) image) imageHeight
  imageHref = ((.) image) imageHref
  imageWidth = ((.) image) imageWidth
instance HasImage Image where
  {-# INLINE imageAspectRatio #-}
  {-# INLINE imageCornerUpperLeft #-}
  {-# INLINE imageDrawAttributes #-}
  {-# INLINE imageHeight #-}
  {-# INLINE imageHref #-}
  {-# INLINE imageWidth #-}
  image = id
  imageAspectRatio f attr =
    fmap (\y -> attr { _imageAspectRatio = y }) (f $ _imageAspectRatio attr)
  imageCornerUpperLeft f attr =
    fmap (\y -> attr { _imageCornerUpperLeft = y }) (f $ _imageCornerUpperLeft attr)
  imageDrawAttributes f attr =
    fmap (\y -> attr { _imageDrawAttributes = y }) (f $ _imageDrawAttributes attr)
  imageHeight f attr =
    fmap (\y -> attr { _imageHeight = y }) (f $ _imageHeight attr)
  imageHref f attr =
    fmap (\y -> attr { _imageHref = y }) (f $ _imageHref attr)
  imageWidth f attr =
    fmap (\y -> attr { _imageWidth = y }) (f $ _imageWidth attr)
instance HasDrawAttributes Image where
  drawAttributes = imageDrawAttributes
instance WithDefaultSvg Image where
  defaultSvg = Image
    { _imageDrawAttributes = mempty
    , _imageCornerUpperLeft = (Num 0, Num 0)
    , _imageWidth = Num 0
    , _imageHeight = Num 0
    , _imageHref = ""
    , _imageAspectRatio = defaultSvg
    }
data Use = Use
  { 
    
    _useBase           :: Point
    
    
  , _useName           :: String
    
    
    
  , _useWidth          :: Maybe Number
    
    
    
  , _useHeight         :: Maybe Number
    
  , _useDrawAttributes :: DrawAttributes
  }
  deriving (Eq, Show)
class HasUse c_anR3 where
  use :: Lens' c_anR3 Use
  useBase :: Lens' c_anR3 Point
  {-# INLINE useBase #-}
  useDrawAttributes :: Lens' c_anR3 DrawAttributes
  {-# INLINE useDrawAttributes #-}
  useHeight :: Lens' c_anR3 (Maybe Number)
  {-# INLINE useHeight #-}
  useName :: Lens' c_anR3 String
  {-# INLINE useName #-}
  useWidth :: Lens' c_anR3 (Maybe Number)
  {-# INLINE useWidth #-}
  useBase = ((.) use) useBase
  useDrawAttributes = ((.) use) useDrawAttributes
  useHeight = ((.) use) useHeight
  useName = ((.) use) useName
  useWidth = ((.) use) useWidth
instance HasUse Use where
  {-# INLINE useBase #-}
  {-# INLINE useDrawAttributes #-}
  {-# INLINE useHeight #-}
  {-# INLINE useName #-}
  {-# INLINE useWidth #-}
  use = id
  useBase f attr =
    fmap (\y -> attr { _useBase = y }) (f $ _useBase attr)
  useDrawAttributes f attr =
    fmap (\y -> attr { _useDrawAttributes = y }) (f $ _useDrawAttributes attr)
  useHeight f attr =
    fmap (\y -> attr { _useHeight = y }) (f $ _useHeight attr)
  useName f attr =
    fmap (\y -> attr { _useName = y }) (f $ _useName attr)
  useWidth f attr =
    fmap (\y -> attr { _useWidth = y }) (f $ _useWidth attr)
instance HasDrawAttributes Use where
  drawAttributes = useDrawAttributes
instance WithDefaultSvg Use where
  defaultSvg = Use
    { _useBase   = (Num 0, Num 0)
    , _useName   = ""
    , _useWidth  = Nothing
    , _useHeight = Nothing
    , _useDrawAttributes = mempty
    }
data TextInfo = TextInfo
  { _textInfoX      :: ![Number] 
  , _textInfoY      :: ![Number] 
  , _textInfoDX     :: ![Number] 
  , _textInfoDY     :: ![Number] 
  , _textInfoRotate :: ![Double] 
  , _textInfoLength :: !(Maybe Number) 
  }
  deriving (Eq, Show)
instance Semigroup TextInfo where
  (<>) (TextInfo x1 y1 dx1 dy1 r1 l1)
       (TextInfo x2 y2 dx2 dy2 r2 l2) =
    TextInfo (x1 <> x2)   (y1 <> y2)
                (dx1 <> dx2) (dy1 <> dy2)
                (r1 <> r2)
                (getLast $ Last l1 <> Last l2)
instance Monoid TextInfo where
  mempty = TextInfo [] [] [] [] [] Nothing
  mappend = (<>)
class HasTextInfo c_ao0m where
  textInfo :: Lens' c_ao0m TextInfo
  textInfoDX :: Lens' c_ao0m [Number]
  {-# INLINE textInfoDX #-}
  textInfoDY :: Lens' c_ao0m [Number]
  {-# INLINE textInfoDY #-}
  textInfoLength :: Lens' c_ao0m (Maybe Number)
  {-# INLINE textInfoLength #-}
  textInfoRotate :: Lens' c_ao0m [Double]
  {-# INLINE textInfoRotate #-}
  textInfoX :: Lens' c_ao0m [Number]
  {-# INLINE textInfoX #-}
  textInfoY :: Lens' c_ao0m [Number]
  {-# INLINE textInfoY #-}
  textInfoDX = ((.) textInfo) textInfoDX
  textInfoDY = ((.) textInfo) textInfoDY
  textInfoLength = ((.) textInfo) textInfoLength
  textInfoRotate = ((.) textInfo) textInfoRotate
  textInfoX = ((.) textInfo) textInfoX
  textInfoY = ((.) textInfo) textInfoY
instance HasTextInfo TextInfo where
  {-# INLINE textInfoDX #-}
  {-# INLINE textInfoDY #-}
  {-# INLINE textInfoLength #-}
  {-# INLINE textInfoRotate #-}
  {-# INLINE textInfoX #-}
  {-# INLINE textInfoY #-}
  textInfo = id
  textInfoDX f attr =
    fmap (\y -> attr { _textInfoDX = y }) (f $ _textInfoDX attr)
  textInfoDY f attr =
    fmap (\y -> attr { _textInfoDY = y }) (f $ _textInfoDY attr)
  textInfoLength f attr =
    fmap (\y -> attr { _textInfoLength = y }) (f $ _textInfoLength attr)
  textInfoRotate f attr =
    fmap (\y -> attr { _textInfoRotate = y }) (f $ _textInfoRotate attr)
  textInfoX f attr =
    fmap (\y -> attr { _textInfoX = y }) (f $ _textInfoX attr)
  textInfoY f attr =
    fmap (\y -> attr { _textInfoY = y }) (f $ _textInfoY attr)
instance WithDefaultSvg TextInfo where
  defaultSvg = mempty
data TextSpanContent
    = SpanText    !T.Text 
    | SpanTextRef !String 
    | SpanSub     !TextSpan 
    deriving (Eq, Show)
data TextSpan = TextSpan
  { 
    _spanInfo           :: !TextInfo
    
  , _spanDrawAttributes :: !DrawAttributes
    
  , _spanContent        :: ![TextSpanContent]
  }
  deriving (Eq, Show)
class HasTextSpan c_aobD where
  textSpan :: Lens' c_aobD TextSpan
  spanContent :: Lens' c_aobD [TextSpanContent]
  {-# INLINE spanContent #-}
  spanDrawAttributes :: Lens' c_aobD DrawAttributes
  {-# INLINE spanDrawAttributes #-}
  spanInfo :: Lens' c_aobD TextInfo
  {-# INLINE spanInfo #-}
  spanContent = ((.) textSpan) spanContent
  spanDrawAttributes = ((.) textSpan) spanDrawAttributes
  spanInfo = ((.) textSpan) spanInfo
instance HasTextSpan TextSpan where
  {-# INLINE spanContent #-}
  {-# INLINE spanDrawAttributes #-}
  {-# INLINE spanInfo #-}
  textSpan = id
  spanContent f attr =
    fmap (\y -> attr { _spanContent = y }) (f $ _spanContent attr)
  spanDrawAttributes f attr =
    fmap (\y -> attr { _spanDrawAttributes = y }) (f $ _spanDrawAttributes attr)
  spanInfo f attr =
    fmap (\y -> attr { _spanInfo = y }) (f $ _spanInfo attr)
instance WithDefaultSvg TextSpan where
  defaultSvg = TextSpan
    { _spanInfo = defaultSvg
    , _spanDrawAttributes = mempty
    , _spanContent        = mempty
    }
data TextPathMethod
  = TextPathAlign   
  | TextPathStretch 
  deriving (Eq, Show)
data TextPathSpacing
  = TextPathSpacingExact 
  | TextPathSpacingAuto  
  deriving (Eq, Show)
data TextPath = TextPath
  { 
    
    _textPathStartOffset :: !Number
    
  , _textPathName        :: !String
    
  , _textPathMethod      :: !TextPathMethod
    
  , _textPathSpacing     :: !TextPathSpacing
  }
  deriving (Eq, Show)
instance WithDefaultSvg TextPath where
  defaultSvg = TextPath
    { _textPathStartOffset = Num 0
    , _textPathName        = mempty
    , _textPathMethod      = TextPathAlign
    , _textPathSpacing     = TextPathSpacingExact
    }
data TextAdjust
  = TextAdjustSpacing 
  | TextAdjustSpacingAndGlyphs 
  deriving (Eq, Show)
data Text = Text
  { 
    _textAdjust :: !TextAdjust
    
  , _textRoot   :: !TextSpan
  }
  deriving (Eq, Show)
class HasText c_aorD where
  text :: Lens' c_aorD Text
  textAdjust :: Lens' c_aorD TextAdjust
  {-# INLINE textAdjust #-}
  textRoot :: Lens' c_aorD TextSpan
  {-# INLINE textRoot #-}
  textAdjust = ((.) text) textAdjust
  textRoot = ((.) text) textRoot
instance HasText Text where
  {-# INLINE textAdjust #-}
  {-# INLINE textRoot #-}
  text = id
  textAdjust f attr =
    fmap (\y -> attr { _textAdjust = y }) (f $ _textAdjust attr)
  textRoot f attr =
    fmap (\y -> attr { _textRoot = y }) (f $ _textRoot attr)
textAt :: Point -> T.Text -> Text
textAt (x, y) txt = Text TextAdjustSpacing tspan where
  tspan = defaultSvg
        { _spanContent = [SpanText txt]
        , _spanInfo = defaultSvg
                    { _textInfoX = [x]
                    , _textInfoY = [y]
                    }
        }
instance HasDrawAttributes Text where
  drawAttributes = textRoot . spanDrawAttributes
instance WithDefaultSvg Text where
  defaultSvg = Text
    { _textRoot = defaultSvg
    , _textAdjust = TextAdjustSpacing
    }
data Tree
    = None
    | UseTree { useInformation :: !Use
              , useSubTree     :: !(Maybe Tree) }
    | GroupTree     !(Group Tree)
    | SymbolTree    !(Symbol Tree)
    | DefinitionTree !(Definitions Tree)
    | FilterTree    !Filter
    | PathTree      !Path
    | CircleTree    !Circle
    | PolyLineTree  !PolyLine
    | PolygonTree   !Polygon
    | EllipseTree   !Ellipse
    | LineTree      !Line
    | RectangleTree !Rectangle
    | TextTree      !(Maybe TextPath) !Text
    | ImageTree     !Image
    | LinearGradientTree !LinearGradient
    | RadialGradientTree !RadialGradient
    | MeshGradientTree !MeshGradient
    | PatternTree   !Pattern
    | MarkerTree    !Marker
    | MaskTree      !Mask
    | ClipPathTree  !ClipPath
    | SvgTree       !Document
    deriving (Eq, Show)
data FilterElement
  = FEBlend
  | FEColorMatrix ColorMatrix
  | FEComponentTransfer 
  | FEComposite Composite
  | FEConvolveMatrix
  | FEDiffuseLighting
  | FEDisplacementMap DisplacementMap
  | FEDropShadow
  | FEFlood
  | FEFuncA 
  | FEFuncB
  | FEFuncG
  | FEFuncR
  | FEGaussianBlur GaussianBlur
  | FEImage
  | FEMerge
  | FEMergeNode
  | FEMorphology
  | FEOffset
  | FESpecularLighting
  | FETile
  | FETurbulence Turbulence
  | FENone
  deriving (Eq,Show)
instance WithDefaultSvg FilterElement where
  defaultSvg = FENone
data TransferFunctionType
  = TFIdentity
  | TFTable
  | TFDiscrete
  | TFLinear
  | TFGamma
  deriving (Eq, Show)
data TransferFunction = TransferFunction
  { _transferFunctionDrawAttributes   :: !DrawAttributes
  , _transferFunctionFilterAttr       :: !FilterAttributes
  , _transferFunctionType             :: TransferFunctionType
  , _transferFunctionTableValues      :: [Double]
  , _transferFunctionSlope            :: Double
  , _transferFunctionIntercept        :: Double
  , _transferFunctionAmplitude        :: Double
  , _transferFunctionExponent         :: Double
  , _transferFunctionOffset           :: Double
  } deriving (Eq, Show)
data ChannelSelector
  = ChannelR
  | ChannelG
  | ChannelB
  | ChannelA
  deriving (Eq, Show)
data DisplacementMap = DisplacementMap
  { _displacementMapDrawAttributes   :: !DrawAttributes
  , _displacementMapFilterAttr       :: !FilterAttributes
  , _displacementMapIn               :: !(Last FilterSource)
  , _displacementMapIn2              :: !(Last FilterSource)
  , _displacementMapScale            :: !(Last Double)
  , _displacementMapXChannelSelector :: ChannelSelector
  , _displacementMapYChannelSelector :: ChannelSelector
  } deriving (Eq, Show)
instance WithDefaultSvg DisplacementMap where
  defaultSvg = DisplacementMap
    { _displacementMapDrawAttributes   = defaultSvg
    , _displacementMapFilterAttr       = defaultSvg
    , _displacementMapIn               = Last Nothing
    , _displacementMapIn2              = Last Nothing
    , _displacementMapScale            = Last Nothing
    , _displacementMapXChannelSelector = ChannelA
    , _displacementMapYChannelSelector = ChannelA
    }
data ColorMatrixType
  = Matrix
  | Saturate
  | HueRotate
  | LuminanceToAlpha
  deriving (Eq,Show)
data ColorMatrix = ColorMatrix
  { _colorMatrixDrawAttributes :: !DrawAttributes
  , _colorMatrixFilterAttr     :: !FilterAttributes
  , _colorMatrixIn             :: !(Last FilterSource)
  , _colorMatrixType           :: !ColorMatrixType
  , _colorMatrixValues         :: !String
  } deriving (Eq,Show)
instance WithDefaultSvg ColorMatrix where
  defaultSvg = ColorMatrix
    { _colorMatrixDrawAttributes = defaultSvg
    , _colorMatrixFilterAttr     = defaultSvg
    , _colorMatrixIn             = Last Nothing
    , _colorMatrixType           = Matrix
    , _colorMatrixValues         = ""
    }
data CompositeOperator
  = CompositeOver 
  | CompositeIn
  | CompositeOut
  | CompositeAtop
  | CompositeXor
  | CompositeArithmetic
  deriving (Eq, Show)
data Composite = Composite
  { _compositeDrawAttributes :: DrawAttributes
  , _compositeFilterAttr     :: !FilterAttributes
  , _compositeIn             :: Last FilterSource
  , _compositeIn2            :: Last FilterSource
  , _compositeOperator       :: CompositeOperator
  , _compositeK1             :: Number
  , _compositeK2             :: Number
  , _compositeK3             :: Number
  , _compositeK4             :: Number
  } deriving (Eq, Show)
instance WithDefaultSvg Composite where
  defaultSvg = Composite
    { _compositeDrawAttributes = defaultSvg
    , _compositeFilterAttr     = defaultSvg
    , _compositeIn             = Last Nothing
    , _compositeIn2            = Last Nothing
    , _compositeOperator       = CompositeOver
    , _compositeK1             = Num 0
    , _compositeK2             = Num 0
    , _compositeK3             = Num 0
    , _compositeK4             = Num 0
    }
data Turbulence = Turbulence
  { _turbulenceDrawAttributes :: !DrawAttributes
  , _turbulenceFilterAttr     :: !FilterAttributes
  , _turbulenceBaseFrequency  :: !(Double, Last Double) 
  , _turbulenceNumOctaves     :: Int 
  , _turbulenceSeed           :: Double
  , _turbulenceStitchTiles    :: StitchTiles
  , _turbulenceType           :: TurbulenceType
  } deriving (Eq, Show)
data StitchTiles
  = NoStitch
  | Stitch
  deriving (Eq, Show)
data TurbulenceType
  = FractalNoiseType
  | TurbulenceType
  deriving (Eq, Show)
instance WithDefaultSvg Turbulence where
  defaultSvg = Turbulence
    { _turbulenceDrawAttributes = defaultSvg
    , _turbulenceFilterAttr     = defaultSvg
    , _turbulenceBaseFrequency  = (0, Last Nothing)
    , _turbulenceNumOctaves     = 1
    , _turbulenceSeed           = 0
    , _turbulenceStitchTiles    = NoStitch
    , _turbulenceType           = TurbulenceType
    }
data EdgeMode
  = EdgeDuplicate
  | EdgeWrap
  | EdgeNone
  deriving (Eq,Show)
data GaussianBlur = GaussianBlur
  { _gaussianBlurDrawAttributes :: DrawAttributes
  , _gaussianBlurFilterAttr     :: !FilterAttributes
  , _gaussianBlurIn             :: Last FilterSource
  , _gaussianBlurStdDeviationX  :: Number
  , _gaussianBlurStdDeviationY  :: Last Number
  , _gaussianBlurEdgeMode       :: EdgeMode
  } deriving (Eq,Show)
instance WithDefaultSvg GaussianBlur where
  defaultSvg = GaussianBlur
    { _gaussianBlurDrawAttributes = defaultSvg
    , _gaussianBlurFilterAttr     = defaultSvg
    , _gaussianBlurIn             = Last Nothing
    , _gaussianBlurStdDeviationX      = Num 0
    , _gaussianBlurStdDeviationY      = Last Nothing
    , _gaussianBlurEdgeMode           = EdgeDuplicate
    }
data MarkerOrientation
  = OrientationAuto        
  | OrientationAngle Coord 
  deriving (Eq, Show)
data MarkerUnit
  = MarkerUnitStrokeWidth    
  | MarkerUnitUserSpaceOnUse 
  deriving (Eq, Show)
data Overflow
  = OverflowVisible    
  | OverflowHidden     
  deriving (Eq, Show)
data Marker = Marker
  { 
    _markerDrawAttributes :: DrawAttributes
    
    
  , _markerRefPoint       :: !(Number, Number)
    
    
  , _markerWidth          :: !(Maybe Number)
    
    
  , _markerHeight         :: !(Maybe Number)
    
  , _markerOrient         :: !(Maybe MarkerOrientation)
    
  , _markerUnits          :: !(Maybe MarkerUnit)
    
  , _markerViewBox        :: !(Maybe (Double, Double, Double, Double))
    
  , _markerOverflow       :: !(Maybe Overflow)
    
  , _markerAspectRatio    :: !PreserveAspectRatio
    
  , _markerElements       :: [Tree]
  }
  deriving (Eq, Show)
class HasMarker c_aoKc where
  marker :: Lens' c_aoKc Marker
  markerAspectRatio :: Lens' c_aoKc PreserveAspectRatio
  {-# INLINE markerAspectRatio #-}
  markerDrawAttributes :: Lens' c_aoKc DrawAttributes
  {-# INLINE markerDrawAttributes #-}
  markerElements :: Lens' c_aoKc [Tree]
  {-# INLINE markerElements #-}
  markerHeight :: Lens' c_aoKc (Maybe Number)
  {-# INLINE markerHeight #-}
  markerOrient :: Lens' c_aoKc (Maybe MarkerOrientation)
  {-# INLINE markerOrient #-}
  markerOverflow :: Lens' c_aoKc (Maybe Overflow)
  {-# INLINE markerOverflow #-}
  markerRefPoint :: Lens' c_aoKc (Number, Number)
  {-# INLINE markerRefPoint #-}
  markerUnits :: Lens' c_aoKc (Maybe MarkerUnit)
  {-# INLINE markerUnits #-}
  markerViewBox ::
    Lens' c_aoKc (Maybe (Double, Double, Double, Double))
  {-# INLINE markerViewBox #-}
  markerWidth :: Lens' c_aoKc (Maybe Number)
  {-# INLINE markerWidth #-}
  markerAspectRatio = ((.) marker) markerAspectRatio
  markerDrawAttributes = ((.) marker) markerDrawAttributes
  markerElements = ((.) marker) markerElements
  markerHeight = ((.) marker) markerHeight
  markerOrient = ((.) marker) markerOrient
  markerOverflow = ((.) marker) markerOverflow
  markerRefPoint = ((.) marker) markerRefPoint
  markerUnits = ((.) marker) markerUnits
  markerViewBox = ((.) marker) markerViewBox
  markerWidth = ((.) marker) markerWidth
instance HasMarker Marker where
  {-# INLINE markerAspectRatio #-}
  {-# INLINE markerDrawAttributes #-}
  {-# INLINE markerElements #-}
  {-# INLINE markerHeight #-}
  {-# INLINE markerOrient #-}
  {-# INLINE markerOverflow #-}
  {-# INLINE markerRefPoint #-}
  {-# INLINE markerUnits #-}
  {-# INLINE markerViewBox #-}
  {-# INLINE markerWidth #-}
  marker = id
  markerAspectRatio f attr =
    fmap (\y -> attr { _markerAspectRatio = y }) (f $ _markerAspectRatio attr)
  markerDrawAttributes f attr =
    fmap (\y -> attr { _markerDrawAttributes = y }) (f $ _markerDrawAttributes attr)
  markerElements f attr =
    fmap (\y -> attr { _markerElements = y }) (f $ _markerElements attr)
  markerHeight f attr =
    fmap (\y -> attr { _markerHeight = y }) (f $ _markerHeight attr)
  markerOrient f attr =
    fmap (\y -> attr { _markerOrient = y }) (f $ _markerOrient attr)
  markerOverflow f attr =
    fmap (\y -> attr { _markerOverflow = y }) (f $ _markerOverflow attr)
  markerRefPoint f attr =
    fmap (\y -> attr { _markerRefPoint = y }) (f $ _markerRefPoint attr)
  markerUnits f attr =
    fmap (\y -> attr { _markerUnits = y }) (f $ _markerUnits attr)
  markerViewBox f attr =
    fmap (\y -> attr { _markerViewBox = y }) (f $ _markerViewBox attr)
  markerWidth f attr =
    fmap (\y -> attr { _markerWidth = y }) (f $ _markerWidth attr)
instance HasDrawAttributes Marker where
  drawAttributes = markerDrawAttributes
instance WithDefaultSvg Marker where
  defaultSvg = Marker
    { _markerDrawAttributes = mempty
    , _markerRefPoint = (Num 0, Num 0)
    , _markerWidth = Just (Num 3)
    , _markerHeight = Just (Num 3)
    , _markerOrient = Nothing 
    , _markerUnits = Nothing 
    , _markerViewBox = Nothing
    , _markerOverflow = Nothing
    , _markerElements = mempty
    , _markerAspectRatio = defaultSvg
    }
appNode :: [[a]] -> a -> [[a]]
appNode [] e           = [[e]]
appNode (curr:above) e = (e:curr) : above
zipTree :: ([[Tree]] -> Tree) -> Tree -> Tree
zipTree f = dig [] where
  dig prev e@None = f $ appNode prev e
  dig prev e@(UseTree _ Nothing) = f $ appNode prev e
  dig prev e@(UseTree nfo (Just u)) =
      f . appNode prev . UseTree nfo . Just $ dig ([] : appNode prev e) u
  dig prev e@(GroupTree g) =
      f . appNode prev . GroupTree $ zipGroup (appNode prev e) g
  dig prev e@(SymbolTree g) =
      f . appNode prev . SymbolTree . Symbol .
            zipGroup (appNode prev e) $ _groupOfSymbol g
  dig prev e@(DefinitionTree g) =
      f . appNode prev . DefinitionTree . Definitions .
            zipGroup (appNode prev e) $ _groupOfDefinitions g
  dig prev e@(FilterTree _) = f $ appNode prev e
  dig prev e@(PathTree _) = f $ appNode prev e
  dig prev e@(CircleTree _) = f $ appNode prev e
  dig prev e@(PolyLineTree _) = f $ appNode prev e
  dig prev e@(PolygonTree _) = f $ appNode prev e
  dig prev e@(EllipseTree _) = f $ appNode prev e
  dig prev e@(LineTree _) = f $ appNode prev e
  dig prev e@(RectangleTree _) = f $ appNode prev e
  dig prev e@(TextTree _ _) = f $ appNode prev e
  dig prev e@(ImageTree _) = f $ appNode prev e
  dig prev e@(MeshGradientTree _) = f $ appNode prev e
  dig prev e@(LinearGradientTree _) = f $ appNode prev e
  dig prev e@(RadialGradientTree _) = f $ appNode prev e
  dig prev e@(PatternTree _) = f $ appNode prev e
  dig prev e@(MarkerTree _) = f $ appNode prev e
  dig prev e@(MaskTree _) = f $ appNode prev e
  dig prev e@(ClipPathTree _) = f $ appNode prev e
  dig prev e@(SvgTree _) = f $ appNode prev e
  zipGroup prev g = g { _groupChildren = updatedChildren }
    where
      groupChild = _groupChildren g
      updatedChildren =
        [dig (c:prev) child
            | (child, c) <- zip groupChild $ inits groupChild]
foldTree :: (a -> Tree -> a) -> a -> Tree -> a
foldTree f = go where
  go acc e = case e of
    None                 -> f acc e
    UseTree _ _          -> f acc e
    PathTree _           -> f acc e
    CircleTree _         -> f acc e
    PolyLineTree _       -> f acc e
    PolygonTree _        -> f acc e
    EllipseTree _        -> f acc e
    LineTree _           -> f acc e
    RectangleTree _      -> f acc e
    TextTree    _ _      -> f acc e
    ImageTree _          -> f acc e
    LinearGradientTree _ -> f acc e
    RadialGradientTree _ -> f acc e
    MeshGradientTree _   -> f acc e
    PatternTree _        -> f acc e
    MarkerTree _         -> f acc e
    MaskTree _           -> f acc e
    ClipPathTree _       -> f acc e
    DefinitionTree g     -> foldGroup (_groupOfDefinitions g)
    FilterTree _         -> f acc e
    GroupTree g          -> foldGroup g
    SymbolTree s         -> foldGroup (_groupOfSymbol s)
    SvgTree{}            -> f acc e
    where
      foldGroup g =
        let subAcc = F.foldl' go acc $ _groupChildren g in
        f subAcc e
mapTree :: (Tree -> Tree) -> Tree -> Tree
mapTree f = go where
  go e@None = f e
  go e@(UseTree _ _) = f e
  go (GroupTree g) = f . GroupTree $ mapGroup g
  go (SymbolTree g) =
      f . SymbolTree . Symbol . mapGroup $ _groupOfSymbol g
  go (DefinitionTree defs) =
    f . DefinitionTree . Definitions . mapGroup $ _groupOfDefinitions defs
  go e@(FilterTree _) = f e
  go e@(PathTree _) = f e
  go e@(CircleTree _) = f e
  go e@(PolyLineTree _) = f e
  go e@(PolygonTree _) = f e
  go e@(EllipseTree _) = f e
  go e@(LineTree _) = f e
  go e@(RectangleTree _) = f e
  go e@(TextTree _ _) = f e
  go e@(ImageTree _) = f e
  go e@(LinearGradientTree _) = f e
  go e@(RadialGradientTree _) = f e
  go e@(MeshGradientTree _) = f e
  go e@(PatternTree _) = f e
  go e@(MarkerTree _) = f e
  go e@(MaskTree _) = f e
  go e@(ClipPathTree _) = f e
  go e@SvgTree{} = f e
  mapGroup g =
      g { _groupChildren = map go $ _groupChildren g }
nameOfTree :: Tree -> T.Text
nameOfTree v =
  case v of
   None                 -> ""
   UseTree _ _          -> "use"
   GroupTree _          -> "g"
   SymbolTree _         -> "symbol"
   DefinitionTree _     -> "defs"
   FilterTree _         -> "filter"
   PathTree _           -> "path"
   CircleTree _         -> "circle"
   PolyLineTree _       -> "polyline"
   PolygonTree _        -> "polygon"
   EllipseTree _        -> "ellipse"
   LineTree _           -> "line"
   RectangleTree _      -> "rectangle"
   TextTree    _ _      -> "text"
   ImageTree _          -> "image"
   LinearGradientTree _ -> "lineargradient"
   RadialGradientTree _ -> "radialgradient"
   MeshGradientTree _   -> "meshgradient"
   PatternTree _        -> "pattern"
   MarkerTree _         -> "marker"
   MaskTree _           -> "mask"
   ClipPathTree _       -> "clipPath"
   SvgTree{}            -> "svg"
drawAttrOfTree :: Tree -> DrawAttributes
drawAttrOfTree v = case v of
  None                 -> mempty
  UseTree e _          -> e ^. drawAttributes
  GroupTree e          -> e ^. drawAttributes
  SymbolTree e         -> e ^. drawAttributes
  DefinitionTree e     -> e ^. drawAttributes
  FilterTree e         -> e ^. drawAttributes
  PathTree e           -> e ^. drawAttributes
  CircleTree e         -> e ^. drawAttributes
  PolyLineTree e       -> e ^. drawAttributes
  PolygonTree e        -> e ^. drawAttributes
  EllipseTree e        -> e ^. drawAttributes
  LineTree e           -> e ^. drawAttributes
  RectangleTree e      -> e ^. drawAttributes
  TextTree _ e         -> e ^. drawAttributes
  ImageTree e          -> e ^. drawAttributes
  LinearGradientTree e -> e ^. drawAttributes
  RadialGradientTree e -> e ^. drawAttributes
  MeshGradientTree e   -> e ^. drawAttributes
  PatternTree e        -> e ^. drawAttributes
  MarkerTree e         -> e ^. drawAttributes
  MaskTree e           -> e ^. drawAttributes
  ClipPathTree e       -> e ^. drawAttributes
  SvgTree _            -> mempty 
setDrawAttrOfTree :: Tree -> DrawAttributes -> Tree
setDrawAttrOfTree v attr' = case v of
  None                 -> None
  UseTree e m          -> UseTree (e & drawAttributes .~ attr) m
  GroupTree e          -> GroupTree $ e & drawAttributes .~ attr
  SymbolTree e         -> SymbolTree $ e & drawAttributes .~ attr
  DefinitionTree e     -> DefinitionTree $ e & drawAttributes .~ attr
  FilterTree e         -> FilterTree $ e & drawAttributes .~ attr
  PathTree e           -> PathTree $ e & drawAttributes .~ attr
  CircleTree e         -> CircleTree $ e & drawAttributes .~ attr
  PolyLineTree e       -> PolyLineTree $ e & drawAttributes .~ attr
  PolygonTree e        -> PolygonTree $ e & drawAttributes .~ attr
  EllipseTree e        -> EllipseTree $ e & drawAttributes .~ attr
  LineTree e           -> LineTree $ e & drawAttributes .~ attr
  RectangleTree e      -> RectangleTree $ e & drawAttributes .~ attr
  TextTree a e         -> TextTree a $ e & drawAttributes .~ attr
  ImageTree e          -> ImageTree $ e & drawAttributes .~ attr
  LinearGradientTree e -> LinearGradientTree $ e & drawAttributes .~ attr
  RadialGradientTree e -> RadialGradientTree $ e & drawAttributes .~ attr
  MeshGradientTree e   -> MeshGradientTree $ e & drawAttributes .~ attr
  PatternTree e        -> PatternTree $ e & drawAttributes .~ attr
  MarkerTree e         -> MarkerTree $ e & drawAttributes .~ attr
  MaskTree e           -> MaskTree $ e & drawAttributes .~ attr
  ClipPathTree e       -> ClipPathTree $ e & drawAttributes .~ attr
  SvgTree e            -> SvgTree e
  where
    attr = attr'{_preRendered = Nothing}
instance HasDrawAttributes Tree where
  drawAttributes = lens drawAttrOfTree setDrawAttrOfTree
instance WithDefaultSvg Tree where
    defaultSvg = None
data Spread
    = SpreadRepeat  
    | SpreadPad     
    | SpreadReflect 
    deriving (Eq, Show)
data LinearGradient = LinearGradient
    { 
      _linearGradientDrawAttributes :: DrawAttributes
      
      
    , _linearGradientUnits          :: CoordinateUnits
      
      
    , _linearGradientStart          :: Point
      
      
    , _linearGradientStop           :: Point
      
      
      
    , _linearGradientSpread         :: Spread
      
      
      
    , _linearGradientTransform      :: [Transformation]
      
    , _linearGradientStops          :: [GradientStop]
    }
    deriving (Eq, Show)
class HasLinearGradient c_apmJ where
  linearGradient :: Lens' c_apmJ LinearGradient
  linearGradientDrawAttributes :: Lens' c_apmJ DrawAttributes
  linearGradientSpread :: Lens' c_apmJ Spread
  {-# INLINE linearGradientSpread #-}
  linearGradientStart :: Lens' c_apmJ Point
  {-# INLINE linearGradientStart #-}
  linearGradientStop :: Lens' c_apmJ Point
  {-# INLINE linearGradientStop #-}
  linearGradientStops :: Lens' c_apmJ [GradientStop]
  {-# INLINE linearGradientStops #-}
  linearGradientTransform :: Lens' c_apmJ [Transformation]
  {-# INLINE linearGradientTransform #-}
  linearGradientUnits :: Lens' c_apmJ CoordinateUnits
  {-# INLINE linearGradientUnits #-}
  linearGradientDrawAttributes = ((.) linearGradient) linearGradientDrawAttributes
  linearGradientSpread = ((.) linearGradient) linearGradientSpread
  linearGradientStart = ((.) linearGradient) linearGradientStart
  linearGradientStop = ((.) linearGradient) linearGradientStop
  linearGradientStops = ((.) linearGradient) linearGradientStops
  linearGradientTransform
    = ((.) linearGradient) linearGradientTransform
  linearGradientUnits = ((.) linearGradient) linearGradientUnits
instance HasLinearGradient LinearGradient where
  {-# INLINE linearGradientSpread #-}
  {-# INLINE linearGradientStart #-}
  {-# INLINE linearGradientStop #-}
  {-# INLINE linearGradientStops #-}
  {-# INLINE linearGradientTransform #-}
  {-# INLINE linearGradientUnits #-}
  linearGradient = id
  linearGradientSpread f attr =
    fmap (\y -> attr { _linearGradientSpread = y }) (f $ _linearGradientSpread attr)
  linearGradientStart f attr =
    fmap (\y -> attr { _linearGradientStart = y }) (f $ _linearGradientStart attr)
  linearGradientStop f attr =
    fmap (\y -> attr { _linearGradientStop = y }) (f $ _linearGradientStop attr)
  linearGradientStops f attr =
    fmap (\y -> attr { _linearGradientStops = y }) (f $ _linearGradientStops attr)
  linearGradientTransform f attr =
    fmap (\y -> attr { _linearGradientTransform = y }) (f $ _linearGradientTransform attr)
  linearGradientUnits f attr =
    fmap (\y -> attr { _linearGradientUnits = y }) (f $ _linearGradientUnits attr)
instance HasDrawAttributes LinearGradient where
  drawAttributes = linearGradientDrawAttributes
instance WithDefaultSvg LinearGradient where
  defaultSvg = LinearGradient
    { _linearGradientDrawAttributes = mempty
    , _linearGradientUnits     = CoordBoundingBox
    , _linearGradientStart     = (Percent 0, Percent 0)
    , _linearGradientStop      = (Percent 1, Percent 0)
    , _linearGradientSpread    = SpreadPad
    , _linearGradientTransform = []
    , _linearGradientStops     = []
    }
data RadialGradient = RadialGradient
  { 
    _radialGradientDrawAttributes :: DrawAttributes
    
    
  , _radialGradientUnits          :: CoordinateUnits
    
    
  , _radialGradientCenter         :: Point
    
    
  , _radialGradientRadius         :: Number
    
    
  , _radialGradientFocusX         :: Maybe Number
    
    
  , _radialGradientFocusY         :: Maybe Number
    
    
    
  , _radialGradientSpread         :: Spread
    
    
    
  , _radialGradientTransform      :: [Transformation]
    
  , _radialGradientStops          :: [GradientStop]
  }
  deriving (Eq, Show)
class HasRadialGradient c_apwt where
  radialGradient :: Lens' c_apwt RadialGradient
  radialGradientDrawAttributes :: Lens' c_apwt DrawAttributes
  radialGradientCenter :: Lens' c_apwt Point
  {-# INLINE radialGradientCenter #-}
  radialGradientFocusX :: Lens' c_apwt (Maybe Number)
  {-# INLINE radialGradientFocusX #-}
  radialGradientFocusY :: Lens' c_apwt (Maybe Number)
  {-# INLINE radialGradientFocusY #-}
  radialGradientRadius :: Lens' c_apwt Number
  {-# INLINE radialGradientRadius #-}
  radialGradientSpread :: Lens' c_apwt Spread
  {-# INLINE radialGradientSpread #-}
  radialGradientStops :: Lens' c_apwt [GradientStop]
  {-# INLINE radialGradientStops #-}
  radialGradientTransform :: Lens' c_apwt [Transformation]
  {-# INLINE radialGradientTransform #-}
  radialGradientUnits :: Lens' c_apwt CoordinateUnits
  {-# INLINE radialGradientUnits #-}
  radialGradientDrawAttributes = ((.) radialGradient) radialGradientDrawAttributes
  radialGradientCenter = ((.) radialGradient) radialGradientCenter
  radialGradientFocusX = ((.) radialGradient) radialGradientFocusX
  radialGradientFocusY = ((.) radialGradient) radialGradientFocusY
  radialGradientRadius = ((.) radialGradient) radialGradientRadius
  radialGradientSpread = ((.) radialGradient) radialGradientSpread
  radialGradientStops = ((.) radialGradient) radialGradientStops
  radialGradientTransform
    = ((.) radialGradient) radialGradientTransform
  radialGradientUnits = ((.) radialGradient) radialGradientUnits
instance HasRadialGradient RadialGradient where
  {-# INLINE radialGradientCenter #-}
  {-# INLINE radialGradientFocusX #-}
  {-# INLINE radialGradientFocusY #-}
  {-# INLINE radialGradientRadius #-}
  {-# INLINE radialGradientSpread #-}
  {-# INLINE radialGradientStops #-}
  {-# INLINE radialGradientTransform #-}
  {-# INLINE radialGradientUnits #-}
  radialGradient = id
  radialGradientCenter f attr =
    fmap (\y -> attr { _radialGradientCenter = y }) (f $ _radialGradientCenter attr)
  radialGradientFocusX f attr =
    fmap (\y -> attr { _radialGradientFocusX = y }) (f $ _radialGradientFocusX attr)
  radialGradientFocusY f attr =
    fmap (\y -> attr { _radialGradientFocusY = y }) (f $ _radialGradientFocusY attr)
  radialGradientRadius f attr =
    fmap (\y -> attr { _radialGradientRadius = y }) (f $ _radialGradientRadius attr)
  radialGradientSpread f attr =
    fmap (\y -> attr { _radialGradientSpread = y }) (f $ _radialGradientSpread attr)
  radialGradientStops f attr =
    fmap (\y -> attr { _radialGradientStops = y }) (f $ _radialGradientStops attr)
  radialGradientTransform f attr =
    fmap (\y -> attr { _radialGradientTransform = y }) (f $ _radialGradientTransform attr)
  radialGradientUnits f attr =
    fmap (\y -> attr { _radialGradientUnits = y }) (f $ _radialGradientUnits attr)
instance HasDrawAttributes RadialGradient where
  drawAttributes = radialGradientDrawAttributes
instance WithDefaultSvg RadialGradient where
  defaultSvg = RadialGradient
    { _radialGradientDrawAttributes = mempty
    , _radialGradientUnits   = CoordBoundingBox
    , _radialGradientCenter  = (Percent 0.5, Percent 0.5)
    , _radialGradientRadius  = Percent 0.5
    , _radialGradientFocusX  = Nothing
    , _radialGradientFocusY  = Nothing
    , _radialGradientSpread  = SpreadPad
    , _radialGradientTransform = []
    , _radialGradientStops   = []
    }
data Mask = Mask
  { 
    _maskDrawAttributes :: DrawAttributes
    
  , _maskContentUnits   :: CoordinateUnits
    
  , _maskUnits          :: CoordinateUnits
    
  , _maskPosition       :: Point
    
  , _maskWidth          :: Number
    
  , _maskHeight         :: Number
    
  , _maskContent        :: [Tree]
  }
  deriving (Eq, Show)
class HasMask c_apHI where
  mask :: Lens' c_apHI Mask
  maskContent :: Lens' c_apHI [Tree]
  {-# INLINE maskContent #-}
  maskContentUnits :: Lens' c_apHI CoordinateUnits
  {-# INLINE maskContentUnits #-}
  maskDrawAttributes :: Lens' c_apHI DrawAttributes
  {-# INLINE maskDrawAttributes #-}
  maskHeight :: Lens' c_apHI Number
  {-# INLINE maskHeight #-}
  maskPosition :: Lens' c_apHI Point
  {-# INLINE maskPosition #-}
  maskUnits :: Lens' c_apHI CoordinateUnits
  {-# INLINE maskUnits #-}
  maskWidth :: Lens' c_apHI Number
  {-# INLINE maskWidth #-}
  maskContent = ((.) mask) maskContent
  maskContentUnits = ((.) mask) maskContentUnits
  maskDrawAttributes = ((.) mask) maskDrawAttributes
  maskHeight = ((.) mask) maskHeight
  maskPosition = ((.) mask) maskPosition
  maskUnits = ((.) mask) maskUnits
  maskWidth = ((.) mask) maskWidth
instance HasMask Mask where
  {-# INLINE maskContent #-}
  {-# INLINE maskContentUnits #-}
  {-# INLINE maskDrawAttributes #-}
  {-# INLINE maskHeight #-}
  {-# INLINE maskPosition #-}
  {-# INLINE maskUnits #-}
  {-# INLINE maskWidth #-}
  mask = id
  maskContent f attr =
    fmap (\y -> attr { _maskContent = y }) (f $ _maskContent attr)
  maskContentUnits f attr =
    fmap (\y -> attr { _maskContentUnits = y }) (f $ _maskContentUnits attr)
  maskDrawAttributes f attr =
    fmap (\y -> attr { _maskDrawAttributes = y }) (f $ _maskDrawAttributes attr)
  maskHeight f attr =
    fmap (\y -> attr { _maskHeight = y }) (f $ _maskHeight attr)
  maskPosition f attr =
    fmap (\y -> attr { _maskPosition = y }) (f $ _maskPosition attr)
  maskUnits f attr =
    fmap (\y -> attr { _maskUnits = y }) (f $ _maskUnits attr)
  maskWidth f attr =
    fmap (\y -> attr { _maskWidth = y }) (f $ _maskWidth attr)
instance HasDrawAttributes Mask where
  drawAttributes = maskDrawAttributes
instance WithDefaultSvg Mask where
  defaultSvg = Mask
    { _maskDrawAttributes = mempty
    , _maskContentUnits = CoordUserSpace
    , _maskUnits        = CoordBoundingBox
    , _maskPosition     = (Percent (-0.1), Percent (-0.1))
    , _maskWidth        = Percent 1.2
    , _maskHeight       = Percent 1.2
    , _maskContent      = []
    }
data ClipPath = ClipPath
  { _clipPathDrawAttributes :: DrawAttributes
    
  , _clipPathUnits          :: CoordinateUnits
    
  , _clipPathContent        :: [Tree]
  }
  deriving (Eq, Show)
class HasClipPath c_apZq where
  clipPath :: Lens' c_apZq ClipPath
  clipPathContent :: Lens' c_apZq [Tree]
  {-# INLINE clipPathContent #-}
  clipPathDrawAttributes :: Lens' c_apZq DrawAttributes
  {-# INLINE clipPathDrawAttributes #-}
  clipPathUnits :: Lens' c_apZq CoordinateUnits
  {-# INLINE clipPathUnits #-}
  clipPathContent = ((.) clipPath) clipPathContent
  clipPathDrawAttributes = ((.) clipPath) clipPathDrawAttributes
  clipPathUnits = ((.) clipPath) clipPathUnits
instance HasClipPath ClipPath where
  {-# INLINE clipPathContent #-}
  {-# INLINE clipPathDrawAttributes #-}
  {-# INLINE clipPathUnits #-}
  clipPath = id
  clipPathContent f attr =
    fmap (\y -> attr { _clipPathContent = y }) (f $ _clipPathContent attr)
  clipPathDrawAttributes f attr =
    fmap (\y -> attr { _clipPathDrawAttributes = y }) (f $ _clipPathDrawAttributes attr)
  clipPathUnits f attr =
    fmap (\y -> attr { _clipPathUnits = y }) (f $ _clipPathUnits attr)
instance HasDrawAttributes ClipPath where
  drawAttributes = clipPathDrawAttributes
instance WithDefaultSvg ClipPath where
  defaultSvg = ClipPath
    { _clipPathDrawAttributes = mempty
    , _clipPathUnits = CoordUserSpace
    , _clipPathContent = mempty
    }
data Pattern = Pattern
    { 
      _patternDrawAttributes :: !DrawAttributes
      
    , _patternViewBox        :: !(Maybe (Double, Double, Double, Double))
      
      
    , _patternWidth          :: !Number
      
      
    , _patternHeight         :: !Number
      
      
    , _patternPos            :: !Point
      
      
    , _patternHref           :: !String
      
    , _patternElements       :: ![Tree]
      
      
      
    , _patternUnit           :: !CoordinateUnits
      
    , _patternAspectRatio    :: !PreserveAspectRatio
      
    , _patternTransform      :: !(Maybe [Transformation])
    }
    deriving (Eq, Show)
class HasPattern c_aq6G where
  pattern :: Lens' c_aq6G Pattern
  patternAspectRatio :: Lens' c_aq6G PreserveAspectRatio
  {-# INLINE patternAspectRatio #-}
  patternDrawAttributes :: Lens' c_aq6G DrawAttributes
  {-# INLINE patternDrawAttributes #-}
  patternElements :: Lens' c_aq6G [Tree]
  {-# INLINE patternElements #-}
  patternHeight :: Lens' c_aq6G Number
  {-# INLINE patternHeight #-}
  patternHref :: Lens' c_aq6G String
  {-# INLINE patternHref #-}
  patternPos :: Lens' c_aq6G Point
  {-# INLINE patternPos #-}
  patternTransform :: Lens' c_aq6G (Maybe [Transformation])
  {-# INLINE patternTransform #-}
  patternUnit :: Lens' c_aq6G CoordinateUnits
  {-# INLINE patternUnit #-}
  patternViewBox ::
    Lens' c_aq6G (Maybe (Double, Double, Double, Double))
  {-# INLINE patternViewBox #-}
  patternWidth :: Lens' c_aq6G Number
  {-# INLINE patternWidth #-}
  patternAspectRatio = ((.) pattern) patternAspectRatio
  patternDrawAttributes = ((.) pattern) patternDrawAttributes
  patternElements = ((.) pattern) patternElements
  patternHeight = ((.) pattern) patternHeight
  patternHref = ((.) pattern) patternHref
  patternPos = ((.) pattern) patternPos
  patternTransform = ((.) pattern) patternTransform
  patternUnit = ((.) pattern) patternUnit
  patternViewBox = ((.) pattern) patternViewBox
  patternWidth = ((.) pattern) patternWidth
instance HasPattern Pattern where
  {-# INLINE patternAspectRatio #-}
  {-# INLINE patternDrawAttributes #-}
  {-# INLINE patternElements #-}
  {-# INLINE patternHeight #-}
  {-# INLINE patternHref #-}
  {-# INLINE patternPos #-}
  {-# INLINE patternTransform #-}
  {-# INLINE patternUnit #-}
  {-# INLINE patternViewBox #-}
  {-# INLINE patternWidth #-}
  pattern = id
  patternAspectRatio f attr =
    fmap (\y -> attr { _patternAspectRatio = y }) (f $ _patternAspectRatio attr)
  patternDrawAttributes f attr =
    fmap (\y -> attr { _patternDrawAttributes = y }) (f $ _patternDrawAttributes attr)
  patternElements f attr =
    fmap (\y -> attr { _patternElements = y }) (f $ _patternElements attr)
  patternHeight f attr =
    fmap (\y -> attr { _patternHeight = y }) (f $ _patternHeight attr)
  patternHref f attr =
    fmap (\y -> attr { _patternHref = y }) (f $ _patternHref attr)
  patternPos f attr =
    fmap (\y -> attr { _patternPos = y }) (f $ _patternPos attr)
  patternTransform f attr =
    fmap (\y -> attr { _patternTransform = y }) (f $ _patternTransform attr)
  patternUnit f attr =
    fmap (\y -> attr { _patternUnit = y }) (f $ _patternUnit attr)
  patternViewBox f attr =
    fmap (\y -> attr { _patternViewBox = y }) (f $ _patternViewBox attr)
  patternWidth f attr =
    fmap (\y -> attr { _patternWidth = y }) (f $ _patternWidth attr)
instance HasDrawAttributes Pattern where
  drawAttributes = patternDrawAttributes
instance WithDefaultSvg Pattern where
  defaultSvg = Pattern
    { _patternViewBox  = Nothing
    , _patternWidth    = Num 0
    , _patternHeight   = Num 0
    , _patternPos      = (Num 0, Num 0)
    , _patternElements = []
    , _patternUnit = CoordBoundingBox
    , _patternDrawAttributes = mempty
    , _patternAspectRatio = defaultSvg
    , _patternHref = ""
    , _patternTransform = mempty
    }
data Element
    = ElementLinearGradient LinearGradient
    | ElementRadialGradient RadialGradient
    | ElementMeshGradient   MeshGradient
    | ElementGeometry Tree
    | ElementPattern  Pattern
    | ElementMarker Marker
    | ElementMask Mask
    | ElementClipPath ClipPath
    deriving (Eq, Show)
data Document = Document
    { _viewBox          :: Maybe (Double, Double, Double, Double)
    , _width            :: Maybe Number
    , _height           :: Maybe Number
    , _elements         :: [Tree]
    , _description      :: String
    , _documentLocation :: FilePath
    , _documentAspectRatio :: PreserveAspectRatio
    }
    deriving (Show, Eq)
makeClassy ''Document
documentSize :: Dpi -> Document -> (Int, Int)
documentSize _ Document { _viewBox = Just (x1, y1, x2, y2)
                        , _width = Just (Percent pw)
                        , _height = Just (Percent ph)
                        } =
    (floor $ dx * pw, floor $ dy * ph)
      where
        dx = abs $ x2 - x1
        dy = abs $ y2 - y1
documentSize _ Document { _width = Just (Num w)
                        , _height = Just (Num h) } = (floor w, floor h)
documentSize dpi doc@(Document { _width = Just w
                               , _height = Just h }) =
  documentSize dpi $ doc
    { _width = Just $ toUserUnit dpi w
    , _height = Just $ toUserUnit dpi h }
documentSize _ Document { _viewBox = Just (x1, y1, x2, y2) } =
    (floor . abs $ x2 - x1, floor . abs $ y2 - y1)
documentSize _ _ = (1, 1)
mayMerge :: Monoid a => Maybe a -> Maybe a -> Maybe a
mayMerge (Just a) (Just b) = Just $ mappend a b
mayMerge _ b@(Just _)      = b
mayMerge a Nothing         = a
instance Semigroup DrawAttributes where
  (<>) a b = DrawAttributes
        { _strokeWidth = (mappend `on` _strokeWidth) a b
        , _strokeColor =  (mappend `on` _strokeColor) a b
        , _strokeLineCap = (mappend `on` _strokeLineCap) a b
        , _strokeOpacity = (opacityMappend `on` _strokeOpacity) a b
        , _strokeLineJoin = (mappend `on` _strokeLineJoin) a b
        , _strokeMiterLimit = (mappend `on` _strokeMiterLimit) a b
        , _fillColor =  (mappend `on` _fillColor) a b
        , _fillOpacity = (opacityMappend `on` _fillOpacity) a b
        , _fontSize = (mappend `on` _fontSize) a b
        , _transform = (mayMerge `on` _transform) a b
        , _fillRule = (mappend `on` _fillRule) a b
        , _attrClass = _attrClass b
        , _attrId = _attrId b
        , _groupOpacity = _groupOpacity b
        , _strokeOffset = (mappend `on` _strokeOffset) a b
        , _strokeDashArray = (mappend `on` _strokeDashArray) a b
        , _fontFamily = (mappend `on` _fontFamily) a b
        , _fontStyle = (mappend `on` _fontStyle) a b
        , _textAnchor = (mappend `on` _textAnchor) a b
        , _maskRef = (mappend `on` _maskRef) a b
        , _clipPathRef = (mappend `on` _clipPathRef) a b
        , _clipRule = (mappend `on` _clipRule) a b
        , _markerStart = (mappend `on` _markerStart) a b
        , _markerMid = (mappend `on` _markerMid) a b
        , _markerEnd = (mappend `on` _markerEnd) a b
        , _filterRef = (mappend `on` _filterRef) a b
        , _preRendered = Nothing
        }
      where
        opacityMappend Nothing Nothing    = Nothing
        opacityMappend (Just v) Nothing   = Just v
        opacityMappend Nothing (Just v)   = Just v
        opacityMappend (Just v) (Just v2) = Just $ v * v2
instance Monoid DrawAttributes where
    mappend = (<>)
    mempty = DrawAttributes
        { _strokeWidth      = Last Nothing
        , _strokeColor      = Last Nothing
        , _strokeOpacity    = Nothing
        , _strokeLineCap    = Last Nothing
        , _strokeLineJoin   = Last Nothing
        , _strokeMiterLimit = Last Nothing
        , _fillColor        = Last Nothing
        , _groupOpacity     = Nothing
        , _fillOpacity      = Nothing
        , _fontSize         = Last Nothing
        , _fontFamily       = Last Nothing
        , _fontStyle        = Last Nothing
        , _transform        = Nothing
        , _fillRule         = Last Nothing
        , _attrClass        = mempty
        , _attrId           = Nothing
        , _strokeOffset     = Last Nothing
        , _strokeDashArray  = Last Nothing
        , _textAnchor       = Last Nothing
        , _maskRef          = Last Nothing
        , _clipPathRef      = Last Nothing
        , _clipRule         = Last Nothing
        , _markerStart      = Last Nothing
        , _markerMid        = Last Nothing
        , _markerEnd        = Last Nothing
        , _filterRef        = Last Nothing
        , _preRendered      = Nothing
        }
instance WithDefaultSvg DrawAttributes where
  defaultSvg = mempty
instance CssMatcheable Tree where
  cssAttribOf _ _ = Nothing
  cssClassOf = view (drawAttributes . attrClass)
  cssIdOf = fmap T.pack . view (drawAttributes . attrId)
  cssNameOf = nameOfTree
class HasPreserveAspectRatio a where
  preserveAspectRatio :: Lens' a PreserveAspectRatio
  aspectRatioAlign :: Lens' a Alignment
  {-# INLINE aspectRatioAlign #-}
  aspectRatioAlign = preserveAspectRatio . aspectRatioAlign
  aspectRatioDefer :: Lens' a Bool
  {-# INLINE aspectRatioDefer #-}
  aspectRatioDefer = preserveAspectRatio . aspectRatioDefer
  aspectRatioMeetSlice :: Lens' a (Maybe MeetSlice)
  {-# INLINE aspectRatioMeetSlice #-}
  aspectRatioMeetSlice = preserveAspectRatio . aspectRatioMeetSlice
instance HasPreserveAspectRatio PreserveAspectRatio where
  preserveAspectRatio = id
  {-# INLINE aspectRatioAlign #-}
  aspectRatioAlign f attr =
    fmap (\y -> attr { _aspectRatioAlign = y }) (f $ _aspectRatioAlign attr)
  {-# INLINE aspectRatioDefer #-}
  aspectRatioDefer f attr =
    fmap (\y -> attr { _aspectRatioDefer = y }) (f $ _aspectRatioDefer attr)
  {-# INLINE aspectRatioMeetSlice #-}
  aspectRatioMeetSlice f attr =
    fmap (\y -> attr { _aspectRatioMeetSlice = y }) (f $ _aspectRatioMeetSlice attr)
class HasFilterAttributes c_asYk where
  filterAttributes :: Lens' c_asYk FilterAttributes
  filterHeight :: Lens' c_asYk (Last Number)
  {-# INLINE filterHeight #-}
  filterResult :: Lens' c_asYk (Maybe String)
  {-# INLINE filterResult #-}
  filterWidth :: Lens' c_asYk (Last Number)
  {-# INLINE filterWidth #-}
  filterX :: Lens' c_asYk (Last Number)
  {-# INLINE filterX #-}
  filterY :: Lens' c_asYk (Last Number)
  {-# INLINE filterY #-}
  filterHeight = ((.) filterAttributes) filterHeight
  filterResult = ((.) filterAttributes) filterResult
  filterWidth = ((.) filterAttributes) filterWidth
  filterX = ((.) filterAttributes) filterX
  filterY = ((.) filterAttributes) filterY
instance HasFilterAttributes FilterAttributes where
  {-# INLINE filterHeight #-}
  {-# INLINE filterResult #-}
  {-# INLINE filterWidth #-}
  {-# INLINE filterX #-}
  {-# INLINE filterY #-}
  filterAttributes = id
  filterHeight
    f_asYl
    (FilterAttributes x1_asYm x2_asYn x3_asYo x4_asYp x5_asYq)
    = (fmap
         (\ y1_asYr
            -> ((((FilterAttributes y1_asYr) x2_asYn) x3_asYo) x4_asYp)
                 x5_asYq))
        (f_asYl x1_asYm)
  filterResult
    f_asYs
    (FilterAttributes x1_asYt x2_asYu x3_asYv x4_asYw x5_asYx)
    = (fmap
         (\ y1_asYy
            -> ((((FilterAttributes x1_asYt) y1_asYy) x3_asYv) x4_asYw)
                 x5_asYx))
        (f_asYs x2_asYu)
  filterWidth
    f_asYz
    (FilterAttributes x1_asYA x2_asYB x3_asYC x4_asYD x5_asYE)
    = (fmap
         (\ y1_asYF
            -> ((((FilterAttributes x1_asYA) x2_asYB) y1_asYF) x4_asYD)
                 x5_asYE))
        (f_asYz x3_asYC)
  filterX
    f_asYG
    (FilterAttributes x1_asYH x2_asYI x3_asYJ x4_asYK x5_asYL)
    = (fmap
         (\ y1_asYM
            -> ((((FilterAttributes x1_asYH) x2_asYI) x3_asYJ) y1_asYM)
                 x5_asYL))
        (f_asYG x4_asYK)
  filterY
    f_asYN
    (FilterAttributes x1_asYO x2_asYP x3_asYQ x4_asYR x5_asYS)
    = (fmap
         (\ y1_asYT
            -> ((((FilterAttributes x1_asYO) x2_asYP) x3_asYQ) x4_asYR)
                 y1_asYT))
        (f_asYN x5_asYS)
makeClassy ''TextPath
makeLenses ''Filter
instance HasDrawAttributes Filter where
  drawAttributes = filterDrawAttributes
instance HasFilterAttributes Filter where
  filterAttributes = filterSelfAttributes
makeClassy ''Composite
makeClassy ''ColorMatrix
makeClassy ''GaussianBlur
makeClassy ''Turbulence
makeClassy ''DisplacementMap
instance HasDrawAttributes Composite where
    drawAttributes = compositeDrawAttributes
instance HasDrawAttributes ColorMatrix where
    drawAttributes = colorMatrixDrawAttributes
instance HasDrawAttributes GaussianBlur where
    drawAttributes = gaussianBlurDrawAttributes
instance HasDrawAttributes Turbulence where
    drawAttributes = turbulenceDrawAttributes
instance HasDrawAttributes DisplacementMap where
    drawAttributes = displacementMapDrawAttributes
instance HasFilterAttributes Composite where
  filterAttributes = compositeFilterAttr
instance HasFilterAttributes ColorMatrix where
  filterAttributes = colorMatrixFilterAttr
instance HasFilterAttributes GaussianBlur where
  filterAttributes = gaussianBlurFilterAttr
instance HasFilterAttributes Turbulence where
  filterAttributes = turbulenceFilterAttr
instance HasFilterAttributes DisplacementMap where
  filterAttributes = displacementMapFilterAttr
instance HasFilterAttributes FilterElement where
  filterAttributes = lens getter setter
    where
      getter fe = case fe of
          FEBlend             -> defaultSvg
          FEColorMatrix m     -> m ^. filterAttributes
          FEComponentTransfer -> defaultSvg
          FEComposite c       -> c ^. filterAttributes
          FEConvolveMatrix    -> defaultSvg
          FEDiffuseLighting   -> defaultSvg
          FEDisplacementMap d -> d ^. filterAttributes
          FEDropShadow        -> defaultSvg
          FEFlood             -> defaultSvg
          FEFuncA             -> defaultSvg
          FEFuncB             -> defaultSvg
          FEFuncG             -> defaultSvg
          FEFuncR             -> defaultSvg
          FEGaussianBlur g    -> g ^. filterAttributes
          FEImage             -> defaultSvg
          FEMerge             -> defaultSvg
          FEMergeNode         -> defaultSvg
          FEMorphology        -> defaultSvg
          FEOffset            -> defaultSvg
          FESpecularLighting  -> defaultSvg
          FETile              -> defaultSvg
          FETurbulence t      -> t ^. filterAttributes
          FENone              -> defaultSvg
      setter fe attr = case fe of
        FEBlend             -> fe
        FEColorMatrix m     -> FEColorMatrix $ m & filterAttributes .~ attr
        FEComponentTransfer -> fe
        FEComposite c       -> FEComposite $ c & filterAttributes .~ attr
        FEConvolveMatrix    -> fe
        FEDiffuseLighting   -> fe
        FEDisplacementMap d -> FEDisplacementMap $ d & filterAttributes .~ attr
        FEDropShadow        -> fe
        FEFlood             -> fe
        FEFuncA             -> fe
        FEFuncB             -> fe
        FEFuncG             -> fe
        FEFuncR             -> fe
        FEGaussianBlur g    -> FEGaussianBlur $ g & filterAttributes .~ attr
        FEImage             -> fe
        FEMerge             -> fe
        FEMergeNode         -> fe
        FEMorphology        -> fe
        FEOffset            -> fe
        FESpecularLighting  -> fe
        FETile              -> fe
        FETurbulence t      -> FETurbulence $ t & filterAttributes .~ attr
        FENone              -> fe