Skip to content

Commit

Permalink
add Transformable instance for FontSize
Browse files Browse the repository at this point in the history
  • Loading branch information
jeffreyrosenbluth committed Mar 25, 2014
1 parent 5af2c2f commit 751f93b
Show file tree
Hide file tree
Showing 3 changed files with 21 additions and 15 deletions.
10 changes: 1 addition & 9 deletions src/Diagrams/TwoD/Attributes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -38,15 +37,8 @@ import Data.Default.Class
import Data.Semigroup

import Diagrams.Core
import Diagrams.TwoD.Types (R2)
import Diagrams.TwoD.Types

-----------------------------------------------------------------

type instance V (Measure Double) = R2

instance Transformable (Measure Double) where
transform tr (Local x) = Local (avgScale tr * x)
transform _ y = y

-----------------------------------------------------------------
-- Line Width -------------------------------------------------
Expand Down
18 changes: 12 additions & 6 deletions src/Diagrams/TwoD/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,8 +38,8 @@ import Diagrams.TwoD.Types
import Data.AffineSpace ((.-.))
import Data.Semigroup
import Data.Colour
import Data.Data
import Data.Default.Class
import Data.Typeable

------------------------------------------------------------
-- Text diagrams
Expand Down Expand Up @@ -162,25 +162,31 @@ font = applyAttr . Font . Last
-- | The @FontSize@ attribute specifies the size of a font's
-- em-square. Inner @FontSize@ attributes override outer ones.
newtype FontSize = FontSize (Last (Measure Double))
deriving (Typeable, Semigroup)
deriving (Typeable, Data, Semigroup)
instance AttributeClass FontSize

type instance V FontSize = R2

instance Default FontSize where
def = FontSize (Last (Local 1))

instance Transformable FontSize where
transform t (FontSize (Last s)) =
FontSize (Last (transform t s))

-- | Extract the size from a @FontSize@ attribute.
getFontSize :: FontSize -> Measure Double
getFontSize (FontSize (Last s)) = s

-- | Set the font size, that is, the size of the font's em-square as
-- measured within the current local vector space. The default size
-- is @1@.
fontSize :: HasStyle a => Measure Double -> a -> a
fontSize = applyAttr . FontSize . Last
fontSize :: (HasStyle a, V a ~ R2) => Measure Double -> a -> a
fontSize = applyGTAttr . FontSize . Last

-- | Apply a 'FontSize' attribute.
fontSizeA :: HasStyle a => FontSize -> a -> a
fontSizeA = applyAttr
fontSizeA :: (HasStyle a, V a ~ R2) => FontSize -> a -> a
fontSizeA = applyGTAttr

--------------------------------------------------
-- Font slant
Expand Down
8 changes: 8 additions & 0 deletions src/Diagrams/TwoD/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -244,3 +244,11 @@ instance HasR P2 where

instance HasTheta P2 where
_theta = _relative origin . _theta

-----------------------------------------------------------------

type instance V (Measure Double) = R2

instance Transformable (Measure Double) where
transform tr (Local x) = Local (avgScale tr * x)
transform _ y = y

0 comments on commit 751f93b

Please sign in to comment.