{- 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 . -} {-# LANGUAGE FlexibleContexts #-} {- Module : $Header$ Description : Generation of new simbols. 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.Common.Fresh ( freshVar -- Indist, Simplify, Target , freshVar' -- PreC , freshSFld -- PreC , freshTmpVar -- Target, PreC, C , freshIndex -- Simplify , freshSmb -- C, PreC ) where import Language.CAO.Common.Monad import Language.CAO.Common.State import Language.CAO.Common.Var import Language.CAO.Type freshSmb :: CaoM e w s m => m (Int, String) freshSmb = do i <- uniqId return (i, 't' : show i) freshVar :: CaoM e w s m => Scope -> Type Var -> m Var freshVar s t = do (i, n) <- freshSmb return $ mkVar s (mkVarName n) i t where mkVar Global = mkGId mkVar Local = mkLId freshVar' :: CaoM e w s m => Scope -> String -> Type Var -> m Var freshVar' s n t = do i <- uniqId return $ mkVar s (mkVarName n) i t where mkVar Global = mkGId mkVar Local = mkLId freshSFld :: CaoM e w s m => String -> Type Var -> m Var freshSFld n t = do i <- uniqId return $ mkGId (mkVarName n) i t freshIndex :: CaoM e w s m => Scope -> Type Var -> m Var freshIndex s t = do (i, n) <- freshSmb return $ mkVar s (mkVarName n) i t Nothing where mkVar Global = mkGConst mkVar Local = mkLConst -- Temporary variables obtained using this function, -- should be stored in the temporary variable pool after -- being used. freshTmpVar :: CaoM e w CaoState m => Type Var -> m Var freshTmpVar typ = tmpFromPool typ >>= maybe (freshVar Local typ) return