{-# 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 C code in WinDll -- ----------------------------------------------------------------------------- module WinDll.Structs.C where import qualified Language.Haskell.Exts as Exts import qualified Language.Haskell.Exts.SrcLoc as Span import Data.Data import WinDll.Structs.Structures import WinDll.Session.Hs2lib (CallConvention) -- | This structure hold include information of which files to include data Include = LibInclude Name -- ^ @LibInclude@ These are includes to be included from a standard location | LocalInclude Name -- ^ @LocalInclude@ These includes are to be included from a local path deriving (Eq,Show,Data,Typeable) -- | This structure hold the enum information which represent the data constructors that are need to be exported -- This is because the following structures: -- -- data Foo = Foo -- | Bar -- -- will create a a union containing 2 structs Foo and Bar, but we need to know which one -- of the constructors was used, and for that we use the enum. -- -- enum FooSelector {cFooFoo, cFooBar} data DataEnum = DataEnum Name [String] -- ^ @DataEnum@ The information here denotes the enum name the enum elements. deriving (Eq,Show,Data,Typeable) -- | This type determines whether the DataField is a Struct or Union. data CDataType = Struct -- ^ @Struct@ A C Struct | Union -- ^ @Union@ A C Union | ENum -- ^ @Enum@ A C Enum | VAlue -- ^@Value@ A normal C value deriving (Eq,Show,Data,Typeable) -- | Determines whether the FieldValue to be printed is of a normal or a Pointer type data FieldType = Normal -- ^ @Normal@ A normal C value | Pointer -- ^ @Pointer@ A C pointer reference deriving (Eq,Show,Data,Typeable) -- | Determines whether the DataField to be printed is of a normal or a typedef type data DataFieldType = TypeDef -- ^ @TypeDef@ A typedef C value | NormalDef -- ^ @NormalDef@ A C normal value deriving (Eq,Show,Data,Typeable) -- | This type holds both structs and unions as they have the same general outline, just different names. -- It's a good idea to keep them in one structure as to make the depencency graph tracing easier later on. data DataField = Field DataFieldType CDataType Name TypeName [DataField] -- ^ @Field@ This decribes which instance to created | Value CDataType TypeName FieldType (Maybe Name) -- ^ @Value@ This describes the elements of the Field above. | Forward CDataType Name -- ^ @Forward@ Forward references. -- Though you could use it to make nested structures, This is not used -- Inside WinDll. deriving (Eq,Show,Data,Typeable) -- | This is the head structure to hold and describe the entire C file to be generated. Generating the instances from -- This type should be rather easy. data C = C { c_includes :: [Include] -- ^ @Includes@ The includes to be generated in the file , c_callconv :: CallConvention -- ^ The calling convention used for the file , c_callbacks :: [Callback] -- ^ @callbacks@ The list of C callback functions to generate , c_enums :: [DataEnum] -- ^ @Enums@ The file enums in the c file , c_forwards :: [DataField] -- ^ The forward references needed in the c file , c_fields :: [DataField] -- ^ The Actual fields in the C file. } deriving (Eq,Show,Data,Typeable)