{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Diagrams.TwoD.Adjust
( setDefault2DAttributes
, adjustSize2D
, adjustDia2D
) where
import Diagrams.Attributes
import Diagrams.BoundingBox
import Diagrams.Core
import Diagrams.Size
import Diagrams.TwoD.Attributes (lineTextureA)
import Diagrams.TwoD.Types
import Diagrams.Util (( # ))
import Control.Lens (Lens', set, (^.))
import Data.Default.Class
import Data.Semigroup
setDefault2DAttributes :: (TypeableFloat n, Semigroup m)
=> QDiagram b V2 n m -> QDiagram b V2 n m
setDefault2DAttributes :: forall n m b.
(TypeableFloat n, Semigroup m) =>
QDiagram b V2 n m -> QDiagram b V2 n m
setDefault2DAttributes QDiagram b V2 n m
d
= QDiagram b V2 n m
d forall a b. a -> (a -> b) -> b
# forall a n.
(N a ~ n, HasStyle a, Typeable n) =>
LineWidthM n -> a -> a
lineWidthM forall a. Default a => a
def
# lineTextureA def
# lineCap def
# lineJoin def
# lineMiterLimitA def
adjustSize2D
:: (TypeableFloat n, Monoid' m)
=> Lens' (Options b V2 n) (SizeSpec V2 n)
-> b
-> Options b V2 n
-> QDiagram b V2 n m
-> (Options b V2 n, Transformation V2 n, QDiagram b V2 n m)
adjustSize2D :: forall n m b.
(TypeableFloat n, Monoid' m) =>
Lens' (Options b V2 n) (SizeSpec V2 n)
-> b
-> Options b V2 n
-> QDiagram b V2 n m
-> (Options b V2 n, Transformation V2 n, QDiagram b V2 n m)
adjustSize2D Lens' (Options b V2 n) (SizeSpec V2 n)
szL b
_ Options b V2 n
opts QDiagram b V2 n m
d = (forall s t a b. ASetter s t a b -> b -> s -> t
set Lens' (Options b V2 n) (SizeSpec V2 n)
szL SizeSpec V2 n
spec Options b V2 n
opts, Transformation V2 n
t, QDiagram b V2 n m
d forall a b. a -> (a -> b) -> b
# forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation V2 n
t)
where
spec :: SizeSpec V2 n
spec = forall (v :: * -> *) n. v n -> SizeSpec v n
dims V2 n
sz
(V2 n
sz, Transformation V2 n
t) = forall (v :: * -> *) n.
(Additive v, Foldable v, OrderedField n) =>
SizeSpec v n -> BoundingBox v n -> (v n, Transformation v n)
sizeAdjustment (Options b V2 n
opts forall s a. s -> Getting a s a -> a
^. Lens' (Options b V2 n) (SizeSpec V2 n)
szL) (forall (v :: * -> *) n a.
(InSpace v n a, HasBasis v, Enveloped a) =>
a -> BoundingBox v n
boundingBox QDiagram b V2 n m
d)
adjustDia2D :: (TypeableFloat n, Monoid' m)
=> Lens' (Options b V2 n) (SizeSpec V2 n)
-> b -> Options b V2 n -> QDiagram b V2 n m
-> (Options b V2 n, Transformation V2 n, QDiagram b V2 n m)
adjustDia2D :: forall n m b.
(TypeableFloat n, Monoid' m) =>
Lens' (Options b V2 n) (SizeSpec V2 n)
-> b
-> Options b V2 n
-> QDiagram b V2 n m
-> (Options b V2 n, Transformation V2 n, QDiagram b V2 n m)
adjustDia2D Lens' (Options b V2 n) (SizeSpec V2 n)
szL b
b Options b V2 n
opts QDiagram b V2 n m
d
= forall n m b.
(TypeableFloat n, Monoid' m) =>
Lens' (Options b V2 n) (SizeSpec V2 n)
-> b
-> Options b V2 n
-> QDiagram b V2 n m
-> (Options b V2 n, Transformation V2 n, QDiagram b V2 n m)
adjustSize2D Lens' (Options b V2 n) (SizeSpec V2 n)
szL b
b Options b V2 n
opts (QDiagram b V2 n m
d forall a b. a -> (a -> b) -> b
# forall n m b.
(TypeableFloat n, Semigroup m) =>
QDiagram b V2 n m -> QDiagram b V2 n m
setDefault2DAttributes)