-- | Renaming functions for UGen descriptions. module Sound.SC3.UGen.DB.Rename where import Data.Char {- base -} import Data.List {- base -} import Sound.SC3.UGen.Name {- hsc3 -} import Sound.SC3.UGen.DB.Record -- | Rename parameters that conflict with /Haskell/ or /LISP/ keywords or -- 'Prelude' functions, or which have otherwise unwieldy names. -- -- > map rename_input ["in","id"] == ["input","id_"] rename_input :: String -> String rename_input p = case p of -- keyword "default" -> "default_" "in" -> "input" "type" -> "type_" -- prelude "div" -> "div_" "drop" -> "drop_" "exp" -> "exp_" "floor" -> "floor_" "id" -> "id_" "init" -> "init_" "length" -> "length_" "min" -> "min_" "max" -> "max_" "mod" -> "mod_" "round" -> "round_" -- internal (hsc3) use "rate" -> "rate_" "control" -> "control_" "label" -> "label_" "envelope" -> "envelope_" -- LISP "list" -> "list_" -- unwieldy "channelsArray" -> "input" _ -> p -- | Rename unit generators that conflict with /Haskell/ keywords or -- 'Prelude' functions, or where the general case rule doesn't work. -- -- > map hs_rename_ugen (words "In Out HPZ1 RLPF") hs_rename_ugen :: String -> String hs_rename_ugen = fromSC3Name -- | Case insensitive 'String' '=='. ci_eq :: String -> String -> Bool ci_eq p q = let f = map toLower in f p == f q -- | If the input name is the same as the ugen name, rename the input. rename_eq_input :: String -> String -> String rename_eq_input u = let f x = if x `ci_eq` u then x ++ "_" else x in rename_input . f -- | 'rename_eq_input' at 'I' of 'U'. i_rename :: U -> I -> I i_rename u i = i {input_name = rename_eq_input (ugen_name u) (input_name i)} -- | 'i_rename' at 'U'. u_rename :: U -> U u_rename u = let i' = map (i_rename u) (ugen_inputs u) in u {ugen_inputs = i'} -- | Rename input if it's listed (case insensitive). i_rename_db :: [String] -> I -> I i_rename_db uu_nm i = let n = input_name i n' = case find (ci_eq n) uu_nm of Just _ -> n ++ "_" Nothing -> n in i {input_name = rename_input n'} -- | Variant that renames inputs to avoid name collisions with any other UGen. u_rename_db :: [U] -> U -> U u_rename_db uu u = let uu_nm = map ugen_name uu i' = map (i_rename_db uu_nm) (ugen_inputs u) in u {ugen_inputs = i'} -- | Names of SC3 operators that conflict with RNRS scheme names. scheme_names :: [String] scheme_names = let uop = "abs cos exp floor log not sin sqrt tan" binop = "gcd lcm max min mod round" in words (unlines [uop,binop]) -- | Prefix reserved names with 'u:'. scheme_rename :: String -> String scheme_rename nm = if nm `elem` scheme_names then "u:" ++ nm else nm u_renamed_inputs :: U -> [String] u_renamed_inputs u = map (rename_input . input_name) (ugen_inputs u)