[Haskell-cafe] greencard and cabal, how to do it right?

Marc Weber marco-oweber at gmx.de
Sun Dec 17 21:20:36 EST 2006


Anyway, how to set  the options using cabal ?
the preprocessor is there so there must be a working way without my
modifications I don't know about.
> And Greencard.hs isn't just empty?

No, Greencard.*gc* looks like:
--------------------------------------------
module Main where
import Test.QuickCheck

%#include c_lib.h
%fun add_int :: Int -> Int -> Int
%call (arg1) (arg2)
%result (res1)

main = do
  print "greencard"
  quickCheck $ (\a b -> (a+b) == add_int a b)
-------------------------------------------

which results in Greencard.hs when invoking the line from the shell:
Greencard.*hs*
---------------------------------------------

module Main where
import Test.QuickCheck

add_int :: Int -> Int -> Int
add_int arg1 arg2 =
  unsafePerformIO(
    prim_add_int)
foreign import  ccall unsafe "Greencard_stub_ffi.h prim_add_int" prim_add_int :: IO ()

main = do
  print "greencard"
  quickCheck $ (\a b -> (a+b) == add_int a b)
---------------------------------------------

Marc


More information about the Haskell-Cafe mailing list