{-# LANGUAGE BangPatterns, TypeOperators, ScopedTypeVariables , TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses #-} {-# OPTIONS_GHC -fno-warn-orphans #-} ---------------------------------------------------------------------- -- | -- Module : Graphics.FieldTrip.Normal3 -- Copyright : (c) Conal Elliott 2008 -- License : BSD3 -- -- Maintainer : conal@conal.net -- Stability : experimental -- -- Normals and Vertex/normal pairs ---------------------------------------------------------------------- module Graphics.FieldTrip.Normal3 ( VN(..), VN3, vectorToNormal3 ) where import Graphics.Rendering.OpenGL hiding (normal) import qualified Graphics.Rendering.OpenGL as G import Graphics.FieldTrip.Point3 import Graphics.FieldTrip.Vector3 -- What do I want here? For displacement mapping, I'll need 'normal' to -- compute a tower. For shading, I'll use the value part of the normal -- and ignore the rest. -- It probably makes more sense to have 'Cross' be the class. Define -- @normal = normalized . cross@. What are some 'Cross' instances? -- Instead of a pair of 3-vectors, start with a @V2 s :> V3 s@ and a @s :> -- V2 s@. -- Hm. I'll want to use tuples for parametric surfaces but vectors for -- rendering. Do I *really* want OpenGL vectors instead of tuples? -- Tuples would get converted to OpenGL vectors, vertices, and normals in -- IO generation anyway. -- | Treat a vector as a normal vectorToNormal3 :: Vector3 s -> Normal3 s vectorToNormal3 (Vector3 x y z) = Normal3 x y z -- | Vertex and normal data VN v n = VN !v !n instance (Vertex v, Normal n) => Vertex (VN v n) where vertex (VN v n) = G.normal n >> vertex v vertexv = error "vertexv: undefined on VN" -- | 3D vertex/normal pair type VN3 s = VN (Point3 s) (Normal3 s)