1

I create simple haskell-opengl project. It is build successful using commands:

cabal configure
cabal build

When I use stack:

stack build

I get error:

GLUT-2.7.0.1: configure
Progress
    Configuring GLUT-2.7.0.1...
    Setup.hs: Missing dependency on a foreign library:
    * Missing C library: glut32
    This problem can usually be solved by installing the system package that
    provides this library (you may need the "-dev" version). If the library is
    already installed but in a non-standard location then you can use the flags
    --extra-include-dirs= and --extra-lib-dirs= to specify where it is.

How to make use stack glut.dll?

module Main where

import Graphics.UI.GLUT
import Foreign.Marshal.Array
import Foreign.Ptr
import Foreign.Storable()
import Foreign.C.Types()
import qualified Data.ByteString as BS
import Control.Monad

data State = State
    {
        vertexBuffer :: BufferObject,
        gpuProgram :: Program
    }

triangleVertexes :: [GLfloat]
triangleVertexes = [
     0.0,  0.5,   0.0, 1.0,
     0.5, -0.366, 0.0, 1.0,
    -0.5, -0.366, 0.0, 1.0,
     1.0,  0.0,   0.0, 1.0,
     0.0,  1.0,   0.0, 1.0,
     0.0,  0.0,   1.0, 1.0
    ]

main :: IO ()
main = do
   (progName, _) <- getArgsAndInitialize
   initialDisplayMode $= [ DoubleBuffered, RGBAMode, WithAlphaComponent, WithDepthBuffer ]
   _ <- createWindow progName
   state <- initializeState
   displayCallback $= display state
   reshapeCallback $= Just (reshape state)
   mainLoop

fragmentShaderFilePath :: FilePath
fragmentShaderFilePath = "shader.frag"

vertexShaderFilePath :: FilePath
vertexShaderFilePath = "shader.vert"

createVertexBuffer :: [GLfloat] -> IO BufferObject
createVertexBuffer vertexes = do
    bufferObject <- genObjectName
    bindBuffer ArrayBuffer $= Just bufferObject
    withArrayLen vertexes $ \count arr ->
        bufferData ArrayBuffer $= (fromIntegral count * 4, arr, StaticDraw)
    enableAttribLocations [0, 1]
    setAttribPointers
    return bufferObject

vertexNumComponents :: NumComponents
vertexNumComponents = 4

colorNumComponents :: NumComponents
colorNumComponents = 4

initializeState :: IO State
initializeState = do
    bufferObject <- createVertexBuffer triangleVertexes
    program <- initGPUProgram
    return State
        {
            vertexBuffer = bufferObject,
            gpuProgram = program
        }

loadShader :: ShaderType -> FilePath -> IO Shader
loadShader t path = do
    shader <- createShader t
    source <- BS.readFile path
    shaderSourceBS shader $= source
    compileShader shader
    status <- get (compileStatus shader)
    unless status $ putStrLn . (("message" ++ " log: ") ++) =<< get (shaderInfoLog shader)
    return shader

initGPUProgram :: IO Program
initGPUProgram = do
    vertexShader <- loadShader VertexShader vertexShaderFilePath
    fragmentShader <- loadShader FragmentShader fragmentShaderFilePath
    let shaders = [vertexShader, fragmentShader]
    program <- createProgram
    mapM_ (attachShader program) shaders
    linkProgram program
    mapM_ (detachShader program) shaders
    return program

display :: State -> DisplayCallback
display state = do
    clearColor $= Color4 1.0 0.0 1.0 1.0
    clear [ ColorBuffer ]
    bindBuffer ArrayBuffer $= Just (vertexBuffer state)
    enableAttribLocations [0, 1]
    setAttribPointers
    currentProgram $= Just (gpuProgram state)
    drawArrays Triangles 0 3
    disableAttribLocations [0, 1]
    swapBuffers
    checkError "display"

setCapabilityForAttribLocations :: Capability -> [GLuint] -> IO ()
setCapabilityForAttribLocations capability =
    mapM_ (\location -> vertexAttribArray (AttribLocation location) $= capability)

disableAttribLocations :: [GLuint] -> IO ()
disableAttribLocations = setCapabilityForAttribLocations Disabled

enableAttribLocations :: [GLuint] -> IO ()
enableAttribLocations = setCapabilityForAttribLocations Enabled

setAttribPointers :: IO ()
setAttribPointers = do
    vertexAttribPointer (AttribLocation 0) $= (ToFloat, VertexArrayDescriptor vertexNumComponents Float 0 nullPtr)
    vertexAttribPointer (AttribLocation 1) $= (ToFloat, VertexArrayDescriptor colorNumComponents Float 0 (plusPtr nullPtr 48))

reshape :: State -> ReshapeCallback
reshape _ size =
     viewport $= (Position 0 0, size)

checkError :: String -> IO ()
checkError functionName = get errors >>= mapM_ reportError
    where reportError e = putStrLn (showError e ++ " detected in " ++ functionName)
          showError (Error category message) = "GL error " ++ show category ++ " (" ++ message ++ ")"

-- fragment shader

#version 330

smooth in vec4 theColor;

out vec4 outputColor;

void main()
{
    outputColor = theColor;
}

-- vertex shader

 #version 330

layout (location = 0) in vec4 position;
layout (location = 1) in vec4 color;

smooth out vec4 theColor;

void main()
{
    gl_Position = position + vec4(0.5, 0.5, 0.0, 1.0);
    theColor = color;
}
ErikR
  • 51,541
  • 9
  • 73
  • 124
Bet
  • 389
  • 4
  • 13
  • Can you provide more information like (1) OS/architecture running on, (2) output for `stack --version` and `stack exec -- ghc --version`, `ghc --version`, and `cabal --version`? – Michael Snoyman Aug 15 '15 at 18:37
  • stack --version: Version 0.1.2.0, Git revision 65246552936b7da4b64b38372feac903d96a8911 – Bet Aug 16 '15 at 11:40
  • stack exec -- ghc --version : Version 0.1.2.0, Git revision 65246552936b7da4b64b38372feac903d96a8911 – Bet Aug 16 '15 at 11:41
  • ghc --version: The Glorious Glasgow Haskell Compilation System, version 7.8.3 – Bet Aug 16 '15 at 11:42
  • cabal --version : cabal-install version 1.18.0.5 using version 1.18.1.3 of the Cabal library – Bet Aug 16 '15 at 11:42
  • This is probably going to become too difficult to debug in an SO question. Please open up a Github issue for this, and include a reproducing case. Also, please rerun `stack exec -- ghc --version`, the output given above does not have the version of GHC in it. – Michael Snoyman Aug 16 '15 at 12:41
  • 1
    Create Issue on Github: https://github.com/commercialhaskell/stack/issues/819 – Bet Aug 18 '15 at 21:29
  • Thanks, will follow up there – Michael Snoyman Aug 19 '15 at 03:26
  • Another possible resolution might be https://stackoverflow.com/a/41588628/562583 – Turion Sep 27 '18 at 09:42
  • With latest stack version it isn't actual. – Bet Sep 29 '18 at 09:44

0 Answers0