{- 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 : Variable names 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 () Variables -} module Language.CAO.Common.Name ( -- * Names Name , NameSpace , IsName (..) --, hashName , nameStr , setNameStr , getNS , mkName , prefix -- * Constructing Names , mkVarName, mkFunName, mkTvName , mkPolIndName, mkStructFldName , isVarName, isFunName, isTvName , isPolIndName, isStructFldName ) where import Language.CAO.Common.Outputable -- | A Name appearing in CAO code -- data Name = Name !NameSpace !String deriving (Show, Read) class IsName a where varName :: a -> Name instance IsName Name where varName = id mkName :: NameSpace -> String -> Name mkName = Name nameStr :: Name -> String nameStr (Name _ s) = s setNameStr :: String -> Name -> Name setNameStr s (Name ns _) = Name ns s prefix :: String -> Name -> Name prefix s (Name ns s1) = Name ns (s ++ s1) getNS :: Name -> NameSpace getNS (Name ns _) = ns instance Eq Name where Name _ s1 == Name _ s2 = s1 == s2 instance Ord Name where compare (Name _ s1) (Name _ s2) = s1 `compare` s2 instance PP Name where ppr (Name sp n) = text n <> ifPprDebug (text "##Kind=" <> text (show sp)) -- | NameSpace for different kinds of 'Name' -- data NameSpace = Variable -- ^ CAO variable names | StructFld -- ^ Struct fields | FunName -- ^ Function names | PolInd -- ^ Polynomial ind | TvName -- ^ Type synonyms or structs deriving (Eq, Ord, Show, Read) mkVarName :: String -> Name mkVarName = Name Variable mkFunName :: String -> Name mkFunName = Name FunName mkTvName :: String -> Name mkTvName = Name TvName mkPolIndName :: String -> Name mkPolIndName = Name PolInd mkStructFldName :: String -> Name mkStructFldName = Name StructFld isVarName, isStructFldName, isPolIndName , isTvName , isFunName :: Name -> Bool isVarName (Name Variable _) = True isVarName _ = False isFunName (Name FunName _) = True isFunName _ = False isTvName (Name TvName _) = True isTvName _ = False isPolIndName (Name PolInd _) = True isPolIndName _ = False isStructFldName (Name StructFld _) = True isStructFldName _ = False