----------------------------------------------------------------------------- -- | -- Module : Windll -- Copyright : (c) Tamar Christina 2009 - 2010 -- License : BSD3 -- -- Maintainer : tamar@zhox.com -- Stability : experimental -- Portability : portable -- -- General Folds for the Haskell-Src-Exts datatypes -- ----------------------------------------------------------------------------- module WinDll.Structs.Folds.C where import WinDll.Structs.C import WinDll.Structs.Types import WinDll.Structs.Structures(Callback) import WinDll.Session.Hs2lib(CallConvention) -- * Type Algebras for the current ADTs in the C file -- | Type Algebra for the Include ADT type IncludeAlgebra a = (Name -> a ,Name -> a ) -- | Type Algebra for the DataEnum ADT type DataEnumAlgebra a = (Name -> [String] -> a) -- | Type Algebra for the CDataType ADT type CDataTypeAlgebra a = (a ,a ,a ,a ) -- | Type Algebra for the FieldType ADT type FieldTypeAlgebra a =(a ,a ) -- | Type Algebra for the DataFieldType ADT type DataFieldTypeAlgebra a =(a ,a ) -- | Type Algebra for the DataField ADT type DataFieldAlgebra a = (DataFieldType -> CDataType -> Name -> TypeName -> [a] -> a ,CDataType -> TypeName -> FieldType -> (Maybe Name) -> a ,CDataType -> Name -> a ) -- | Type Algebra for the C ADT type CAlgebra a = ([Include] -> CallConvention -> [Callback] -> [DataEnum] -> [DataField] -> [DataField] -> a) -- * The general folds used with the ADTs defined in the C file -- | General fold for the Include ADT foldInclude :: IncludeAlgebra a -> Include -> a foldInclude (lib,local) = fold where fold (LibInclude a) = lib a fold (LocalInclude a) = local a -- | General fold for the DataEnum ADT foldDataEnum :: DataEnumAlgebra a -> DataEnum -> a foldDataEnum (dataenum) = fold where fold (DataEnum a b) = dataenum a b -- | General fold for the CDataType ADT foldCDataType :: CDataTypeAlgebra a -> CDataType -> a foldCDataType (struct,union,dnum,val) = fold where fold Struct = struct fold Union = union fold ENum = dnum fold VAlue = val -- | General fold for the FieldType ADT foldFieldType :: FieldTypeAlgebra a -> FieldType -> a foldFieldType (normal,pointer) = fold where fold Normal = normal fold Pointer = pointer -- | General fold for the DataFieldType ADT foldDataFieldType :: DataFieldTypeAlgebra a -> DataFieldType -> a foldDataFieldType (typedef,normaldef) = fold where fold TypeDef = typedef fold NormalDef = normaldef -- | General fold for the DataField ADT foldDataField :: DataFieldAlgebra a -> DataField -> a foldDataField (field,value,forw) = fold where fold (Field x a b c d) = field x a b c (map fold d) fold (Value a b c d) = value a b c d fold (Forward a b) = a `forw` b -- | General fold for the C ADT foldC :: CAlgebra a -> C -> a foldC (ccons) = fold where fold (C a b c d e f) = ccons a b c d e f