{- | Various facilities for dealing with vectors generically. -} {-# LANGUAGE MultiParamTypeClasses #-} module Data.Vector.Fancy where import Data.Vector.Class import Data.Vector.V1 import Data.Vector.V2 import Data.Vector.V3 import Data.Vector.V4 import Data.Vector.Axis -- | Class for generically reading/writing vector coordinates. class VectorAxis vector axis where -- | Read from the specified coordinate axis. get_coord :: axis -> vector -> Scalar -- | Replace the existing value of the given coordinate axis. set_coord :: axis -> Scalar -> vector -> vector -- | This class relates two vector types having consecutive sizes. class Project lo hi where -- | Reduce number of dimensions by one. (Return the dropped dimension as a @Scalar@.) orthographic_down :: hi -> (lo, Scalar) -- | Increase number of dimensions by one. (Supply value for new dimension as a @Scalar@.) orthographic_up :: (lo, Scalar) -> hi -- | Perspective-project to N-1 dimensions. (Also return the distance from the camera as a @Scalar@.) perspective_down :: hi -> (lo, Scalar) -- | Inverse-perspective project into N+1 dimension. (Supply the distance from the camera as a @Scalar@.) perspective_up :: (lo, Scalar) -> hi instance VectorAxis Vector1 AxisX where get_coord _ = v1x set_coord _ x _ = Vector1 x instance VectorAxis Vector2 AxisX where get_coord _ = v2x set_coord _ x v = v {v2x = x} instance VectorAxis Vector3 AxisX where get_coord _ = v3x set_coord _ x v = v {v3x = x} instance VectorAxis Vector4 AxisX where get_coord _ = v4x set_coord _ x v = v {v4x = x} instance VectorAxis Vector2 AxisY where get_coord _ = v2y set_coord _ y v = v {v2y = y} instance VectorAxis Vector3 AxisY where get_coord _ = v3y set_coord _ y v = v {v3y = y} instance VectorAxis Vector4 AxisY where get_coord _ = v4y set_coord _ y v = v {v4y = y} instance VectorAxis Vector3 AxisZ where get_coord _ = v3z set_coord _ z v = v {v3z = z} instance VectorAxis Vector4 AxisZ where get_coord _ = v4z set_coord _ z v = v {v4z = z} instance VectorAxis Vector4 AxisW where get_coord _ = v4w set_coord _ w v = v {v4w = w} instance Project Vector1 Vector2 where orthographic_down (Vector2 x y) = (Vector1 x, y) orthographic_up (Vector1 x, y) = (Vector2 x y) perspective_down (Vector2 x y) = (Vector1 (x/y), y) perspective_up (Vector1 x, y) = (Vector2 (x*y) y) instance Project Vector2 Vector3 where orthographic_down (Vector3 x y z) = (Vector2 x y, z) orthographic_up (Vector2 x y, z) = (Vector3 x y z) perspective_down (Vector3 x y z) = (Vector2 (x/z) (y/z), z) perspective_up (Vector2 x y, z) = (Vector3 (x*z) (y*z) z) instance Project Vector3 Vector4 where orthographic_down (Vector4 x y z w) = (Vector3 x y z, w) orthographic_up (Vector3 x y z, w) = (Vector4 x y z w) perspective_down (Vector4 x y z w) = (Vector3 (x/w) (y/w) (z/w), w) perspective_up (Vector3 x y z, w) = (Vector4 (x*w) (y*w) (z*w) w)