{-# LANGUAGE FunctionalDependencies , FlexibleInstances #-} --------------------------------------------------------------------------------------------------- -- | -- Module : SO3 -- Description : Showcase -- Copyright : (c) Felix Springer, 2019 -- License : BSD3 -- Maintainer : felixspringer149@gmail.com -- Stability : experimental -- Portability : POSIX -- -- This is a definition of the SO(3), useful to load into GHCi. -- --------------------------------------------------------------------------------------------------- module LieExample.SO3 ( Vector (..) , crossProduct ) where import Lie.LieAlgebra -- | Vector in ℝ³ data Vector = V Double Double Double deriving Eq -- | Crossproduct, which returns orthogonal vectors where the length is the area of the -- parallelogram spanned by the input vectors crossProduct :: Vector -> Vector -> Vector crossProduct (V a b c) (V d e f) = V (b * f - c * e) (c * d - a * f) (a * e - b * d) instance Show Vector where show (V a b c) = "(" ++ show a ++ " " ++ show b ++ " " ++ show c ++ ")" instance LieAlgebra Vector Double where (|+|) (V a b c) (V d e f) = V (a + b) (c + d) (e + f) (|*|) alpha (V a b c) = V (alpha * a) (alpha * b) (alpha * c) (|.|) = crossProduct basis = [ V 1 0 0 , V 0 1 0 , V 0 0 1 ] trace f = sum $ zipWith euclideanScalarproduct transformedBasis basis where transformedBasis = map f basis euclideanScalarproduct :: Vector -> Vector -> Double euclideanScalarproduct (V a b c) (V d e f) = a * d + b * e + c * f