{- 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 : Useful function to manipulate indexes. 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.Index.Utils where import Language.CAO.Common.Literal import Language.CAO.Common.SrcLoc import Language.CAO.Common.Var import Language.CAO.Index import Language.CAO.Syntax import Language.CAO.Type ind2Expr :: IExpr Var -> LExpr Var -- TODO: Not handling int's ind2Expr (IInt n) = genLoc $ Lit $ ILit n ind2Expr (IInd v) = genLoc $ Var v ind2Expr (ISum l) = aux l where aux :: [IExpr Var] -> LExpr Var aux [] = error ": empty sum list" aux [e] = ind2Expr e -- TODO: HACK to handle type annotations aux (e:es) = genLoc $ BinaryOp (ArithOp Plus) (annL RInt (ind2Expr e)) (annL RInt (aux es)) ind2Expr (IArith op e1 e2) = genLoc $ BinaryOp (ArithOp (iAOp2AOp op)) (annL RInt (ind2Expr e1)) (annL RInt (ind2Expr e2)) ind2Expr (ISym e) = genLoc $ UnaryOp Sym (annL RInt (ind2Expr e)) iAOp2AOp :: IAOp -> AOp iAOp2AOp IMinus = Minus iAOp2AOp ITimes = Times iAOp2AOp IPower = Power iAOp2AOp IDiv = Div iAOp2AOp IModOp = ModOp queryIndexTy :: IExpr Var -> Type Var queryIndexTy (IInt _) = RInt -- TODO: what about Int's?? queryIndexTy (IInd v) = varType v queryIndexTy (ISym e) = queryIndexTy e queryIndexTy (IArith _ e _) = queryIndexTy e queryIndexTy (ISum (e:_)) = queryIndexTy e queryIndexTy _ = error ": not expected" mapAOp :: AOp -> (IExpr id -> IExpr id -> IExpr id) mapAOp Minus = (.-.) mapAOp Times = (.*.) mapAOp Power = (.**.) mapAOp Div = (./.) mapAOp ModOp = (.%.) mapAOp _ = error ": not expected" mapBOp :: BOp -> (ICond id -> ICond id -> ICond id) mapBOp Or = (.||.) mapBOp Xor = (.^^.) mapBOp _ = error ": not expected" mapCOp :: COp -> (IExpr id -> IExpr id -> ICond id) mapCOp Eq = (.==.) mapCOp Neq = (./=.) mapCOp Lt = (.<.) mapCOp Leq = (.<=.) mapCOp Gt = (.>.) mapCOp Geq = (.>=.)