Skip to content

Commit

Permalink
change Measure parameter to vector rather than scalar type
Browse files Browse the repository at this point in the history
This lets us properly express vector-space-generic V and Transformable
instances for Measure.
  • Loading branch information
byorgey committed Mar 29, 2014
1 parent 1922a00 commit 004998b
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 8 deletions.
6 changes: 3 additions & 3 deletions src/Diagrams/Core/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -132,7 +132,7 @@ fromDTree = fromDTree' mempty
-- transformation used to convert the diagram from local to output
-- units.
toRTree
:: (HasLinearMap v, InnerSpace v, Data (Scalar v), OrderedField (Scalar v), Monoid m, Semigroup m)
:: (HasLinearMap v, InnerSpace v, Data v, Data (Scalar v), OrderedField (Scalar v), Monoid m, Semigroup m)
=> Transformation v -> QDiagram b v m -> RTree b v Annotation
toRTree globalToOutput d
= (fmap . onRStyle) (toOutput gToO nToO)
Expand Down Expand Up @@ -162,11 +162,11 @@ onRStyle _ n = n
-- case if all transformations have been fully pushed down and
-- applied).
toOutput
:: forall v. (Data (Scalar v), Num (Scalar v))
:: forall v. (Data v, Data (Scalar v), Num (Scalar v))
=> Scalar v -> Scalar v -> Style v -> Style v
toOutput globalToOutput normToOutput = gmapAttrs convert
where
convert :: Measure (Scalar v) -> Measure (Scalar v)
convert :: Measure v -> Measure v
convert m@(Output _) = m
convert (Local s) = Output s
convert (Global s) = Output (globalToOutput * s)
Expand Down
22 changes: 17 additions & 5 deletions src/Diagrams/Core/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
Expand Down Expand Up @@ -166,11 +167,22 @@ import Diagrams.Core.V
-- Measurement Units -------------------------------------
------------------------------------------------------------
-- | Type of measurement units for attributes.
data Measure t = Output t
| Normalized t
| Local t
| Global t
deriving (Eq, Ord, Show, Data, Typeable)
data Measure v = Output (Scalar v)
| Normalized (Scalar v)
| Local (Scalar v)
| Global (Scalar v)
deriving (Typeable)

deriving instance (Eq (Scalar v)) => Eq (Measure v)
deriving instance (Ord (Scalar v)) => Ord (Measure v)
deriving instance (Show (Scalar v)) => Show (Measure v)
deriving instance (Typeable v, Data v, Data (Scalar v)) => Data (Measure v)

type instance V (Measure v) = v

instance (HasLinearMap v, Floating (Scalar v)) => Transformable (Measure v) where
transform tr (Local x) = Local (avgScale tr * x)
transform _ y = y

------------------------------------------------------------
-- Diagrams ----------------------------------------------
Expand Down

2 comments on commit 004998b

@jeffreyrosenbluth
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Ah, I was wondering if there was a way generalize the Transformable instance for Measure.
Nice :)

@byorgey
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, and I think this makes the types read more nicely too: Measure R2 tells me a lot more about the intent than Measure Double.

Please sign in to comment.