%
% (c) The Foo Project, Universities of Glasgow & Utrecht, 1997-8
%
% @(#) $Docid: Nov. 16th 2001 17:13 Sigbjorn Finne $
% @(#) $Contactid: sof@galconn.com $
%
The CoreIDL interface defines the intermediate representation
used for IDL specifications.
\begin{code}
module CoreIDL where
import Literal
import BasicTypes
import Int ( Int32 )
import TypeInfo
\end{code}
\begin{code}
data Decl
= Typedef { declId :: Id, declType :: Type, declOrigType :: Type }
| Constant { declId :: Id
, declType :: Type
, declOrigType :: Type
, declExpr :: Expr
}
| Interface { declId :: Id
, isReference :: Bool
, declInherit :: InterfaceInherit
, declDecls :: [InterfaceDecl]
}
| Module { declId :: Id, declDecls :: [ModuleDecl] }
| DispInterface { declId :: Id
, dispExpandedFrom :: Maybe Decl
, declProps :: [DispInterfaceDecl]
, declDecls :: [DispInterfaceDecl]
}
| CoClass { declId :: Id, declCoDecls :: [CoClassDecl] }
| Library { declId :: Id, declDecls :: [LibraryDecl] }
| Method { declId :: Id
, methCallConv :: CallConv
, methResult :: Result
, methParams :: [Param]
, methOffset :: Maybe Int
}
| Property { declId :: Id
, declType :: Type
, propOffset :: Maybe Int
, declSetId :: Id
, declGetId :: Id
}
| HsLiteral String
| CInclude String
| CLiteral String
type InterfaceDecl = Decl
type ModuleDecl = Decl
type DispInterfaceDecl = Decl
data CoClassDecl
= CoClassInterface { coClassId :: Id, coClassDecl :: Maybe Decl }
| CoClassDispInterface { coClassId :: Id, coClassDecl :: Maybe Decl }
type LibraryDecl = Decl
type InterfaceInherit =
[( QualName
, Int
)]
\end{code}
\begin{code}
data Expr
= Binary BinaryOp Expr Expr
| Cond Expr Expr Expr
| Unary UnaryOp Expr
| Var Name
| Lit Literal
| Cast Type Expr
| Sizeof Type
deriving ( Eq
, Show
)
\end{code}
The type language for Core IDL:
\begin{code}
data Type
= Integer Size Signed
| StablePtr
| FunTy CallConv Result [Param]
| Float Size
| Char Signed
| WChar
| Bool | Octet | Any | Object
| String Type Bool (Maybe Expr) | WString Bool (Maybe Expr)
| Sequence Type (Maybe Expr) (Maybe Expr)
| Fixed Expr IntegerLit
| Name Name
Name
(Maybe Name)
(Maybe [Attribute])
(Maybe Type)
(Maybe TypeInfo)
| Struct Id
[Field]
(Maybe Int)
| Enum Id EnumKind [EnumValue]
| Union Id Type Id Id [Switch]
| UnionNon Id [Switch]
| CUnion Id [Field]
(Maybe Int)
| Pointer PointerType
Bool
Type
| Array Type [Expr]
| Void
| Iface Name
(Maybe Name)
Name
[Attribute]
Bool
InterfaceInherit
| SafeArray Type
deriving ( Eq
, Show
)
type Signed = Bool
\end{code}
In Core, we pin attributes on Ids:
\begin{code}
data Id
= Id {
idName :: Name,
idOrigName :: Name,
idModule :: Maybe Name,
idAttributes :: [Attribute]
}
deriving ( Eq
, Show
)
\end{code}
\begin{code}
data Attribute
= AttrMode ParamDir
| AttrDependent {
atReason :: DepReason,
atParams :: [AttributeParam]
}
| Attribute {
atName :: Name,
atParams :: [AttributeParam]
}
deriving ( Eq
, Show
)
data AttributeParam
= ParamLit Literal
| ParamType Type
| ParamExpr Expr
| ParamVar Name
| ParamVoid
| ParamPtr AttributeParam
deriving ( Eq
, Show
)
data DepReason
= SizeIs | LengthIs
| LastIs | FirstIs
| MaxIs | MinIs
| SwitchIs
deriving ( Eq, Show )
\end{code}
\begin{code}
data Result =
Result {
resultType :: Type,
resultOrigType :: Type
}
deriving ( Eq
, Show
)
data Param
= Param {
paramId :: Id,
paramMode :: ParamDir,
paramType :: Type,
paramOrigType :: Type,
paramDependent :: Bool
}
deriving ( Eq
, Show
)
data Switch
= Switch {
switchId :: Id,
switchLabels :: [CaseLabel],
switchType :: Type,
switchOrigType :: Type
}
| SwitchEmpty (Maybe [(CaseLabel,String)])
deriving ( Eq
, Show
)
data CaseLabel
= Case Expr | Default
deriving ( Eq
, Show
)
data Field
= Field {
fieldId :: Id,
fieldType :: Type,
fieldOrigType :: Type,
fieldSize :: Maybe Int,
fieldOffset :: Maybe Int
} deriving ( Eq
, Show
)
data EnumValue
= EnumValue {
enumName :: Id,
enumValue :: (Either Int32 Expr)
} deriving ( Eq
, Show
)
\end{code}