Skip to content

Commit

Permalink
Merge pull request #78 from bergey/matrix-basis-rep
Browse files Browse the repository at this point in the history
Matrix basis rep
  • Loading branch information
byorgey committed Mar 22, 2013
2 parents ac0fdb5 + 05049d2 commit 0b58a5f
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 8 deletions.
11 changes: 3 additions & 8 deletions src/Diagrams/Backend/Show.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@
module Diagrams.Backend.Show where

import Diagrams.Prelude
import Diagrams.Core.Transform (onBasis)

import Data.Basis

Expand Down Expand Up @@ -46,14 +47,8 @@ instance Monoid (Render ShowBackend v) where
renderTransf :: forall v. (Num (Scalar v), HasLinearMap v, Show (Scalar v))
=> Transformation v -> Doc
renderTransf t = renderMat mat
where tr :: v
tr = transl t
basis :: [Basis v]
basis = map fst (decompose tr)
es :: [v]
es = map basisValue basis
vmat :: [v]
vmat = map (apply t) es
where vmat :: [v]
(vmat, _) = onBasis t
mat :: [[Scalar v]]
mat = map decompV vmat
-- mat' :: [[Scalar v]]
Expand Down
10 changes: 10 additions & 0 deletions src/Diagrams/TwoD/Transform.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,9 +48,12 @@ module Diagrams.TwoD.Transform
-- * Scale invariance
, ScaleInv(..), scaleInv

-- * component-wise
, onBasis
) where

import Diagrams.Core
import qualified Diagrams.Core.Transform as T

import Control.Newtype (over)

Expand Down Expand Up @@ -308,3 +311,10 @@ instance (V t ~ R2, Transformable t) => Transformable (ScaleInv t) where
rot = rotateAbout l angle
l' = transform tr l
trans = translate (l' .-. l)

-- | Get the matrix equivalent of the linear transform,
-- (as a pair of columns) and the translation vector. This
-- is mostly useful for implementing backends.
onBasis :: Transformation R2 -> ((R2, R2), R2)
onBasis t = ((x, y), v)
where ((x:y:[]), v) = T.onBasis t

0 comments on commit 0b58a5f

Please sign in to comment.