[Haskell-cafe] FunPtr error?

Galchin, Vasili vigalchin at gmail.com
Mon Jun 9 23:54:20 EDT 2008


Ryan,

     I tried but the compiler didn't seem to like the keyword "import":

vigalchin at ubuntu:~/FTP/Haskell/unix-2.2.0.0/tests/timer$ runhaskell
Setup.lhs build
Preprocessing executables for Test-1.0...
Building Test-1.0...
[1 of 1] Compiling Main             ( ./timer.hs,
dist/build/timer/timer-tmp/Main.o )

./timer.hs:29:8: parse error on input `import'


.... source ...:

module Main where

import System.Posix
import Foreign
import Foreign.C
import Foreign.Ptr

type Notify = Sigval -> IO ()

main = do

         notifyFPtr <- mkNotify notifyFunc

         let event = Sigevent{sigevFunction=notifyFPtr}

         timerId <- timerCreate Clock_Realtime Nothing

         timerDelete timerId

         return ()

notifyFunc :: Sigval -> IO ()
notifyFunc sigval = do
   putStrLn "timer POP!!!!!!!"
   return ()


foreign import ccall "wrapper"
   mkNotify :: Notify -> IO (FunPtr Notify)
~

Everything looks ok to me. ??

Regards, Vasili

On Mon, Jun 9, 2008 at 2:16 PM, Ryan Ingram <ryani.spam at gmail.com> wrote:

> > type Notify = Sigval -> IO ()
> > foreign import ccall "wrapper" mkNotify :: Notify -> IO (FunPtr Notify)
>
> then
> > main = do
> >    notifyFPtr <- mkNotify notifyFunc
> >    -- rest of code here
> >
> >    -- then, when you are done and nothing is referencing the pointer any
> more
> >    freeHaskellFunPtr notifyFPtr
>
> On 6/9/08, Galchin, Vasili <vigalchin at gmail.com> wrote:
> > In any case, what I want to do is store FunPtr in  a data type and
> marshall
> > into a C struct as a C function pointer.
> >
> > Vasili
>
> This will be suitable for that purpose.
>
>  -- ryan
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080609/a2ac483c/attachment.htm


More information about the Haskell-Cafe mailing list