{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeSynonymInstances #-} ----------------------------------------------------------------------------- -- | -- Module : Windll -- Copyright : (c) Tamar Christina 2009 - 2010 -- License : BSD3 -- -- Maintainer : tamar@zhox.com -- Stability : experimental -- Portability : portable -- -- Structures used when generating CSharp code in WinDll -- ----------------------------------------------------------------------------- module WinDll.Structs.CSharp where import qualified Language.Haskell.Exts as Exts import qualified Language.Haskell.Exts.SrcLoc as Span import Data.Data import WinDll.Session.Hs2lib import WinDll.Structs.Structures import WinDll.Structs.Types import WinDll.Structs.C import WinDll.Structs.MShow.C import WinDll.Structs.Folds.C type Key = String type Value = String type Values = [Value] type Comment = String type CsType = String -- | Datatype to hold the attributes for the generated C\# types -- The boolean indicates whether the Attribute is a parameter -- attribute. data Attr = Attr AttrType Key Values deriving(Eq,Data,Typeable) -- | The type of the attribute annotation -- normal means no annotation -- param means 'param: ' -- return means 'return: ' data AttrType = Normal | Param | Return deriving(Eq,Data,Typeable) -- | The type of an argument of a function data Argument = Argument [Attr] CsType Name deriving(Eq,Data,Typeable) -- | Module export declarations. data CsExport = CsExport { cseComments :: [Comment] , cseTopAttr :: [Attr] , cseName :: Name , cseRetType :: CsType , cseArguments :: [Argument] } deriving(Eq,Data,Typeable) -- | The type of the struct. Determins how it's printed. data CsStructType = CsTUnion | CsTStruct deriving(Eq,Data,Typeable) -- | Newtype wrapper for the C# include newtype CsInclude = CsInclude { csUnpackInclude :: Include } deriving(Eq,Data,Typeable) -- | Newtype wrapper for the C# Callbacks data CsCallback = CsCallback { cscName :: Name , cscTopAttr :: [Attr] , cscRetType :: CsType , cscArguments :: [Argument] } deriving(Eq,Data,Typeable) -- | Newtype wrapper for the C# include newtype CsDataEnum = CsDataEnum { csUnpackEnum :: DataEnum } deriving(Eq,Data,Typeable) -- | Declaration for a C# struct data CsStruct = CsStruct { cssType :: CsStructType , cssTopAttr :: [Attr] , cssName :: Name , cssElements :: [Argument] } deriving(Eq,Data,Typeable) -- | The main C# file data CSharp = CSharp { _header :: String , _namespace :: String , _class :: String , _callconv :: CallConvention , _callbacks :: [CsCallback] , _includes :: [CsInclude] , _typeDecls :: [TypeDecL] , _functions :: [CsExport] , _preserved :: [CsExport] , _rtscontrol :: [CsExport] , _structs :: [CsStruct] , _enums :: [CsDataEnum] } deriving(Eq,Data,Typeable)