{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} {-# OPTIONS_GHC -Wall #-} ---------------------------------------------------------------------- -- | -- Module : Transform -- Copyright : (c) Conal Elliott and Andy J Gill 2008 -- License : BSD3 -- -- Maintainer : conal@conal.net, andygill@ku.edu -- Stability : experimental -- -- General transform class ---------------------------------------------------------------------- module Graphics.FieldTrip.Transform (Transform(..), Invertible(..)) where import Control.Arrow ((***)) -- import Control.Applicative (liftA2) infixr 7 *% -- transform application -- | General transform class class Transform xf a where -- | Transform a value (*%) :: xf -> a -> a instance (Transform xf a, Transform xf b) => Transform xf (a,b) where (*%) xf = (*%) xf *** (*%) xf -- Alternative definitions: -- xf *% (a,b) = (xf *% a, xf *% b) -- (*%) = liftA2 (***) (*%) (*%) instance (Transform xf a, Transform xf b, Transform xf c) => Transform xf (a,b,c) where xf *% (a,b,c) = (xf *% a, xf *% b, xf *% c) instance (Transform xf a, Transform xf b, Transform xf c, Transform xf d) => Transform xf (a,b,c,d) where xf *% (a,b,c,d) = (xf *% a, xf *% b, xf *% c, xf *% d) -- | Invertible transformations class Invertible xf where inverse :: xf -> xf instance (Invertible xf, Transform xf a, Transform xf b) => Transform xf (a -> b) where xf *% f = (xf *%) . f . (inverse xf *%)