{- CAO Compiler Copyright (C) 2014 Cryptography and Information Security Group, HASLab - INESC TEC and Universidade do Minho This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | Module : $Header$ Description : Information about the target platform. Copyright : (C) 2014 Cryptography and Information Security Group, HASLab - INESC TEC and Universidade do Minho License : GPL Maintainer : Paulo Silva Stability : experimental Portability : non-portable This file contains the specificatio of the target platform to guide the translation process. -} module Language.CAO.Platform.Specification where import Data.Array import Language.CAO.Platform.Naming import Language.CAO.Platform.Literals -------------------------------------------------------------------------------- data TranslationSpec = TranslationSpec { globalTransSpec :: GlobalTransSpec , typeTransSpec :: TypeTransSpec } deriving Show -- One entry for each native CAO type data TypeTransSpec = TypeTransSpec { boolT :: (Maybe TypeSpec) , intT :: (Maybe TypeSpec) , rintT :: (Maybe TypeSpec) , ubitsT :: [(Size, TypeSpec)] , sbitsT :: [(Size, TypeSpec)] , modT :: [(Size, TypeSpec)] , vectorT :: [(Size, TypeSpec)] , matrixT :: [(Size, TypeSpec)] , structT :: (Maybe TypeSpec) , modpolT :: (Maybe TypeSpec) } deriving Show data GlobalTransSpec = GlobalTransSpec { initProcName :: String , disposeProcName :: String , tpPrefix :: String , callPrefix :: String , defaultHeader :: Header , defaultSafety :: SafetyConv , structFields :: FieldsConv , wordSize :: (Maybe Int) } deriving Show emptyTranslationSpec :: TranslationSpec emptyTranslationSpec = TranslationSpec { globalTransSpec = emptyGlobalTransSpec , typeTransSpec = emptyTypeTransSpec } emptyGlobalTransSpec :: GlobalTransSpec emptyGlobalTransSpec = GlobalTransSpec { initProcName = "" , disposeProcName = "" , tpPrefix = "" , callPrefix = "" , defaultHeader = "" , defaultSafety = Unsafe , structFields = GlobalF , wordSize = Nothing } emptyTypeTransSpec :: TypeTransSpec emptyTypeTransSpec = TypeTransSpec { boolT = Nothing , intT = Nothing , rintT = Nothing , ubitsT = [] , sbitsT = [] , modT = [] , vectorT = [] , matrixT = [] , structT = Nothing , modpolT = Nothing } data TypeSpec = TypeSpec { nameInPlat :: String -- Translation to a platform name , headerFile :: Header -- Header file with definitions for the type , code :: String -- Short code for the type , declConv :: VarDeclaration , memoryConv :: VarMemory , funcCall :: FuncReturn , operands :: Consts , literal :: Maybe LitCheck , operations :: Array OpCode (Maybe (OpReturn, Consts, SafetyConv)) -- Map of CAO operation to operations in the platform } deriving Show data VarDeclaration = VarDecl | MacroDecl deriving Show data VarMemory = Auto | AutoRef | Alloc deriving Show data FuncReturn = FFuncRef | FFuncReturn deriving Show data OpReturn = OMacroRef | OMacroReturn | OFuncRef | OFuncReturn deriving Show data SafetyConv = Safe | Unsafe | ArgSafe deriving Show data FieldsConv = GlobalF | InlinedF deriving Show -- Inlined: all operands must be literal constants inlined in the call -- LocalV: All the operands should be stored in variables. Literals should be stored in local variables -- GlobalV: All the operands should be stored in variables. Literals should be stored in global variables data Consts = GlobalV | LocalV | Inlined | Mixed deriving Show type Header = String