{- 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 : Operation codes and naming 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 () -} module Language.CAO.Platform.Naming where import Data.Array import Data.List (elemIndex) -------------------------------------------------------------------------------- class Codes e where codeOf :: e -> OpCode -------------------------------------------------------------------------------- -- Operations type OpCode = Int type OpName = String operName :: OpCode -> OpName operName op = operationNames ! op -- The code of an operator maps into its position in the list/array. -- E.g: -- operationNames ! code_init = "init" -- elementIndex "decl" opNames = code_decl code_init, code_decl, code_dispose, code_assign, code_equal :: OpCode code_nequal, code_cast, code_add, code_sub, code_mul, code_div :: OpCode code_pow, code_sym, code_mod, code_lte, code_lt, code_gte :: OpCode code_gt, code_or, code_and, code_xor , code_not, code_shift_up :: OpCode code_shift_down, code_rot_up, code_rot_down, code_range_select :: OpCode code_select, code_range_set, code_set, code_concat, code_ref :: OpCode code_row_range_select, code_col_range_select, code_row_range_set :: OpCode code_col_range_set, code_init_def :: OpCode code_init = 0 code_decl = 1 code_dispose = 2 code_assign = 3 code_equal = 4 code_nequal = 5 code_lte = 6 code_lt = 7 code_gte = 8 code_gt = 9 code_cast = 10 code_add = 11 code_sub = 12 code_mul = 13 code_div = 14 code_pow = 15 code_sym = 16 code_mod = 17 code_or = 18 code_and = 19 code_xor = 20 code_not = 21 code_shift_up = 22 code_shift_down = 23 code_rot_up = 24 code_rot_down = 25 code_range_select = 26 code_select = 27 code_range_set = 28 code_set = 29 code_concat = 30 code_ref = 31 code_row_range_select = 32 code_col_range_select = 33 code_row_range_set = 34 code_col_range_set = 35 code_init_def = 36 isCompCode :: OpCode -> Bool isCompCode c = code_equal <= c && c <= code_gt getCode :: OpName -> Maybe OpCode getCode w = elemIndex w opNames operationNames :: Array OpCode OpName operationNames = listArray (0, 36) opNames opNames :: [OpName] opNames = [ "init" , "decl" , "dispose" , "assign" , "equal" , "nequal" , "lte" , "lt" , "gte" , "gt" , "cast" , "add" , "sub" , "mul" , "div" , "pow" , "sym" , "mod" , "or" , "and" , "xor" , "not" , "shift_up" , "shift_down" , "rot_up" , "rot_down" , "range_select" , "select" , "range_set" , "set" , "concat" , "ref" , "row_range_select" , "col_range_select" , "row_range_set" , "col_range_set" , "initD" ] -------------------------------------------------------------------------------- -- Other strings used in the translation caoRes, caoRef :: String caoRes = "RES" caoRef = "REF" caoOk :: String caoOk = "CAO_OK" -- Variable, parameter and function names retArgId, vjump, structRes :: String retArgId = "_r" vjump = "vjump" structRes = "sRes" cTrueValue, cFalseValue :: Integer cTrueValue = 1 cFalseValue = 0 nullVal :: String nullVal = "0"