[HOpenGL] Segmentation Fault Running Panitz's Tutorial Code

Scott scottymcdoo at gmail.com
Thu Apr 1 07:54:55 EDT 2010


Hello!

I have a problem when trying to run some code found on this tutorial page:

http://public.beuth-hochschule.de/~panitz/hopengl/skript.html<http://public.beuth-hochschule.de/%7Epanitz/hopengl/skript.html>

The demo is called "LightCube."  The problem seems to have to do with the
following line (which I've commented out in the provided source):

depthFunc $= Just Less

Uncommenting the line gives a Segmentation Fault when I run the executable
generated by:

ghc --make -package GLUT -o LightCube LightCube.hs

Does anyone else have this problem?  Here is the necessary code:
*
LightCube*

import Graphics.Rendering.OpenGL
import Graphics.UI.GLUT  as GLUT

import Cube

main = do
  (progName,_) <-  getArgsAndInitialize

--  depthFunc $= Just Less

  createWindow progName

  lighting $= Enabled
  position (Light 0) $= Vertex4 1 0.4 0.8  1
  light (Light 0) $= Enabled

  displayCallback $= display
  mainLoop

display = do
  clear [ColorBuffer]
  rotate 40 (Vector3 1 1 (1::GLfloat))
  cube 0.5
  loadIdentity
  flush
*
Cube
*
module Cube where

import Graphics.Rendering.OpenGL
import Graphics.UI.GLUT  as GLUT

import PointsForRendering

cube l = renderAs Quads corners
  where
   corners =
    [(l,0,l),(0,0,l),(0,l,l),(l,l,l)
    ,(l,l,l),(l,l,0),(l,0,0),(l,0,l)
    ,(0,0,0),(l,0,0),(l,0,l),(0,0,l)
    ,(l,l,0),(0,l,0),(0,0,0),(l,0,0)
    ,(0,l,l),(l,l,l),(l,l,0),(0,l,0)
    ,(0,l,l),(0,l,0),(0,0,0),(0,0,l)
    ]
*
PointsForRendering*

module PointsForRendering where
import Graphics.UI.GLUT
import Graphics.Rendering.OpenGL

renderInWindow displayFunction = do
  (progName,_) <-  getArgsAndInitialize
  createWindow progName
  displayCallback $= displayFunction
  mainLoop

displayPoints points primitiveShape = do
  renderAs primitiveShape points
  flush

renderAs figure ps = renderPrimitive figure$makeVertexes ps

makeVertexes = mapM_ (\(x,y,z)->vertex$Vertex3 x y z)

mainFor primitiveShape
 = renderInWindow (displayMyPoints primitiveShape)

displayMyPoints primitiveShape = do
  clear [ColorBuffer]
  currentColor $= Color4 1 1 0 1
  displayPoints myPoints primitiveShape

myPoints
 = [(0.2,-0.4,0::GLfloat)
   ,(0.46,-0.26,0)
   ,(0.6,0,0)
   ,(0.6,0.2,0)
   ,(0.46,0.46,0)
   ,(0.2,0.6,0)
   ,(0.0,0.6,0)
   ,(-0.26,0.46,0)
   ,(-0.4,0.2,0)
   ,(-0.4,0,0)
   ,(-0.26,-0.26,0)
   ,(0,-0.4,0)
   ]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/hopengl/attachments/20100401/eb430c8e/attachment-0001.html


More information about the HOpenGL mailing list