{-# 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 Haskell code in WinDll -- ----------------------------------------------------------------------------- module WinDll.Structs.Haskell (module WinDll.Structs.Haskell ,S.HaskellExport(..) ,S.HaskellImport(..)) where import qualified Language.Haskell.Exts as Exts import qualified Language.Haskell.Exts.SrcLoc as Span import Data.Data import WinDll.Structs.Structures hiding (Import) import WinDll.Structs.C import WinDll.Session.Hs2lib import qualified WinDll.Session.Hs2lib as S type Field = String type PtrName = String -- | Global Comments added to the top of the module data HaskellComment = HaskellComment String deriving(Eq,Show,Data,Typeable) -- | The type of pragma to use data PragmaType = GHC_OPTION | LANGUAGE deriving(Eq,Show,Data,Typeable) -- | GHC Pragmas to insert into the generated file data GHCPragma = Pragma PragmaType String deriving(Eq,Show,Data,Typeable) -- | Haskell Import statements data Import = Import String deriving(Eq,Show,Data,Typeable) -- | An hsc Let statement data HSC_Let = HSC_Let String deriving(Eq,Show,Data,Typeable) -- | Type declarations to pointers type Ptr_Type = TypeDecL -- | A Haskell function export data HaskellFunction = HaskellFunction { hfnName :: Name -- ^ @hfnName@ Original function name , hfnAs :: Name -- ^ @hfnAs@ re-exported function name/alias , hfnType :: Type -- ^ @hfnType@ The working function type , hfnAnn :: Ann -- ^ @hfnAnn@ Annotations associated with the @hfnType@ , hfnOrigType :: Type -- ^ @hfnOrigType@ The original (largely) unmodified type } deriving(Eq,Show,Data,Typeable) -- | Simple type alias for \Callback\ type HaskellCallback = Callback -- | A datatype to hold all Storable instance definitions (Both normal and specializations) data HaskellStorable = HSStorable { hsname :: Name -- ^ @hsname@ Name of the storable instance , hsizes :: [(Name,Int)] -- ^ @hssizes@ A mapping from Constructors to arity to generate correct sizes , hsptr :: PtrName -- ^ @hsptr@ The base pointer name to use in this instance , hsvars :: [TypeName] -- ^ @hsvars@ The full type arity of the datatype , hsspec :: Bool -- ^ @hsspec@ Whether the instance is a specialized instance or not. If it is FFIType should not be used and the types not escaped. , pokes :: [HaskellStorable] -- ^ @pokes@ The pokes to be outputted by the program , peeks :: [HaskellStorable] -- ^ @peeks@ The peeks to be generated by the program , hsann :: Ann -- ^ @hsann@ The buffer containing the proper lookup annotations for translate } | HSPoke { pokename :: Name -- ^ @pokename@ The name of the Constructor we're generating instances for , pokeModule :: ModuleName -- ^ @pokeModule@ The name of the module exporting the constructor , pokearrity :: Int -- ^ @pokearrity@ The arrity of the current constructor , pokebody :: [StorablePoke] -- ^ @pokebody@ The body of the poke } | HSPeek { peekbody :: [StorablePeek] -- ^ @peekbody@ The complete peek body } deriving(Eq,Show,Data,Typeable) -- | Structure to describe the Peek values in a Storable instance data StorablePeek = PeekTag TypeName PtrName TypeName | PeekEntry Int [StorablePeek] | PeekValue Name TypeName Name PtrName TypeName | PeekReturn Bool Bool Name [(Name,TypeName,Ann)] ModuleName deriving(Eq,Show,Data,Typeable) -- | Structure to describe the Poke values in a Storable instance data StorablePoke = PokeTag TypeName Field PtrName StorablePoke | NewPtr Bool Name TypeName | PokeValue Name | PokeVar Bool Bool Name (Maybe Name) Type Ann | PokeReturn ModuleName deriving(Eq,Show,Data,Typeable) -- | Information about the Haskell file to generate data HaskellFile = HaskellFile {_hsname :: Name -- ^ @hsname@ Name of the module , comments :: [HaskellComment] -- ^ @comments@ The top level comments to include for the module , pragmas :: [GHCPragma] -- ^ @pragmas@ The pragmas to include in the module , imports :: [Import] -- ^ @imports@ The set of imports to use in the module , hsclets :: [HSC_Let] -- ^ @hsclets@ The set of Hsc2Hs custom macros to include , includes :: [Include] -- ^ @includes@ The set of includes to include for hsc2hs to be able to calculate alignments etc , hsenums :: [DataEnum] -- ^ @hsenums@ Haskell Enums, used for the same purpose as in "DataEnum" in the C module. , hstypes :: [Ptr_Type] -- ^ @hstypes@ The Ptr type declarations used for clarity , hsexports :: [HaskellExport] -- ^ @hsexports@ The set of exported functions , hsimports :: [HaskellImport] -- ^ @hsimports@ The set of imported functions , hsfuncs :: [HaskellFunction] -- ^ @hsfuncs@ the set of haskell function bodies exported , hsstorable :: [HaskellStorable] -- ^ @hsstorable@ The set of Storable instances to create , hscallbacks :: [HaskellCallback] -- ^ @hscallbacks@ A set of callback functions for which mappings need to generated. , hsstables :: [Stable] -- ^ @hsstable@ List of stable ptrs which needs to be freed } deriving(Eq,Show,Data,Typeable)