Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Direction type #186

Merged
merged 23 commits into from
Jun 11, 2014
Merged
Show file tree
Hide file tree
Changes from 7 commits
Commits
Show all changes
23 commits
Select commit Hold shift + click to select a range
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
14 changes: 11 additions & 3 deletions src/Diagrams/Angle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,16 +23,24 @@ module Diagrams.Angle
, HasTheta(..)
) where

import Control.Lens (Iso', Lens', iso, review, (^.))
-- , review , (^.), _1, _2, Lens', lens)
import Control.Lens (Iso', Lens', iso, review, (^.))

import Data.VectorSpace
import Data.Monoid hiding ((<>))
import Data.Semigroup
import Data.VectorSpace

-- | Angles can be expressed in a variety of units. Internally,
-- they are represented in radians.
newtype Angle = Radians Double
deriving (Read, Show, Eq, Ord, Enum, AdditiveGroup)

instance Semigroup Angle where
(<>) = (^+^)

instance Monoid Angle where
mappend = (<>)
mempty = Radians 0

instance VectorSpace Angle where
type Scalar Angle = Double
s *^ Radians t = Radians (s*t)
Expand Down
54 changes: 54 additions & 0 deletions src/Diagrams/Direction.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
-----------------------------------------------------------------------------
-- |
-- Module : Diagrams.Angle
Copy link
Contributor

Choose a reason for hiding this comment

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

Should be Diagrams.Direction?

-- Copyright : (c) 2013 diagrams-lib team (see LICENSE)
-- License : BSD-style (see LICENSE)
-- Maintainer : diagrams-discuss@googlegroups.com
--
-- Type for representing directions, polymorphic in vector space
--
-----------------------------------------------------------------------------

module Diagrams.Direction
( Direction
, _Dir
, direction, fromDirection
, angleBetweenDirs
) where

import Control.Lens
import Data.VectorSpace

import Diagrams.Angle

--------------------------------------------------------------------------------
-- Direction

-- | A vector is described by a @Direction@ and a magnitude. So we
-- can think of a @Direction@ as a vector that has forgotten its
-- magnitude. @Direction@s can be used with 'fromDirection' and the
-- lenses provided by its instances.
data Direction v = Direction v

-- | _Dir is provided to allow efficient implementations of functions
-- in particular vector-spaces, but should be used with care as it
-- exposes too much information.
_Dir :: Iso' (Direction v) v
_Dir = iso (\(Direction v) -> v) Direction

-- | @direction v@ is the direction in which @v@ points. Returns an
-- unspecified value when given the zero vector as input.
direction :: v -> Direction v
direction = Direction

-- | @fromDirection d@ is the unit vector in the direction @d@.
fromDirection :: (InnerSpace v, Floating (Scalar v)) => Direction v -> v
fromDirection (Direction v) = normalized v

-- | compute the positive angle between the two directions in their common plane
angleBetweenDirs :: (InnerSpace v, Scalar v ~ Double) =>
Direction v -> Direction v -> Angle
angleBetweenDirs d1 d2 = angleBetween (fromDirection d1) (fromDirection d2)
3 changes: 3 additions & 0 deletions src/Diagrams/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,6 +88,8 @@ module Diagrams.Prelude
, module Diagrams.Angle
-- | Convenience infix operators for working with coordinates.
, module Diagrams.Coordinates
-- | Directions, distinguished from angles or vectors
, module Diagrams.Direction

-- | A wide range of things (shapes, transformations,
-- combinators) specific to creating two-dimensional
Expand Down Expand Up @@ -132,6 +134,7 @@ import Diagrams.Combinators
import Diagrams.Coordinates
import Diagrams.CubicSpline
import Diagrams.Deform
import Diagrams.Direction
import Diagrams.Envelope
import Diagrams.Located
import Diagrams.Names
Expand Down
7 changes: 4 additions & 3 deletions src/Diagrams/ThreeD/Camera.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ import Data.Typeable

import Diagrams.Angle
import Diagrams.Core
import Diagrams.Direction
import Diagrams.ThreeD.Types
import Diagrams.ThreeD.Vector

Expand Down Expand Up @@ -118,13 +119,13 @@ mm50Wide = PerspectiveLens (43.2 @@ deg) (27 @@ deg)
-- aspect ratio of 4:3, for VGA and similar computer resulotions.
mm50Narrow = PerspectiveLens (36 @@ deg) (27 @@ deg)

camForward :: Camera l -> Direction
camForward :: Camera l -> Direction R3
camForward = direction . forward

camUp :: Camera l -> Direction
camUp :: Camera l -> Direction R3
camUp = direction . up

camRight :: Camera l -> Direction
camRight :: Camera l -> Direction R3
camRight c = direction right where
right = cross3 (forward c) (up c)

