\section{Translation}
Changing the vector position of an atom via translation an rotation abut a point
> module ZEBEDDE.Translation 
>              ( translate,
>                com,
>                comFrame,
>                rotate,
>                rotateAboutPoint,
>                rotateInCom) where
> import ZEBEDDE.Core.Vector
> import ZEBEDDE.Core.Molecule
> import qualified ZEBEDDE.Quaternion as Q
Define translation for molecules
> translate :: Vec -> (Molecule -> Molecule)
> translate v = doToMolecule (map (doToAtom (+v)))
> rotate :: Vec -> Double -> (Molecule -> Molecule)
> rotate v d = doToMolecule' (Q.rotate (v,d))
Rotate about a point
> rotateAboutPoint :: Vec -> Vec -> Double -> (Molecule -> Molecule)
> rotateAboutPoint center axis theta = t3.t2.t1
>  where
>   t1 = translate (0center)
>   t2 = rotate axis theta
>   t3 = translate center
Perform a rotation on a Molecule in its center of mass frame
> centerOfMass :: [Atom] -> Vec
> centerOfMass atoms = (sum x) / (sum ms)
>  where
>     x = zipWith (*) ms rs
>     ms = map fromIntegral ms'
>     (_,ms',rs) = unzip3 atoms
> com = centerOfMass.atoms 
> comFrame :: Molecule -> Molecule
> comFrame m@(_,_,atoms) = translate (0(centerOfMass atoms)) m
> rotateInCom :: Vec -> Double -> Molecule -> Molecule 
> rotateInCom axis theta m = rotateAboutPoint (com m) axis theta m