理解OpenGL中的光照

5
我正在尝试使用Haskell / GLUT从一堆三角形中创建3D球体。它工作得非常好:绿色的是“我的”球体,红色的是使用GLUT的renderObject Sphere'创建的。当我移动相机时,可以看到“我的”球体确实是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

6
你没有提供任何表面法线。 - derhass
1
@derhass 我猜他也不知道那是什么意思。 - Cubic
1
猜对了,但我还是要去谷歌一下。谢谢。 - martingw
1
@martingw添加了答案,尽我所能地解释法线,希望能有所帮助。 - Spektre
1个回答

4
  1. 面法线对于光照方程至关重要

    表面法线是垂直于表面的向量。 对于三角形,可以通过任意两个顶点向量的叉积来计算其法向量,因此如果三角形的指针为p0,p1,p2,则法向量为n = cross(p1-p0,p2-p1) 或者其他组合。

    法线通常告诉我们像素/面/多边形朝向哪个方向,通常会在渲染引擎中计算与光线方向的点积,这会给出一个cos(光线和表面法线之间的夹角)。当乘以光源强度时,此数字是击中表面的光线数量的比例,与表面颜色的组合一起,渲染获得像素颜色。有许多光模型,这种模型是非常简单的(法线着色)。

    为使点积有效,法线应为单位向量,因此需要将其除以其长度n=n/|n|

    以下是法线的小例子

    example

    对于球体,法线很容易计算任何点p的法向量nn=(p-center)/radius

  2. 如果法线与表面不对应

    那么您可以执行光效果,例如在网格上视觉平滑锐边。 例如看这里:

    也可以实现完全相反的效果(平滑网格但是锐边呈现)

  3. OpenGL接口

    旧式gl使用类似于glNormal3f(nx,ny,nz);的东西。 VBO / VAO /数组也了解法线。 在新样式中,glNormal像大多数参数一样被弃用,因此您需要自己将其绑定到自定义布局。

  4. 法线方向

    任何表面都有沿垂直法线的两个可能方向。 通常使用指向网格外部的法线方向。 有时会使用双面材料的3D曲线,这意味着点积被处理为abs值,因此法线指向哪个方向并不重要。否则,表面的反面将始终很暗。

    因此,如果您拥有法线并且看不到照明,则请尝试否定法线


网页内容由stack overflow 提供, 点击上面的
可以查看英文原文,
原文链接