FFI.hsc

Plain text version of FFI.hsc

{-# LANGUAGE ForeignFunctionInterface, MagicHash, BangPatterns #-}

module PGF2.FFI where

#include <gu/defs.h>
#include <gu/hash.h>
#include <gu/utf8.h>
#include <pgf/pgf.h>
#include <pgf/data.h>

import Foreign ( alloca, peek, poke, peekByteOff )
import Foreign.C
import Foreign.Ptr
import Foreign.ForeignPtr
import Control.Exception
import GHC.Ptr
import Data.Int
import Data.Word

type Touch = IO ()

-- | An abstract data type representing multilingual grammar
-- in Portable Grammar Format.
data PGF = PGF {pgf :: Ptr PgfPGF, touchPGF :: Touch}
data Concr = Concr {concr :: Ptr PgfConcr, touchConcr :: Touch}

------------------------------------------------------------------
-- libgu API

data GuEnum
data GuExn
data GuIn
data GuOut
data GuKind
data GuType
data GuString
data GuStringBuf
data GuMap
data GuMapItor
data GuHasher
data GuSeq
data GuBuf
data GuPool
type GuVariant = Ptr ()
type GuHash = (#type GuHash)
type GuUCS = (#type GuUCS)

type CSizeT = (#type size_t)
type CUInt8 = (#type uint8_t)

foreign import ccall unsafe fopen :: CString -> CString -> IO (Ptr ())

foreign import ccall unsafe "gu/mem.h gu_new_pool"
  gu_new_pool :: IO (Ptr GuPool)

foreign import ccall unsafe "gu/mem.h gu_malloc"
  gu_malloc :: Ptr GuPool -> CSizeT -> IO (Ptr a)

foreign import ccall unsafe "gu/mem.h gu_malloc_aligned"
  gu_malloc_aligned :: Ptr GuPool -> CSizeT -> CSizeT -> IO (Ptr a)

foreign import ccall unsafe "gu/mem.h gu_pool_free"
  gu_pool_free :: Ptr GuPool -> IO ()

foreign import ccall unsafe "gu/mem.h &gu_pool_free"
  gu_pool_finalizer :: FinalizerPtr GuPool

foreign import ccall unsafe "gu/exn.h gu_new_exn"
  gu_new_exn :: Ptr GuPool -> IO (Ptr GuExn)

foreign import ccall unsafe "gu/exn.h gu_exn_is_raised"
  gu_exn_is_raised :: Ptr GuExn -> IO Bool

foreign import ccall unsafe "gu/exn.h gu_exn_caught_"
  gu_exn_caught :: Ptr GuExn -> CString -> IO Bool

foreign import ccall unsafe "gu/exn.h gu_exn_raise_"
  gu_exn_raise :: Ptr GuExn -> CString -> IO (Ptr ())

gu_exn_type_GuErrno = Ptr "GuErrno"## :: CString

gu_exn_type_GuEOF = Ptr "GuEOF"## :: CString

gu_exn_type_PgfLinNonExist = Ptr "PgfLinNonExist"## :: CString

gu_exn_type_PgfExn = Ptr "PgfExn"## :: CString

gu_exn_type_PgfParseError = Ptr "PgfParseError"## :: CString

gu_exn_type_PgfTypeError = Ptr "PgfTypeError"## :: CString

foreign import ccall unsafe "gu/string.h gu_string_in"
  gu_string_in :: CString -> Ptr GuPool -> IO (Ptr GuIn)

foreign import ccall unsafe "gu/string.h gu_new_string_buf"
  gu_new_string_buf :: Ptr GuPool -> IO (Ptr GuStringBuf)

foreign import ccall unsafe "gu/string.h gu_string_buf_out"
  gu_string_buf_out :: Ptr GuStringBuf -> IO (Ptr GuOut)

foreign import ccall unsafe "gu/file.h gu_file_in"
  gu_file_in :: Ptr () -> Ptr GuPool -> IO (Ptr GuIn)

foreign import ccall safe  "gu/enum.h gu_enum_next"
  gu_enum_next :: Ptr a -> Ptr (Ptr b) -> Ptr GuPool -> IO ()

foreign import ccall unsafe "gu/string.h gu_string_buf_freeze"
  gu_string_buf_freeze :: Ptr GuStringBuf -> Ptr GuPool -> IO CString

foreign import ccall unsafe "gu/utf8.h gu_utf8_decode"
  gu_utf8_decode :: Ptr CString -> IO GuUCS

foreign import ccall unsafe "gu/utf8.h gu_utf8_encode"
  gu_utf8_encode :: GuUCS -> Ptr CString -> IO ()

foreign import ccall unsafe "gu/seq.h gu_make_seq"
  gu_make_seq :: CSizeT -> CSizeT -> Ptr GuPool -> IO (Ptr GuSeq)

foreign import ccall unsafe "gu/seq.h gu_make_buf"
  gu_make_buf :: CSizeT -> Ptr GuPool -> IO (Ptr GuBuf)

foreign import ccall unsafe "gu/map.h gu_make_map"
  gu_make_map :: CSizeT -> Ptr GuHasher -> CSizeT -> Ptr a ->