Skip to content

Commit

Permalink
Coordinate lenses for R2, P2, R3, P3, using type classes
Browse files Browse the repository at this point in the history
  • Loading branch information
bergey committed Oct 17, 2013
1 parent 701ac6e commit 6f82ca4
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 6 deletions.
15 changes: 14 additions & 1 deletion src/Diagrams/Coordinates.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,11 @@
-----------------------------------------------------------------------------

module Diagrams.Coordinates
( (:&)(..), Coordinates(..) )
( (:&)(..), Coordinates(..)

-- * Lenses for particular axes
, HasX(..), HasY(..), HasZ(..)
)
where

import Diagrams.Core.Points
Expand Down Expand Up @@ -104,3 +108,12 @@ instance Coordinates v => Coordinates (Point v) where

x & y = P (x & y)
coords (P v) = coords v

class HasX t where
_x :: Functor f => (Double -> f Double) -> t -> f t

class HasY t where
_y :: Functor f => (Double -> f Double) -> t -> f t

class HasZ t where
_z :: Functor f => (Double -> f Double) -> t -> f t
25 changes: 23 additions & 2 deletions src/Diagrams/ThreeD/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ module Diagrams.ThreeD.Types
) where

import Control.Applicative
import Control.Lens (Iso', iso, over)
import Control.Lens (Iso', iso, over, _1, _2, _3)

import Diagrams.Coordinates
import Diagrams.Core
Expand Down Expand Up @@ -99,10 +99,13 @@ type P3 = Point R3
p3 :: (Double, Double, Double) -> P3
p3 = P . R3

-- | Convert a 2D point back into a triple of coordinates.
-- | Convert a 3D point back into a triple of coordinates.
unp3 :: P3 -> (Double, Double, Double)
unp3 = unR3 . unPoint

p3Iso :: Iso' P3 (Double, Double, Double)
p3Iso = iso unp3 p3

-- | Transformations in R^3.
type T3 = Transformation R3

Expand Down Expand Up @@ -149,3 +152,21 @@ instance (Angle a) => Direction (Spherical a) where
-- intermediate type would be ambiguous.
asSpherical :: Spherical Turn -> Spherical Turn
asSpherical = id

instance HasX R3 where
_x = r3Iso . _1

instance HasX P3 where
_x = p3Iso . _1

instance HasY R3 where
_y = r3Iso . _2

instance HasY P3 where
_y = p3Iso . _2

instance HasZ R3 where
_z = r3Iso . _3

instance HasZ P3 where
_z = p3Iso . _3
23 changes: 20 additions & 3 deletions src/Diagrams/TwoD/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,8 @@

module Diagrams.TwoD.Types
( -- * 2D Euclidean space
R2(..), r2, unr2
, P2, p2, unp2
R2(..), r2, unr2, r2Iso
, P2, p2, unp2, p2Iso
, T2

-- * Angles
Expand All @@ -40,7 +40,7 @@ import Data.NumInstances.Tuple ()
import Data.VectorSpace

import Data.Typeable

import Control.Lens (Iso', iso, _1, _2)
------------------------------------------------------------
-- 2D Euclidean space

Expand Down Expand Up @@ -151,6 +151,15 @@ instance Coordinates R2 where
x & y = R2 x y
coords (R2 x y) = x :& y

r2Iso :: Iso' R2 (Double, Double)
r2Iso = iso unr2 r2

instance HasX R2 where
_x = r2Iso . _1

instance HasY R2 where
_y = r2Iso . _2

-- | Points in R^2. This type is intentionally abstract.
--
-- * To construct a point, use 'p2', or '&' (see
Expand Down Expand Up @@ -190,6 +199,14 @@ type T2 = Transformation R2
instance Transformable R2 where
transform = apply

p2Iso :: Iso' P2 (Double, Double)
p2Iso = iso unp2 p2

instance HasX P2 where
_x = p2Iso . _1

instance HasY P2 where
_y = p2Iso . _2
------------------------------------------------------------
-- Angles

Expand Down

0 comments on commit 6f82ca4

Please sign in to comment.