Skip to content

Commit

Permalink
Wall: add instances for Polar
Browse files Browse the repository at this point in the history
move some instances around,
remove some imports
  • Loading branch information
bergey committed May 16, 2014
1 parent e6c1433 commit ddce8f6
Show file tree
Hide file tree
Showing 8 changed files with 26 additions and 24 deletions.
2 changes: 1 addition & 1 deletion src/Diagrams/Direction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,10 @@ module Diagrams.Direction
( Direction
, _Dir
, direction, fromDirection
, angleBetweenDirs
) where

import Control.Lens
import Data.AffineSpace
import Data.VectorSpace

import Diagrams.Angle
Expand Down
5 changes: 2 additions & 3 deletions src/Diagrams/TwoD/Arc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ import Diagrams.Trail
import Diagrams.TrailLike
import Diagrams.TwoD.Transform
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector (e, unitX, unitY, unit_Y, xDir)
import Diagrams.TwoD.Vector (unitX, unitY, unit_Y, xDir)
import Diagrams.Util (( # ))

import Control.Lens ((^.))
Expand Down Expand Up @@ -98,7 +98,7 @@ arcT start sweep
| sweep < zeroV = arcT start (sweep ^-^ (fromIntegral d @@ turn))
| otherwise = (if sweep >= fullTurn then glueTrail else id)
$ trailFromSegments bs
where end = start .+^ sweep
where
bs = map (rotate $ start .-. xDir) . bezierFromSweep $ sweep
d = floor (sweep^.turn) :: Integer

Expand Down Expand Up @@ -175,7 +175,6 @@ arcBetween p q ht = trailLike (a # rotate (v^._theta) # moveTo p)
mid | ht >= 0 = direction unitY
| otherwise = direction unit_Y
st = mid .-^ th
end = mid .+^ th
a | isStraight
= fromOffsets [d *^ unitX]
| otherwise
Expand Down
4 changes: 2 additions & 2 deletions src/Diagrams/TwoD/Arrowheads.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ module Diagrams.TwoD.Arrowheads
, ArrowHT
) where

import Control.Lens ((&), (.~), (^.), (%~), (-~), (+~))
import Control.Lens ((&), (.~), (^.))
import Data.AffineSpace
import Data.Default.Class
import Data.Monoid (mempty, (<>))
Expand All @@ -76,7 +76,7 @@ import Diagrams.TwoD.Polygons
import Diagrams.TwoD.Shapes
import Diagrams.TwoD.Transform
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector (e, unitX, unit_X, xDir)
import Diagrams.TwoD.Vector (e, unit_X, xDir)
import Diagrams.Util (( # ))

-----------------------------------------------------------------------------
Expand Down
3 changes: 1 addition & 2 deletions src/Diagrams/TwoD/Combinators.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module Diagrams.TwoD.Combinators
(
-- * Binary combinators

(===), (|||), atAngle
(===), (|||), atDirection

-- * n-ary combinators
, hcat, hcat'
Expand All @@ -45,7 +45,6 @@ import Data.VectorSpace

import Diagrams.Core

import Diagrams.Angle
import Diagrams.BoundingBox
import Diagrams.Combinators
import Diagrams.Coordinates
Expand Down
4 changes: 1 addition & 3 deletions src/Diagrams/TwoD/Ellipse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,6 @@ module Diagrams.TwoD.Ellipse
, ellipseXY
) where

import Data.AdditiveGroup

import Diagrams.Core

import Diagrams.Angle
Expand All @@ -32,7 +30,7 @@ import Diagrams.TrailLike
import Diagrams.TwoD.Arc
import Diagrams.TwoD.Transform
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector
import Diagrams.TwoD.Vector (xDir)
import Diagrams.Util

-- | A circle of radius 1, with center at the origin.
Expand Down
2 changes: 0 additions & 2 deletions src/Diagrams/TwoD/Transform/ScaleInv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ module Diagrams.TwoD.Transform.ScaleInv
where

import Control.Lens (makeLenses, view)
import Data.AdditiveGroup
import Data.AffineSpace ((.-.))
import Data.Semigroup
import Data.Typeable
Expand All @@ -30,7 +29,6 @@ import Diagrams.Angle
import Diagrams.Core
import Diagrams.TwoD.Transform
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector

-- | The @ScaleInv@ wrapper creates two-dimensional /scale-invariant/
-- objects. Intuitively, a scale-invariant object is affected by
Expand Down
22 changes: 18 additions & 4 deletions src/Diagrams/TwoD/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,13 +28,15 @@ module Diagrams.TwoD.Types
) where

import Control.Lens (Iso', Rewrapped, Wrapped (..), iso,
lens, (^.), _1, _2)
(^.), (&), (<>~), _1, _2)


import Diagrams.Angle
import Diagrams.Direction
import Diagrams.Coordinates
import Diagrams.Core

import Data.AffineSpace
import Data.AffineSpace.Point
import Data.Basis
import Data.MemoTrie (HasTrie (..))
Expand Down Expand Up @@ -182,11 +184,10 @@ instance HasY R2 where
_y = r2Iso . _2

instance HasTheta R2 where
_theta = lens (\v -> atanA (v^._y / v^._x))
(\v θ -> let r = magnitude v in R2 (r * cosA θ) (r * sinA θ))
_theta = polar._2

instance HasR R2 where
_r = lens magnitude (\v r -> let s = r/magnitude v in s *^ v)
_r = polar._1

instance HasTheta (Direction R2) where
_theta = _Dir . _theta
Expand Down Expand Up @@ -252,3 +253,16 @@ instance HasTheta P2 where
-- | Types which can be expressed in polar 2D coordinates, as a magnitude and an angle.
class Polar t where
polar :: Iso' t (Double, Angle)

instance Polar R2 where
polar =
iso (\v -> ( magnitude v, atanA (v^._y / v^._x)))

This comment has been minimized.

Copy link
@fryguybob

fryguybob May 18, 2014

Member

Shouldn't this use atan2?

(\(r,θ) -> R2 (r * cosA θ) (r * sinA θ))

instance Polar P2 where
polar = _relative origin . polar

instance AffineSpace (Direction R2) where
type Diff (Direction R2) = Angle
a .-. b = a^._theta ^-^ b^._theta
a .+^ θ = a & _theta <>~ θ

This comment has been minimized.

Copy link
@bergey

bergey May 17, 2014

Author Member

This is a weird instance since (d .+^ a) .-. d is not a for a > fullTurn. Is that a problem?

This comment has been minimized.

Copy link
@byorgey

byorgey May 26, 2014

Member

Wait, it's not? Why is that?

This comment has been minimized.

Copy link
@bergey

bergey May 26, 2014

Author Member

For example xDir .+^ fullTurn = xDir. Going around a full turn brings you back to the starting direction, and the Direction type has no notion of the path taken to get there. Having thought about this a bit more, I think we should remove the instance. angleBetweenDirs and rotate give us the same behavior, without breaking laws.

This comment has been minimized.

Copy link
@byorgey

byorgey May 26, 2014

Member

Oh, right, I see now. It fails the uniqueness law (http://en.wikipedia.org/wiki/Affine_space#Definition). Yes, removing it is probably the right thing to do. The fact that there is "almost" an affine space in R2 seems sort of like an accident, since it breaks down in higher dimensions.

8 changes: 1 addition & 7 deletions src/Diagrams/TwoD/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,9 +23,8 @@ module Diagrams.TwoD.Vector
, perp, leftTurn
) where

import Control.Lens ((^.), (&), (<>~))
import Data.VectorSpace
import Data.AffineSpace
import Data.VectorSpace

import Diagrams.Angle
import Diagrams.Direction
Expand All @@ -48,11 +47,6 @@ unit_X = (-1) ^& 0
unit_Y :: R2
unit_Y = 0 ^& (-1)

instance AffineSpace (Direction R2) where
type Diff (Direction R2) = Angle
a .-. b = a^._theta ^-^ b^._theta
a .+^ θ = a & _theta <>~ θ

-- | The origin of the direction AffineSpace. For all d, @d .-. xDir
-- = d^._theta@.
xDir :: Direction R2
Expand Down

0 comments on commit ddce8f6

Please sign in to comment.