module Anims where import Basics import Objects import Vectors import Camera import World import Control.Applicative sequ :: [Anim a] -> Anim [a] sequ (x:xs) t = x t : sequ xs t sequ [] t = [] type Anim a = Scal -> a aObject :: Anim Shape -> Texture -> Int -> Anim Object aObject shape color id time = Object id (shape time) (color) aMeta l threshold t = Meta [f t | f <- l] (threshold t) -- aMetaPoint = liftA2 MetaPoint -- aPlane = liftA2 Plane (|+|), (|-|), (|*|) :: Anim Scal -> Anim Scal -> Anim Scal (|+|) = liftA2 (+) (|-|) = liftA2 (-) (|*|) = liftA2 (*) -- aRowProd = liftA2 rowProd orbit :: Anim Vector -> -- axis Anim Vector -> -- starting point Anim Vector orbit axis point time = rotateMatrix time (normalized (axis time)) `mulVec` (point time) liss :: Anim Vector -> Anim Vector -> Anim Vector -> Anim Vector liss ampl freq phase time = ampl time `rowProd` liftV sin ((time `scale` freq time) + phase time) ask :: Anim Scal ask time = time