{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : Windll -- Copyright : (c) Tamar Christina 2009 - 2010 -- License : BSD3 -- -- Maintainer : tamar@zhox.com -- Stability : experimental -- Portability : portable -- -- This module contains the lookup values to do type conversions. -- These lists are the basic, build-in predefined lists. -- ----------------------------------------------------------------------------- module WinDll.Lib.Native where type Defs = [(String, String)] -- | List containing mapping to C/C++ Types nativeLisths2c :: [(String , String )] nativeLisths2c = [("String" , "wchar_t*" ) ,("Int" , "int" ) ,("Int8" , "int8_t" ) ,("Int16" , "int16_t" ) ,("Int32" , "int32_t" ) ,("Int64" , "int64_t" ) ,("Word8" , "uint8_t" ) ,("Word16" , "uint16_t" ) ,("Word32" , "uint32_t" ) ,("Word64" , "uint64_t" ) ,("Float" , "float" ) ,("Double" , "double" ) ,("CDouble" , "double" ) ,("CWString" , "wchar_t*" ) ,("CInt" , "int" ) ,("Bool" , "int8_t" ) ,("FastString" , "wchar_t*" ) ,("FastInt" , "int" ) ,("Char" , "wchar_t" ) ,("CWchar" , "wchar_t" ) ,("CChar" , "char" ) ,("Integer" , "long long int" ) ,("Rational" , "long long int" ) ,("StablePtr" , "void*" ) ,("()" , "void" )] -- | Contains a list of mapping types. -- This is the first list to be extended by the pragmas -- We need to preserve the Haskell type name for later -- transformations and for FFI nativeConvList :: [(String,String)] nativeConvList = [("String" ,"CWString" ) ,("Int" ,"CInt" ) ,("Bool" ,"Int8" ) ,("Float" ,"CFloat" ) ,("FastString" ,"CWString" ) ,("CWString" ,"CWString" ) ,("CDouble" ,"CDouble" ) ,("CInt" ,"CInt" ) ,("CIntPtr" ,"CIntPtr" ) ,("CWchar" ,"CWchar" ) ,("CLLong" ,"CLLong" ) ,("FastInt" ,"CInt" ) ,("Double" ,"Double" ) ,("Char" ,"CWchar" ) ,("Integer" ,"CLLong" ) ,("Rational" ,"CDouble" ) ,("IO" ,"IO" ) ,("()" ,"()" ) ,("StablePtr" ,"StablePtr" ) ,("Ptr" ,"Ptr" ) ,("FunPtr" ,"FunPtr" )] -- | List of type conversion from C/C++ to C# types nativeC2cslist :: [(String , String )] nativeC2cslist = [("wchar_t*" , "char*" ) ,("int" , "int" ) ,("int8_t" , "SByte" ) ,("int16_t" , "Int16" ) ,("int32_t" , "Int32" ) ,("int64_t" , "Int64" ) ,("uint8_t" , "Byte" ) ,("uint16_t" , "UInt16" ) ,("uint32_t" , "UInt32" ) ,("uint64_t" , "UInt64" ) ,("float" , "float" ) ,("double" , "double" ) ,("wchar_t" , "char" ) ,("void*" , "void*" ) ,("void" , "void" ) ,("long long int" , "long" )] -- | List containing mapping to C# Types nativeCslist :: Bool -> [(String , String )] nativeCslist struct = [("String" , str ) ,("Int" , "int" ) ,("Int8" , "SByte" ) ,("Int16" , "Int16" ) ,("Int32" , "Int32" ) ,("Int64" , "Int64" ) ,("Word8" , "Byte" ) ,("Word16" , "UInt16" ) ,("Word32" , "UInt32" ) ,("Word64" , "UInt64" ) ,("Float" , "float" ) ,("Double" , "double" ) ,("CDouble" , "double" ) ,("CWString" , str ) ,("CInt" , "int" ) ,("Bool" , "bool" ) ,("FastString" , str ) ,("FastInt" , "int" ) ,("Char" , "char" ) ,("CWchar" , "Char" ) ,("CChar" , "char" ) ,("Integer" , "long" ) ,("Rational" , "long" ) ,("StablePtr" , "IntPtr" ) ,("IntPtr" , "IntPtr" ) ,("()" , "void" )] where str = if struct then "char*" else "StringBuilder" #if i386_HOST_ARCH -- | List containing mapping to CSizes nativeC_sizes ::[(String , Int)] nativeC_sizes = [("*" , 4) ,("wchar_t" , 2) ,("int" , 4) ,("int8_t" , 1) ,("int16_t" , 2) ,("int32_t" , 4) ,("int64_t" , 8) ,("uint8_t" , 1) ,("uint16_t" , 2) ,("wchar_t" , 4) ,("uint32_t" , 8) ,("float" , 4) ,("double" , 8) ,("char" , 1) ,("long long int" , 8) ,("void" , 0) ] defaultPointerSize :: Int defaultPointerSize = 4 #else -- | List containing mapping to CSizes nativeC_sizes ::[(String , Int)] nativeC_sizes = [("*" , 8) ,("wchar_t" , 2) ,("int" , 8) ,("int8_t" , 1) ,("int16_t" , 2) ,("int32_t" , 4) ,("int64_t" , 8) ,("uint8_t" , 1) ,("uint16_t" , 2) ,("wchar_t" , 4) ,("uint32_t" , 8) ,("float" , 4) ,("double" , 8) ,("char" , 1) ,("long long int" , 8) ,("void" , 0) ] defaultPointerSize :: Int defaultPointerSize = 8 #endif