了解 OpenGL 中的光照
Understanding lighting in OpenGL
我正在尝试用 Haskell / GLUT 从一堆三角形中创建一个 3D 球体。它工作得很好:绿色的是 "my" 球体,红色的是用 GLUT 的 renderObject Sphere' 完成的。当我四处移动相机时,我可以看到 "my" 球体是真正的 3D,这很好。
那么为什么 GLUT 的灯光很好,而我的却没有? (我是一个新手,并不知道我在下面的 initGL 中做了什么,从 Hackage 的 cuboid 包中复制了这些东西...)
代码如下:
module Main where
import Graphics.UI.GLUT
main :: IO ()
main = do
initGL
displayCallback $= render
mainLoop
initGL :: IO ()
initGL = do
getArgsAndInitialize
initialDisplayMode $= [DoubleBuffered]
createWindow "Chip!"
initialDisplayMode $= [ WithDepthBuffer ]
depthFunc $= Just Less
clearColor $= Color4 0 0 0 0
light (Light 0) $= Enabled
lighting $= Enabled
lightModelAmbient $= Color4 0.5 0.5 0.5 1
diffuse (Light 0) $= Color4 1 1 1 1
blend $= Enabled
blendFunc $= (SrcAlpha, OneMinusSrcAlpha)
colorMaterial $= Just (FrontAndBack, AmbientAndDiffuse)
reshapeCallback $= Just resizeScene
return ()
render :: DisplayCallback
render = do
clear [ ColorBuffer, DepthBuffer ]
loadIdentity
color $ Color3 (1 :: GLdouble) 1 1
position (Light 0) $= Vertex4 0 50 (50) 1
preservingMatrix $ do
translate $ Vector3 ((-0.5) :: GLfloat) (-0.5) (-5)
color green
ball 12 8 0.03
preservingMatrix $ do
translate $ Vector3 (0.5 :: GLfloat) 0.5 (-5)
color red
renderObject Solid (Sphere' 0.25 20 20)
flush
swapBuffers
where green = Color4 0.8 1.0 0.7 0.9 :: Color4 GLdouble
red = Color4 1.0 0.7 0.8 1.0 :: Color4 GLdouble
vertex3f :: (GLfloat, GLfloat, GLfloat) -> IO ()
vertex3f (x, y, z) = vertex $ Vertex3 x y z
upperInnerCircle :: Int -> [(GLfloat, GLfloat)]
upperInnerCircle numSegs =
concat [[(0,0)
,(cos a, sqrt(1-(cos a)*(cos a)))
,(cos b, sqrt(1-(cos b)*(cos b)))]
| (a,b)<-as ]
where
seg'=pi/(fromIntegral numSegs)
as = [(fromIntegral n * seg', fromIntegral (n+1) * seg') | n<-[0..numSegs-1]]
lowerInnerCircle :: Int -> [(GLfloat, GLfloat)]
lowerInnerCircle numSegs =
map (\(x,y) -> (x,-y)) $ upperInnerCircle numSegs
innerCircle :: Int -> [(GLfloat, GLfloat)]
innerCircle numSegs = upperInnerCircle numSegs ++ (lowerInnerCircle numSegs)
upperOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
upperOutSegment numSegs ring seg =
[x,y,u, u,v,y]
where
seg'=pi/(fromIntegral numSegs)
(a, b) = (fromIntegral seg * seg', fromIntegral (seg+1) * seg')
x = (fromIntegral ring * cos a, fromIntegral ring * sqrt(1-(cos a)*(cos a)))
y = (fromIntegral ring * cos b, fromIntegral ring * sqrt(1-(cos b)*(cos b)))
u = (fromIntegral (ring+1) * cos a, fromIntegral (ring+1) * sqrt(1-(cos a)*(cos a)))
v = (fromIntegral (ring+1) * cos b, fromIntegral (ring+1) * sqrt(1-(cos b)*(cos b)))
lowerOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
lowerOutSegment numSegs ring seg =
map (\(x,y) -> (x,-y)) $ upperOutSegment numSegs ring seg
outSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
outSegment numSegs ring seg = upperOutSegment numSegs ring seg ++ (lowerOutSegment numSegs ring seg)
outerRing :: Int -> Int -> [(GLfloat, GLfloat)]
outerRing numSegs ring =
concat [outSegment numSegs ring n | n<-[0..numSegs-1]]
ball numSegs numRings factor =
let ips = innerCircle numSegs
ops = concat [outerRing numSegs i | i<-[1..numRings]]
height dir ps =
map (\(x,y) ->
let dist = sqrt(x*x+y*y)/(fromIntegral (numRings+1))
height' = sqrt(1.001-dist*dist)*factor*(fromIntegral (numRings+1))
in (x*factor,y*factor,dir*height')) $ ps
ups = height 1 $ ips ++ ops
lps = height (-1) $ ips ++ ops
in renderPrimitive Triangles $ mapM_ vertex3f (ups++lps)
resizeScene :: Size -> IO ()
resizeScene (Size w 0) = resizeScene (Size w 1) -- prevent divide by zero
resizeScene s@(Size width height) = do
viewport $= (Position 0 0, s)
matrixMode $= Projection
loadIdentity
perspective 45 (w2/h2) 1 1000
matrixMode $= Modelview 0
flush
where
w2 = half width
h2 = half height
half z = realToFrac z / 2
编辑:现在可用,感谢 Spektre!
图片如下:
这是代码:
module Main where
import Graphics.UI.GLUT
main :: IO ()
main = do
initGL
displayCallback $= render
mainLoop
initGL :: IO ()
initGL = do
getArgsAndInitialize
initialDisplayMode $= [DoubleBuffered]
createWindow "Chip!"
initialDisplayMode $= [ WithDepthBuffer ]
depthFunc $= Just Less
clearColor $= Color4 0 0 0 0
light (Light 0) $= Enabled
lighting $= Enabled
lightModelAmbient $= Color4 0.5 0.5 0.5 1
diffuse (Light 0) $= Color4 1 1 1 1
blend $= Enabled
blendFunc $= (SrcAlpha, OneMinusSrcAlpha)
colorMaterial $= Just (FrontAndBack, AmbientAndDiffuse)
reshapeCallback $= Just resizeScene
return ()
render :: DisplayCallback
render = do
clear [ ColorBuffer, DepthBuffer ]
loadIdentity
color $ Color3 (1 :: GLdouble) 1 1
position (Light 0) $= Vertex4 0 50 (50) 1
preservingMatrix $ do
translate $ Vector3 ((-0.5) :: GLfloat) (-0.5) (-5)
color green
ball 12 8 0.03
preservingMatrix $ do
translate $ Vector3 (0.5 :: GLfloat) 0.5 (-5)
color red
renderObject Solid (Sphere' 0.25 20 20)
flush
swapBuffers
where green = Color4 0.8 1.0 0.7 0.9 :: Color4 GLdouble
red = Color4 1.0 0.7 0.8 1.0 :: Color4 GLdouble
pushTriangle :: ((GLfloat, GLfloat, GLfloat)
,(GLfloat, GLfloat, GLfloat)
,(GLfloat, GLfloat, GLfloat)) ->
IO ()
pushTriangle (p0, p1, p2) = do
let (_,d0,_)=p0
let (_,d1,_)=p1
let (_,d2,_)=p2
--if it points upwards, reverse normal
let d=if d0+d1+d2>0 then (-1) else 1
let n = cross (minus p1 p0) (minus p2 p1)
let nL = 1/lenVec n
let (n1, n2, n3) = scaleVec n (nL*d)
normal $ Normal3 n1 n2 n3
vertex3f p0
vertex3f p1
vertex3f p2
vertex3f :: (GLfloat, GLfloat, GLfloat) -> IO ()
vertex3f (x, y, z) =
vertex $ Vertex3 x y z
lenVec (a1,a2,a3) = sqrt $ a1*a1 + a2*a2 + a3*a3
scaleVec (a1,a2,a3) x = (a1*x,a2*x,a3*x)
cross (a1,a2,a3) (b1,b2,b3) =
(a2*b3-a3*b2
,a3*b1-a1*b3
,a1*b2-a2*b1)
minus (a1,a2,a3) (b1,b2,b3) =
(a1-b1, a2-b2, a3-b3)
upperInnerCircle :: Int -> [(GLfloat, GLfloat)]
upperInnerCircle numSegs =
concat [[(cos a, sqrt(1-(cos a)*(cos a)))
,(0,0)
,(cos b, sqrt(1-(cos b)*(cos b)))]
| (a,b)<-as ]
where
seg'=pi/(fromIntegral numSegs)
as = [(fromIntegral n * seg', fromIntegral (n+1) * seg') | n<-[0..numSegs-1]]
lowerInnerCircle :: Int -> [(GLfloat, GLfloat)]
lowerInnerCircle numSegs =
map (\(x,y) -> (x,-y)) $ upperInnerCircle numSegs
innerCircle :: Int -> [(GLfloat, GLfloat)]
innerCircle numSegs = upperInnerCircle numSegs ++ (lowerInnerCircle numSegs)
upperOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
upperOutSegment numSegs ring seg =
[x,y,u, v,u,y]
where
seg'=pi/(fromIntegral numSegs)
(a, b) = (fromIntegral seg * seg', fromIntegral (seg+1) * seg')
x = (fromIntegral ring * cos a, fromIntegral ring * sqrt(1-(cos a)*(cos a)))
y = (fromIntegral ring * cos b, fromIntegral ring * sqrt(1-(cos b)*(cos b)))
u = (fromIntegral (ring+1) * cos a, fromIntegral (ring+1) * sqrt(1-(cos a)*(cos a)))
v = (fromIntegral (ring+1) * cos b, fromIntegral (ring+1) * sqrt(1-(cos b)*(cos b)))
lowerOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
lowerOutSegment numSegs ring seg =
map (\(x,y) -> (x,-y)) $ upperOutSegment numSegs ring seg
outSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
outSegment numSegs ring seg = upperOutSegment numSegs ring seg ++ (lowerOutSegment numSegs ring seg)
outerRing :: Int -> Int -> [(GLfloat, GLfloat)]
outerRing numSegs ring =
concat [outSegment numSegs ring n | n<-[0..numSegs-1]]
ball numSegs numRings factor =
let ips = innerCircle numSegs
ops = concat [outerRing numSegs i | i<-[1..numRings]]
height dir ps =
map (\(x,y) ->
let dist = sqrt(x*x+y*y)/(fromIntegral (numRings+1))
height' = sqrt(1.001-dist*dist)*factor*(fromIntegral (numRings+1))
in (x*factor,y*factor,dir*height')) $ ps
ups = height 1 $ ips ++ ops
lps = height (-1) $ ips ++ ops
in renderPrimitive Triangles $ mapM_ pushTriangle (toTriples (ups++lps))
toTriples :: [a] -> [(a,a,a)]
toTriples [] = []
toTriples (a:b:c:rest) = (a,b,c):toTriples rest
resizeScene :: Size -> IO ()
resizeScene (Size w 0) = resizeScene (Size w 1) -- prevent divide by zero
resizeScene s@(Size width height) = do
viewport $= (Position 0 0, s)
matrixMode $= Projection
loadIdentity
perspective 45 (w2/h2) 1 1000
matrixMode $= Modelview 0
flush
where
w2 = half width
h2 = half height
half z = realToFrac z / 2
表面法线对光照方程至关重要
Normal to surface 是垂直于表面的向量。因为三角形是通过其任何 2 个顶点向量的叉积计算的,所以如果三角形点是 p0,p1,p2
,那么法线是 n=cross(p1-p0,p2-p1)
或任何其他组合。
法线告诉 pixel/face/polygon 转动的方向通常与光方向的点积由提供 cos(angle_between light and surface normal)
的渲染引擎计算。这个数字是照射到表面的光量乘以光源强度后得到的光色......
结合表面颜色渲染得到像素颜色有很多光模型这个很简单(正常着色)。
要使点积起作用,法线应该是单位向量,所以将它除以它的长度 n=n/|n|
这里是法线的小例子
对于球体法线很容易法线n
对于任何点p
是n=(p-center)/radius
如果法线与表面不对应
然后你可以做灯光效果,比如在视觉上平滑网格的锐边。例如如何看这里:
- smoothing normals
也可以实现完全相反的效果(平滑的网格但锐边渲染)
OpenGL 界面
旧式 gl 使用类似 glNormal3f(nx,ny,nz);
的东西 VBO/VAO/arrays 也知道法线。在新样式中,glNormal
像大多数参数一样被弃用,因此您需要将其绑定到您自己的自定义布局
法线方向
任何表面都有2个可能的垂直法线方向。通常使用从网格向外指向的那个。有时 3D 曲线是双面的 material,这意味着点积被处理为 abs
值,因此法线指向哪个方向并不重要。没有这个,表面的另一面将永远是黑暗的
因此,如果您有法线并且看不到光照,则尝试否定法线
我正在尝试用 Haskell / GLUT 从一堆三角形中创建一个 3D 球体。它工作得很好:绿色的是 "my" 球体,红色的是用 GLUT 的 renderObject Sphere' 完成的。当我四处移动相机时,我可以看到 "my" 球体是真正的 3D,这很好。
那么为什么 GLUT 的灯光很好,而我的却没有? (我是一个新手,并不知道我在下面的 initGL 中做了什么,从 Hackage 的 cuboid 包中复制了这些东西...)
代码如下:
module Main where
import Graphics.UI.GLUT
main :: IO ()
main = do
initGL
displayCallback $= render
mainLoop
initGL :: IO ()
initGL = do
getArgsAndInitialize
initialDisplayMode $= [DoubleBuffered]
createWindow "Chip!"
initialDisplayMode $= [ WithDepthBuffer ]
depthFunc $= Just Less
clearColor $= Color4 0 0 0 0
light (Light 0) $= Enabled
lighting $= Enabled
lightModelAmbient $= Color4 0.5 0.5 0.5 1
diffuse (Light 0) $= Color4 1 1 1 1
blend $= Enabled
blendFunc $= (SrcAlpha, OneMinusSrcAlpha)
colorMaterial $= Just (FrontAndBack, AmbientAndDiffuse)
reshapeCallback $= Just resizeScene
return ()
render :: DisplayCallback
render = do
clear [ ColorBuffer, DepthBuffer ]
loadIdentity
color $ Color3 (1 :: GLdouble) 1 1
position (Light 0) $= Vertex4 0 50 (50) 1
preservingMatrix $ do
translate $ Vector3 ((-0.5) :: GLfloat) (-0.5) (-5)
color green
ball 12 8 0.03
preservingMatrix $ do
translate $ Vector3 (0.5 :: GLfloat) 0.5 (-5)
color red
renderObject Solid (Sphere' 0.25 20 20)
flush
swapBuffers
where green = Color4 0.8 1.0 0.7 0.9 :: Color4 GLdouble
red = Color4 1.0 0.7 0.8 1.0 :: Color4 GLdouble
vertex3f :: (GLfloat, GLfloat, GLfloat) -> IO ()
vertex3f (x, y, z) = vertex $ Vertex3 x y z
upperInnerCircle :: Int -> [(GLfloat, GLfloat)]
upperInnerCircle numSegs =
concat [[(0,0)
,(cos a, sqrt(1-(cos a)*(cos a)))
,(cos b, sqrt(1-(cos b)*(cos b)))]
| (a,b)<-as ]
where
seg'=pi/(fromIntegral numSegs)
as = [(fromIntegral n * seg', fromIntegral (n+1) * seg') | n<-[0..numSegs-1]]
lowerInnerCircle :: Int -> [(GLfloat, GLfloat)]
lowerInnerCircle numSegs =
map (\(x,y) -> (x,-y)) $ upperInnerCircle numSegs
innerCircle :: Int -> [(GLfloat, GLfloat)]
innerCircle numSegs = upperInnerCircle numSegs ++ (lowerInnerCircle numSegs)
upperOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
upperOutSegment numSegs ring seg =
[x,y,u, u,v,y]
where
seg'=pi/(fromIntegral numSegs)
(a, b) = (fromIntegral seg * seg', fromIntegral (seg+1) * seg')
x = (fromIntegral ring * cos a, fromIntegral ring * sqrt(1-(cos a)*(cos a)))
y = (fromIntegral ring * cos b, fromIntegral ring * sqrt(1-(cos b)*(cos b)))
u = (fromIntegral (ring+1) * cos a, fromIntegral (ring+1) * sqrt(1-(cos a)*(cos a)))
v = (fromIntegral (ring+1) * cos b, fromIntegral (ring+1) * sqrt(1-(cos b)*(cos b)))
lowerOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
lowerOutSegment numSegs ring seg =
map (\(x,y) -> (x,-y)) $ upperOutSegment numSegs ring seg
outSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
outSegment numSegs ring seg = upperOutSegment numSegs ring seg ++ (lowerOutSegment numSegs ring seg)
outerRing :: Int -> Int -> [(GLfloat, GLfloat)]
outerRing numSegs ring =
concat [outSegment numSegs ring n | n<-[0..numSegs-1]]
ball numSegs numRings factor =
let ips = innerCircle numSegs
ops = concat [outerRing numSegs i | i<-[1..numRings]]
height dir ps =
map (\(x,y) ->
let dist = sqrt(x*x+y*y)/(fromIntegral (numRings+1))
height' = sqrt(1.001-dist*dist)*factor*(fromIntegral (numRings+1))
in (x*factor,y*factor,dir*height')) $ ps
ups = height 1 $ ips ++ ops
lps = height (-1) $ ips ++ ops
in renderPrimitive Triangles $ mapM_ vertex3f (ups++lps)
resizeScene :: Size -> IO ()
resizeScene (Size w 0) = resizeScene (Size w 1) -- prevent divide by zero
resizeScene s@(Size width height) = do
viewport $= (Position 0 0, s)
matrixMode $= Projection
loadIdentity
perspective 45 (w2/h2) 1 1000
matrixMode $= Modelview 0
flush
where
w2 = half width
h2 = half height
half z = realToFrac z / 2
编辑:现在可用,感谢 Spektre!
图片如下:
这是代码:
module Main where
import Graphics.UI.GLUT
main :: IO ()
main = do
initGL
displayCallback $= render
mainLoop
initGL :: IO ()
initGL = do
getArgsAndInitialize
initialDisplayMode $= [DoubleBuffered]
createWindow "Chip!"
initialDisplayMode $= [ WithDepthBuffer ]
depthFunc $= Just Less
clearColor $= Color4 0 0 0 0
light (Light 0) $= Enabled
lighting $= Enabled
lightModelAmbient $= Color4 0.5 0.5 0.5 1
diffuse (Light 0) $= Color4 1 1 1 1
blend $= Enabled
blendFunc $= (SrcAlpha, OneMinusSrcAlpha)
colorMaterial $= Just (FrontAndBack, AmbientAndDiffuse)
reshapeCallback $= Just resizeScene
return ()
render :: DisplayCallback
render = do
clear [ ColorBuffer, DepthBuffer ]
loadIdentity
color $ Color3 (1 :: GLdouble) 1 1
position (Light 0) $= Vertex4 0 50 (50) 1
preservingMatrix $ do
translate $ Vector3 ((-0.5) :: GLfloat) (-0.5) (-5)
color green
ball 12 8 0.03
preservingMatrix $ do
translate $ Vector3 (0.5 :: GLfloat) 0.5 (-5)
color red
renderObject Solid (Sphere' 0.25 20 20)
flush
swapBuffers
where green = Color4 0.8 1.0 0.7 0.9 :: Color4 GLdouble
red = Color4 1.0 0.7 0.8 1.0 :: Color4 GLdouble
pushTriangle :: ((GLfloat, GLfloat, GLfloat)
,(GLfloat, GLfloat, GLfloat)
,(GLfloat, GLfloat, GLfloat)) ->
IO ()
pushTriangle (p0, p1, p2) = do
let (_,d0,_)=p0
let (_,d1,_)=p1
let (_,d2,_)=p2
--if it points upwards, reverse normal
let d=if d0+d1+d2>0 then (-1) else 1
let n = cross (minus p1 p0) (minus p2 p1)
let nL = 1/lenVec n
let (n1, n2, n3) = scaleVec n (nL*d)
normal $ Normal3 n1 n2 n3
vertex3f p0
vertex3f p1
vertex3f p2
vertex3f :: (GLfloat, GLfloat, GLfloat) -> IO ()
vertex3f (x, y, z) =
vertex $ Vertex3 x y z
lenVec (a1,a2,a3) = sqrt $ a1*a1 + a2*a2 + a3*a3
scaleVec (a1,a2,a3) x = (a1*x,a2*x,a3*x)
cross (a1,a2,a3) (b1,b2,b3) =
(a2*b3-a3*b2
,a3*b1-a1*b3
,a1*b2-a2*b1)
minus (a1,a2,a3) (b1,b2,b3) =
(a1-b1, a2-b2, a3-b3)
upperInnerCircle :: Int -> [(GLfloat, GLfloat)]
upperInnerCircle numSegs =
concat [[(cos a, sqrt(1-(cos a)*(cos a)))
,(0,0)
,(cos b, sqrt(1-(cos b)*(cos b)))]
| (a,b)<-as ]
where
seg'=pi/(fromIntegral numSegs)
as = [(fromIntegral n * seg', fromIntegral (n+1) * seg') | n<-[0..numSegs-1]]
lowerInnerCircle :: Int -> [(GLfloat, GLfloat)]
lowerInnerCircle numSegs =
map (\(x,y) -> (x,-y)) $ upperInnerCircle numSegs
innerCircle :: Int -> [(GLfloat, GLfloat)]
innerCircle numSegs = upperInnerCircle numSegs ++ (lowerInnerCircle numSegs)
upperOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
upperOutSegment numSegs ring seg =
[x,y,u, v,u,y]
where
seg'=pi/(fromIntegral numSegs)
(a, b) = (fromIntegral seg * seg', fromIntegral (seg+1) * seg')
x = (fromIntegral ring * cos a, fromIntegral ring * sqrt(1-(cos a)*(cos a)))
y = (fromIntegral ring * cos b, fromIntegral ring * sqrt(1-(cos b)*(cos b)))
u = (fromIntegral (ring+1) * cos a, fromIntegral (ring+1) * sqrt(1-(cos a)*(cos a)))
v = (fromIntegral (ring+1) * cos b, fromIntegral (ring+1) * sqrt(1-(cos b)*(cos b)))
lowerOutSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
lowerOutSegment numSegs ring seg =
map (\(x,y) -> (x,-y)) $ upperOutSegment numSegs ring seg
outSegment :: Int -> Int -> Int -> [(GLfloat, GLfloat)]
outSegment numSegs ring seg = upperOutSegment numSegs ring seg ++ (lowerOutSegment numSegs ring seg)
outerRing :: Int -> Int -> [(GLfloat, GLfloat)]
outerRing numSegs ring =
concat [outSegment numSegs ring n | n<-[0..numSegs-1]]
ball numSegs numRings factor =
let ips = innerCircle numSegs
ops = concat [outerRing numSegs i | i<-[1..numRings]]
height dir ps =
map (\(x,y) ->
let dist = sqrt(x*x+y*y)/(fromIntegral (numRings+1))
height' = sqrt(1.001-dist*dist)*factor*(fromIntegral (numRings+1))
in (x*factor,y*factor,dir*height')) $ ps
ups = height 1 $ ips ++ ops
lps = height (-1) $ ips ++ ops
in renderPrimitive Triangles $ mapM_ pushTriangle (toTriples (ups++lps))
toTriples :: [a] -> [(a,a,a)]
toTriples [] = []
toTriples (a:b:c:rest) = (a,b,c):toTriples rest
resizeScene :: Size -> IO ()
resizeScene (Size w 0) = resizeScene (Size w 1) -- prevent divide by zero
resizeScene s@(Size width height) = do
viewport $= (Position 0 0, s)
matrixMode $= Projection
loadIdentity
perspective 45 (w2/h2) 1 1000
matrixMode $= Modelview 0
flush
where
w2 = half width
h2 = half height
half z = realToFrac z / 2
表面法线对光照方程至关重要
Normal to surface 是垂直于表面的向量。因为三角形是通过其任何 2 个顶点向量的叉积计算的,所以如果三角形点是
p0,p1,p2
,那么法线是n=cross(p1-p0,p2-p1)
或任何其他组合。法线告诉 pixel/face/polygon 转动的方向通常与光方向的点积由提供
cos(angle_between light and surface normal)
的渲染引擎计算。这个数字是照射到表面的光量乘以光源强度后得到的光色...... 结合表面颜色渲染得到像素颜色有很多光模型这个很简单(正常着色)。要使点积起作用,法线应该是单位向量,所以将它除以它的长度
n=n/|n|
这里是法线的小例子
对于球体法线很容易法线
n
对于任何点p
是n=(p-center)/radius
如果法线与表面不对应
然后你可以做灯光效果,比如在视觉上平滑网格的锐边。例如如何看这里:
- smoothing normals
也可以实现完全相反的效果(平滑的网格但锐边渲染)
OpenGL 界面
旧式 gl 使用类似
glNormal3f(nx,ny,nz);
的东西 VBO/VAO/arrays 也知道法线。在新样式中,glNormal
像大多数参数一样被弃用,因此您需要将其绑定到您自己的自定义布局法线方向
任何表面都有2个可能的垂直法线方向。通常使用从网格向外指向的那个。有时 3D 曲线是双面的 material,这意味着点积被处理为
abs
值,因此法线指向哪个方向并不重要。没有这个,表面的另一面将永远是黑暗的因此,如果您有法线并且看不到光照,则尝试否定法线