module CsMaps where import qualified Data.Map as M import qualified Data.Set as S -- | classes that need to be imported qualified to prevent clashes qualifiedNameMap :: M.Map String String qualifiedNameMap = M.fromList [("CsOscili", "CSE") ,("CsOscil", "CSE") ,("CsSum", "CSE") ] qualifyName :: String -> String qualifyName nm = maybe nm ( ++ "." ++ nm) $ M.lookup nm qualifiedNameMap -- | Map any csound names which are unallowed in Haskell to valid names invalidNameMap :: M.Map String String invalidNameMap = M.fromList [("in", "inCS") ,("i", "iCS") ,("k", "kCS") ,("a", "aCS")] -- | Anything in this set is already bound as part of the core language -- and shouldn't be re-bound noReuseSet :: S.Set String noReuseSet = S.fromList ["vdelay3" ,"vdelay" ,"abs" ,"int" ,"floor" ,"frac" ,"logbtwo" ,"octcps" ,"octpch" ,"cpsoct" ,"cpspch" ,"pchcps" ,"pchoct" ,"out" ,"outs" ,"outq" ,"outo" ,"phasor" ,"slider32table" ,"slider32tablef" ,"slider64table" ,"slider64tablef" ,"sqrt" ] -- | if a function needs a special context, add it addCtxt :: String -> [String] addCtxt str | take 3 str == "pvs" = ["PVS repr"] -- PVS context (for FSig) addCtxt _ = []