Skip to content

Commit 844b100

Browse files
committed
Fix facingAB projections.
1 parent 5087488 commit 844b100

File tree

2 files changed

+11
-9
lines changed

2 files changed

+11
-9
lines changed

src/Diagrams/LinearMap.hs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@
2222

2323
module Diagrams.LinearMap where
2424

25-
import Control.Lens hiding (lmap)
25+
import Control.Lens
2626
import Data.FingerTree as FT
2727
import Data.Foldable (Foldable)
2828

@@ -57,12 +57,11 @@ class LinearMappable a b where
5757
-- r ~ A u m => LinearMappable (A v n) r
5858
--
5959
-- so ghc knows there's only one possible result from calling vmap.
60-
-- I can't think of a better way to set up the class.
6160

6261
-- | Apply a linear map.
63-
lmap :: (InSpace v n a, Foldable v, LinearMappable a b, N b ~ n)
62+
linmap :: (InSpace v n a, Foldable v, LinearMappable a b, N b ~ n)
6463
=> LinearMap v (V b) n -> a -> b
65-
lmap = vmap . lapply
64+
linmap = vmap . lapply
6665

6766
instance r ~ Offset c u m => LinearMappable (Offset c v n) r where
6867
vmap f (OffsetClosed v) = OffsetClosed (f v)
@@ -125,7 +124,7 @@ toAffineMap t = AffineMap (toLinearMap t) (transl t)
125124
class (LinearMappable a b, N a ~ N b) => AffineMappable a b where
126125
amap :: (Additive (V a), Foldable (V a), Additive (V b), Num (N b))
127126
=> AffineMap (V a) (V b) (N b) -> a -> b
128-
amap (AffineMap f _) = lmap f
127+
amap (AffineMap f _) = linmap f
129128
{-# INLINE amap #-}
130129

131130
instance r ~ Offset c u n => AffineMappable (Offset c v n) r
@@ -135,7 +134,7 @@ instance (Metric v, Metric u, OrderedField n, r ~ Trail' l u n) => AffineMappabl
135134
instance (Metric v, Metric u, OrderedField n, r ~ Trail u n) => AffineMappable (Trail v n) r
136135

137136
instance (Additive v, Foldable v, Num n, r ~ Point u n) => AffineMappable (Point v n) r where
138-
amap (AffineMap f v) p = lmap f p .+^ v
137+
amap (AffineMap f v) p = linmap f p .+^ v
139138
{-# INLINE amap #-}
140139

141140
instance r ~ FixedSegment u n => AffineMappable (FixedSegment v n) r where
@@ -144,7 +143,7 @@ instance r ~ FixedSegment u n => AffineMappable (FixedSegment v n) r where
144143
{-# INLINE amap #-}
145144

146145
instance (LinearMappable a b, N a ~ N b, r ~ Located b) => AffineMappable (Located a) r where
147-
amap m@(AffineMap l _) (Loc p x) = Loc (amap m p) (lmap l x)
146+
amap m@(AffineMap l _) (Loc p x) = Loc (amap m p) (linmap l x)
148147
{-# INLINE amap #-}
149148

150149
instance (Metric v, Metric u, OrderedField n, r ~ Path u n)

src/Diagrams/ThreeD/Projection.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -78,12 +78,15 @@ import Linear.Projection
7878

7979
-- Parallel projections
8080

81+
-- | Look at the xy-plane with y as the up direction.
8182
facingXY :: (Epsilon n, Floating n) => AffineMap V3 V2 n
82-
facingXY = lookingAt unitX origin zDir
83+
facingXY = lookingAt unitZ origin yDir
8384

85+
-- | Look at the xz-plane with z as the up direction.
8486
facingXZ :: (Epsilon n, Floating n) => AffineMap V3 V2 n
85-
facingXZ = lookingAt unitY origin yDir
87+
facingXZ = lookingAt unitY origin zDir
8688

89+
-- | Look at the yz-plane with z as the up direction.
8790
facingYZ :: (Epsilon n, Floating n) => AffineMap V3 V2 n
8891
facingYZ = lookingAt unitX origin zDir
8992

0 commit comments

Comments
 (0)