Expand Down
3 changes: 2 additions & 1 deletion src/Diagrams/ThreeD/Light.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ import Data.Monoid
import Data.Typeable

import Diagrams.Core
import Diagrams.Direction
import Diagrams.ThreeD.Types

data PointLight = PointLight P3 (Colour Double)
Expand Down Expand Up @@ -48,7 +49,7 @@ pointLight c = mkQD (Prim $ PointLight origin c) mempty mempty mempty

-- | Construct a Diagram with a single ParallelLight, which takes up no space.
parallelLight :: (Backend b R3, Renderable ParallelLight b)
=> Direction -- ^ The direction in which the light travels.
=> Direction R3 -- ^ The direction in which the light travels.
-> Colour Double -- ^ The color of the light.
-> Diagram b R3
parallelLight d c = mkQD (Prim $ ParallelLight (fromDirection d) c)
Expand Down
5 changes: 3 additions & 2 deletions src/Diagrams/ThreeD/Transform.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ import Diagrams.Core
import qualified Diagrams.Core.Transform as T

import Diagrams.Angle
import Diagrams.Direction
import Diagrams.Transform
import Diagrams.ThreeD.Types
import Diagrams.Coordinates
Expand Down Expand Up @@ -104,7 +105,7 @@ aboutY ang = fromLinear r (linv r) where
-- passing through @p@.
rotationAbout ::
P3 -- ^ origin of rotation
-> Direction -- ^ direction of rotation axis
-> Direction R3 -- ^ direction of rotation axis
-> Angle -- ^ angle of rotation
-> T3
rotationAbout p d a
Expand All @@ -127,7 +128,7 @@ rotationAbout p d a
-- without tilting, it will be, otherwise if only tilting is
-- necessary, no panning will occur. The tilt will always be between
-- ± 1/4 turn.
pointAt :: Direction -> Direction -> Direction -> T3
pointAt :: Direction R3 -> Direction R3 -> Direction R3 -> T3
pointAt a i f = pointAt' (fromDirection a) (fromDirection i) (fromDirection f)

-- | pointAt' has the same behavior as 'pointAt', but takes vectors
Expand Down
33 changes: 3 additions & 30 deletions src/Diagrams/ThreeD/Types.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
Expand All @@ -26,8 +25,6 @@ module Diagrams.ThreeD.Types
, T3
, r3Iso, p3Iso

-- * Directions in 3D
, Direction, direction, fromDirection, angleBetweenDirs
-- * other coördinate systems
, Spherical(..), Cylindrical(..), HasPhi(..)
) where
Expand All @@ -37,6 +34,7 @@ import Control.Lens (Iso', Lens', iso, over

import Diagrams.Core
import Diagrams.Angle
import Diagrams.Direction
import Diagrams.TwoD.Types (R2)
import Diagrams.Coordinates

Expand Down Expand Up @@ -122,18 +120,6 @@ instance Transformable R3 where
instance HasCross3 R3 where
cross3 u v = r3 $ cross3 (unr3 u) (unr3 v)

--------------------------------------------------------------------------------
-- Direction

-- | A @Direction@ represents directions in R3. The constructor is
-- not exported; @Direction@s can be used with 'fromDirection' and the
-- lenses provided by its instances.
data Direction = Direction R3

-- | Not exported
_Dir :: Iso' Direction R3
_Dir = iso (\(Direction v) -> v) Direction

instance HasX R3 where
_x = r3Iso . _1

Expand Down Expand Up @@ -203,21 +189,8 @@ instance Cylindrical P3 where
instance Spherical P3 where
spherical = _relative origin . spherical

instance HasTheta Direction where
instance HasTheta (Direction R3) where
_theta = _Dir . _theta

instance HasPhi Direction where
instance HasPhi (Direction R3) where
_phi = _Dir . _phi

-- | @direction v@ is the direction in which @v@ points. Returns an
-- unspecified value when given the zero vector as input.
direction :: R3 -> Direction
direction = Direction

-- | @fromDirection d@ is the unit vector in the direction @d@.
fromDirection :: Direction -> R3
fromDirection (Direction v) = normalized v

-- | compute the positive angle between the two directions in their common plane
angleBetweenDirs :: Direction -> Direction -> Angle
angleBetweenDirs d1 d2 = angleBetween (fromDirection d1) (fromDirection d2)
3 changes: 1 addition & 2 deletions src/Diagrams/TwoD.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,6 @@ module Diagrams.TwoD
, P2, p2, unp2, mkP2
, T2
, unitX, unitY, unit_X, unit_Y
, direction, fromDirection

-- * Angles
, tau
Expand Down Expand Up @@ -200,7 +199,7 @@ module Diagrams.TwoD

-- * Combinators
-- ** Combining multiple diagrams
, (===), (|||), atAngle
, (===), (|||), atDirection
, hcat, hcat'
, vcat, vcat'

Expand Down
Loading