Skip to content

Commit

Permalink
Add Direction type
Browse files Browse the repository at this point in the history
  • Loading branch information
bergey committed May 16, 2014
1 parent e59214d commit 2d18288
Show file tree
Hide file tree
Showing 2 changed files with 57 additions and 0 deletions.
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
-- 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
) where

import Control.Lens
import Data.AffineSpace
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

This comment has been minimized.

Copy link
@bergey

bergey May 17, 2014

Author Member

Should this be a newtype?


-- | _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

0 comments on commit 2d18288

Please sign in to comment.