module Textures where import Basics import Data.Bits( (.&.), xor ) import Colors(blackColor) matte :: Color -> Texture matte col = const Material {diffuse = col, materialReflection = blackColor, materialRefraction = blackColor, materialRefrCoef = 0 } checkboard :: Vector -> Texture -> Texture -> Texture -- mix two texture in a chequer board fashion checkboard unit m1 m2 v = if d .&. 1 == 0 then m1 v else m2 v where d = floor x `xor` floor y `xor` floor z d :: Int Vector x y z = v `rowProd` invUnit invUnit = liftV (1/) unit project :: Vector -> Texture -> Texture -- project a given texture on a plane (axis .* x = 0) project axis t x = t x0 where x0 = x - (axis .* x) `scale` axis