-- | UGen DB record definitions. module Sound.SC3.UGen.DB.Record where import Data.List {- base -} import Data.Maybe {- base -} import Safe {- safe -} import Sound.SC3.UGen.Rate {- hsc3 -} import Sound.SC3.UGen.DB.Meta {- hsc3-db -} -- | UGen input descriptor data I = I {input_name :: String ,input_default :: Double} deriving (Eq,Show) -- | UGen descriptor data U = U {ugen_name :: String ,ugen_operating_rates :: [Rate] ,ugen_default_rate :: Rate ,ugen_inputs :: [I] ,ugen_outputs :: Maybe Int ,ugen_summary :: String ,ugen_std_mce :: Bool ,ugen_nc_input :: Bool ,ugen_nc_mce :: Maybe Int ,ugen_filter :: Maybe [Int] ,ugen_reorder :: Maybe [Int] ,ugen_enumerations :: Maybe [(Int,String)] ,ugen_nondet :: Bool ,ugen_pseudo_inputs :: Maybe [Int] ,ugen_fixed_rate :: Maybe Rate } deriving (Eq,Show) -- | (nm,rr,rt,inp,outp,dsc) -- -- nm = name, rr = possible rates, rt = default rate, inp = list of -- inputs, outp = output, dsc = description (synopsis) type SC3_U = (String,[Rate],Rate,[I],Int,String) remove_nc_inputs :: [I] -> [I] remove_nc_inputs = let f i = input_name i `notElem` ["numChannels","numChans"] in filter f -- this is the way the permutations are written... reorder_f :: Show a => a -> [a1] -> [Int] -> [a1] reorder_f u inp n = let f i = let j = fromMaybe (error "read_meta: input reorder") (findIndex (== i) n) in atNote (show u) inp j in map f [0 .. length inp - 1] read_meta :: SC3_U -> U read_meta sc3_u = let (nm,rr,rt,inp,outp,dsc) = sc3_u nc = meta_has_nc_input nm inp' = if nc then remove_nc_inputs inp else inp srt = lookup nm meta_input_reorder inp'' = case srt of Nothing -> inp' Just n -> reorder_f sc3_u inp' n fx = meta_is_fixed_rate nm ir = if meta_allows_i_rate nm then [IR] else [] rr' = nub (sort (ir ++ rr ++ maybe [] return fx)) in U {ugen_name = nm ,ugen_operating_rates = rr' ,ugen_default_rate = rt ,ugen_inputs = inp'' ,ugen_outputs = if meta_has_var_inputs nm then Nothing else Just outp ,ugen_summary = dsc ,ugen_std_mce = meta_is_std_mce nm ,ugen_nc_input = nc ,ugen_nc_mce = lookup nm meta_nc_mce ,ugen_filter = lookup nm meta_filters ,ugen_reorder = srt ,ugen_enumerations = lookup nm meta_enumeration_inputs ,ugen_nondet = meta_is_nondet nm ,ugen_pseudo_inputs = lookup nm meta_pseudo_inputs ,ugen_fixed_rate = fx} input_enumeration :: U -> Int -> Maybe String input_enumeration u ix = case ugen_enumerations u of Just e -> lookup ix e Nothing -> Nothing -- | Infinite default value inf :: Double inf = 10 ** 8 -- | Enumeration for @Onsets@ UGen @odftype@ input. rcomplex :: Double rcomplex = 3 -- | 'true' is @1@. true :: Double true = 1 -- | 'false' is @0@. false :: Double false = 0 -- | Alternate view of 'ugen_nc_input' and 'ugen_nc_mce'. u_fixed_outputs :: U -> Maybe Int u_fixed_outputs u = case (ugen_nc_input u,ugen_nc_mce u) of (False,Nothing) -> ugen_outputs u _ -> Nothing -- | Is 'DR' the only allowed 'Rate'? u_is_demand_rate :: U -> Bool u_is_demand_rate = (== [DR]) . ugen_operating_rates -- | List of input names. -- -- > import Sound.SC3.UGen.DB -- > fmap u_input_names (uLookup "SinOsc") == Just ["freq","phase"] -- > fmap u_input_names (uLookup "BufRd") == Just ["bufnum","phase","loop","interpolation"] -- > fmap u_input_names (uLookup "Dseq") == Just ["list","repeats"] u_input_names :: U -> [String] u_input_names = map input_name . ugen_inputs -- | Is the input 'I' mce collapsed at 'U'. i_is_mce :: U -> I -> Bool i_is_mce u i = ugen_std_mce u && i == last (ugen_inputs u) -- | Pretty printer for 'I'. -- -- > let Just u = uLookup "SinOsc" -- > in i_pp u (I 0 "freq" 440.0) == "freq=440.0" -- -- > let Just u = uLookup "Out" -- > in i_pp u (I 1 "channelsArray" 0) == "*channelsArray=0.0" i_pp :: U -> I -> String i_pp u i = let m = if i_is_mce u i then "*" else "" in m ++ input_name i ++ "=" ++ show (input_default i) -- | Generate simple summary string for 'U'. u_summary :: U -> String u_summary u = let commas = intercalate ", " mce n = if n then Just "MCE" else Nothing nc n = if n then Just ("NC INPUT: " ++ show n) else Nothing flt _ = "FILTER: TRUE" sq l = "REORDERS INPUTS: " ++ show l en l = "ENUMERATION INPUTS: " ++ commas (map (\(ix,nm) -> show ix ++ "=" ++ nm) l) ps l = "PSUEDO INPUTS: " ++ show l gen f p = fmap f (p u) nd (d,b) = if d then Just "DEMAND/NONDET" else if b then Just "NONDET" else Nothing secondary = commas (catMaybes [mce (ugen_std_mce u) ,nc (ugen_nc_input u) ,gen flt ugen_filter ,gen sq ugen_reorder ,gen en ugen_enumerations ,gen ps ugen_pseudo_inputs ,nd (u_is_demand_rate u,ugen_nondet u)]) secondary' = if null secondary then [] else "\n " ++ secondary in unwords [ugen_name u ,show (ugen_operating_rates u) ,unwords (map (i_pp u) (ugen_inputs u))] ++ secondary'