Skip to content

Commit

Permalink
various minor Haddock enhancements
Browse files Browse the repository at this point in the history
  • Loading branch information
byorgey committed Mar 11, 2015
1 parent f109b0d commit 3f6ed34
Show file tree
Hide file tree
Showing 6 changed files with 22 additions and 18 deletions.
2 changes: 1 addition & 1 deletion src/Diagrams/Deform.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ import Linear.Vector

-- | @Deformations@ are a superset of the affine transformations
-- represented by the 'Transformation' type. In general they are not
-- invertable. @Deformation@s include projective transformations.
-- invertible. @Deformation@s include projective transformations.
-- @Deformation@ can represent other functions from points to points
-- which are "well-behaved", in that they do not introduce small wiggles.
newtype Deformation v u n = Deformation (Point v n -> Point u n)
Expand Down
6 changes: 3 additions & 3 deletions src/Diagrams/LinearMap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ module Diagrams.LinearMap where

import Control.Lens
import Data.FingerTree as FT
import qualified Data.Foldable as F
import qualified Data.Foldable as F

import Diagrams.Core
import Diagrams.Core.Transform
Expand Down Expand Up @@ -109,8 +109,8 @@ instance (Metric v, Metric u, OrderedField n, OrderedField m, r ~ Path u m)
vmap f = _Wrapped . mapped %~ vmap f
{-# INLINE vmap #-}

-- | Affine linear maps. Unlike Transformation these do not have to be
-- invertable so we can map between spaces.
-- | Affine linear maps. Unlike 'Transformation' these do not have to be
-- invertible so we can map between spaces.
data AffineMap v u n = AffineMap (LinearMap v u n) (u n)

-- | Make an affine map from a linear function and a translation.
Expand Down
11 changes: 6 additions & 5 deletions src/Diagrams/Trail.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,14 +3,14 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE LambdaCase #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
Expand Down Expand Up @@ -107,8 +107,9 @@ module Diagrams.Trail
) where

import Control.Arrow ((***))
import Control.Lens hiding ((|>), (<|), transform, at)
import Data.FingerTree (FingerTree, ViewL (..), ViewR (..), (<|), (|>))
import Control.Lens hiding (at, transform, (<|), (|>))
import Data.FingerTree (FingerTree, ViewL (..), ViewR (..),
(<|), (|>))
import qualified Data.FingerTree as FT
import Data.Fixed
import qualified Data.Foldable as F
Expand Down Expand Up @@ -856,7 +857,7 @@ lineFromSegments :: (Metric v, OrderedField n)
=> [Segment Closed v n] -> Trail' Line v n
lineFromSegments = Line . SegTree . FT.fromList

-- | Contruct a loop from a list of close segments and an open segment
-- | Construct a loop from a list of closed segments and an open segment
-- that completes the loop.
loopFromSegments :: (Metric v, OrderedField n)
=> [Segment Closed v n] -> Segment Open v n -> Trail' Loop v n
Expand Down Expand Up @@ -1181,7 +1182,7 @@ loopVertices = loopVertices' tolerance
-- The other points connecting segments are included if the slope at the
-- end of a segment is not equal to the slope at the beginning of the next.
-- The 'toler' parameter is used to control how close the slopes need to
-- be in order to declatre them equal.
-- be in order to declare them equal.
segmentVertices' :: (Metric v, OrderedField n)
=> n -> Point v n -> [Segment Closed v n] -> [Point v n]
segmentVertices' toler p ts =
Expand Down
9 changes: 6 additions & 3 deletions src/Diagrams/Transform.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,19 +47,22 @@ conjugate :: (Additive v, Num n, Functor v)
=> Transformation v n -> Transformation v n -> Transformation v n
conjugate t1 t2 = inv t1 <> t2 <> t1

-- | Carry out some transformation \"under\" another one: @f ``under``
-- | Carry out some transformation \"under\" another one: @f ``underT``
-- t@ first applies @t@, then @f@, then the inverse of @t@. For
-- example, @'scaleX' 2 ``under`` 'rotation' (-1/8 \@\@ Turn)@
-- example, @'scaleX' 2 ``underT`` 'rotation' (-1/8 \@\@ Turn)@
-- is the transformation which scales by a factor of 2 along the
-- diagonal line y = x.
--
-- Note that
--
-- @
-- (transform t2) `under` t1 == transform (conjugate t1 t2)
-- (transform t2) `underT` t1 == transform (conjugate t1 t2)
-- @
--
-- for all transformations @t1@ and @t2@.
--
-- See also the isomorphisms like 'transformed', 'movedTo',
-- 'movedFrom', and 'translated'.
underT :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b)
=> (a -> b) -> Transformation v n -> a -> b
f `underT` t = transform (inv t) . f . transform t
Expand Down
8 changes: 4 additions & 4 deletions src/Diagrams/Transform/Matrix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,10 +12,10 @@
module Diagrams.Transform.Matrix where

import Control.Applicative
import Control.Arrow ((&&&))
import Control.Arrow ((&&&))
import Control.Lens
import Data.Distributive
import qualified Data.Foldable as F
import qualified Data.Foldable as F
import Data.Functor.Rep

import Diagrams.Core.Transform as D
Expand All @@ -35,13 +35,13 @@ mkMatHomo :: Num n => Transformation V3 n -> M44 n
mkMatHomo t = mkTransformationMat (mkMat t) (transl t)

-- | Make a 2D transformation from a 2x2 transform matrix and a
-- translation vector. If the matrix is not invertable, 'Nothing' is
-- translation vector. If the matrix is not invertible, 'Nothing' is
-- returned.
fromMat22 :: (Epsilon n, Floating n) => M22 n -> V2 n -> Maybe (T2 n)
fromMat22 m v = flip (fromMatWithInv m) v <$> inv22 m

-- | Make a 3D transformation from a 3x3 transform matrix and a
-- translation vector. If the matrix is not invertable, 'Nothing' is
-- translation vector. If the matrix is not invertible, 'Nothing' is
-- returned.
fromMat33 :: (Epsilon n, Floating n) => M33 n -> V3 n -> Maybe (T3 n)
fromMat33 m v = flip (fromMatWithInv m) v <$> inv33 m
Expand Down
4 changes: 2 additions & 2 deletions src/Diagrams/TwoD/Combinators.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,8 +60,8 @@ import Diagrams.TwoD.Vector
import Diagrams.Util (( # ))

import Linear.Affine
import Linear.Vector
import Linear.Metric
import Linear.Vector

infixl 6 ===
infixl 6 |||
Expand Down Expand Up @@ -235,7 +235,7 @@ extrudeTop s
| s >= 0 = extrudeEnvelope $ unitY ^* s
| otherwise = intrudeEnvelope $ unitY ^* s

-- | @boxEnvelope p v@ sets the envelope of a diagram to a rectangle whose
-- | @rectEnvelope p v@ sets the envelope of a diagram to a rectangle whose
-- lower-left corner is at @p@ and whose upper-right corner is at @p
-- .+^ v@. Useful for selecting the rectangular portion of a
-- diagram which should actually be \"viewed\" in the final render,
Expand Down

1 comment on commit 3f6ed34

@cchalmers
Copy link
Member

Choose a reason for hiding this comment

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

Thanks :)

Please sign in to comment.