hsc3-rw-0.14: hsc3 re-writing

Safe HaskellNone

Sound.SC3.RW.Tag

Description

Rewrite expressions and modules attaching tags to numeric literals.

Synopsis

Documentation

mk_var :: String -> ExpSource

Make Var Exp for String.

 mk_var "tag" == Var (UnQual (Ident "tag"))

mk_str_lit :: String -> ExpSource

Make String Lit.

 mk_str_lit "c1" == Lit (String "c1")

mk_int_lit :: Integral n => n -> ExpSource

Make Int Lit.

mk_frac_lit :: Real n => n -> ExpSource

Make Frac Lit.

exp_num_lit :: Exp -> Maybe LiteralSource

Numeric literal at Exp else Nothing

tag_exp :: String -> Exp -> ExpSource

Tag an Exp with String.

at_tagged :: (String -> Exp -> Exp) -> (Exp -> Exp) -> Exp -> ExpSource

Apply f at Exp e if it is tagged, else g. If the tag is within a Paren then it is discarded.

untag_exp :: Exp -> ExpSource

Inverse of tag_exp.

 let z = mk_int_lit (0::Integer)
 in untag_exp (Paren (tag_exp "c1" z)) == z

nil_src_loc :: SrcLocSource

Empty source location.

tag_exp_auto :: Exp -> State Int ExpSource

Variant of tag_exp that derives the the tag name using a State counter.

at_num_lit :: (Exp -> t) -> (Exp -> t) -> Exp -> tSource

Apply f at numeric literals, else g.

type RW t m a = t -> m aSource

type RW_st t a = t -> State Int aSource

type Tr_m m = String -> m StringSource

apply_rw :: (Monad m, Pretty a) => RW_Opt -> Parser t -> RW t m a -> Tr_m mSource

Parse String using Parser and apply RW.

apply_rw_pure :: Pretty a => RW_Opt -> Parser t -> (t -> a) -> TrSource

apply_rw_st :: Pretty a => RW_Opt -> Parser t -> RW_st t a -> TrSource

exp_rw :: String -> StringSource

Rewrite Exp.

 let r = "sinOsc AR (tag \"c1\" 440) (tag \"c2\" 0) * tag \"c3\" 0.1"
 in exp_rw "sinOsc AR 440 0 * 0.1" == r

module_rw :: String -> StringSource

Rewrite Module.

 let m = ["import Sound.SC3"
         ,"o = sinOsc AR (midiCPS 65.00) 0.00"
         ,"a = dbAmp (-12.00)"
         ,"main = audition (out 0.00 (o * a))"]
 in module_rw (unlines m)

rw_html_opt :: RW_OptSource

RW_Opt for html. The span code generates long lines...

exp_rw_html :: String -> StringSource

Transform re-written form to HTML.

 let e = "sinOsc AR 440 0 * 0.1"
 in exp_rw_html (exp_rw e)

module_rw_html :: String -> StringSource

Module variant of exp_rw_html.

 let m = "o = sinOsc AR 440 0 * 0.1\nmain = audition (out 0 o)"
 in module_rw_html (module_rw m)