[jhc] ffi: context reduction, no instance for: Jhc.Class.Real.Fractional Jhc.Type.C.CDouble

Nawal Husnoo nawal at husnoo.com
Sat Sep 23 10:11:48 UTC 2017


Hi,

I can't get the FFI to work as advertised - any ideas?

Thanks,

Nawal.


Tutorial from here:
http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html

$ cat fore.hs
{-# LANGUAGE ForeignFunctionInterface #-}

import Prelude

import Foreign
import Foreign.C.Types

foreign import ccall "math.h sin"
     c_sin :: CDouble -> CDouble

fastsin :: Double -> Double
fastsin x = realToFrac (c_sin (realToFrac x))


main = print (fastsin 0.5)

$ jhc -phaskell2010 fore.hs -o bin/fore
jhc -phaskell2010 fore.hs -o bin/fore
jhc 0.8.2 (mydniquipepo-32)
Finding Dependencies...
Using Ho Cache: '/home/nawal/.jhc/cache'
Main                    [fore.hs]
Typechecking...
[1 of 1] Main             (......................jhc: user error (
What:    failure
Why:     context reduction, no instance for: Jhc.Class.Real.Fractional
Jhc.Type.C.CDouble
Where:   on line 12 in fore.hs
in the explicitly typed Main.fastsin Main.1_x
  = Jhc.Num.realToFrac (Main.c_sin (Jhc.Num.realToFrac Main.1_x))
    {- on line 12 -}
Compilation of module: Main)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/jhc/attachments/20170923/f704ee50/attachment.html>


More information about the jhc mailing list