hdf-0.15: HDF: Uniform Rate Audio Signal Processing in Haskell

Safe HaskellSafe-Inferred
LanguageHaskell98

Sound.DF.Uniform.LL.CGen

Contents

Description

C code generator

Synopsis

C init / call

type C_Comment = String Source

C comment.

c_comment :: String -> C_Comment Source

Add comment markers.

c_comment "c" == "/* c */"

type C_Type = String Source

C type.

c_typerep_ctype :: TypeRep -> C_Type Source

Translate TypeRep to C_Type.

c_typerep_ctype bool_t == "bool"
c_typerep_ctype (typeOf (0.0::Float)) == "float"

type C_QName = (String, String, String) Source

Qualified name, (structure,access,member).

c_init_atom :: C_QName -> Var_Fld -> String Source

Initialise C_QName to value.

c_init_atom ("s",".","r") 5 == "s.m = 5;"

c_init_vec :: (Eq a, Show a) => C_QName -> [a] -> [String] Source

Initialise C_QName to array. Generates loop code for sequences of equal initial values.

c_init_vec ("s",".","r") [0,1] == ["s.r[0] = 0;"
                                  ,"s.r[1] = 1;"]
let r = ["for(int i=0;i < 2;i++) {s.r[i] = 0;}"]
in c_init_vec ("s",".","r") [0,0] == r

c_init_var :: C_QName -> Var_Fld -> [String] Source

Initialise C_QName to value or array.

let {qn = ("s","->","r")
    ;r = ["for(int i=0;i < 2;i++) {s->r[i] = 0;}","s->r[2] = 1;"]}
in c_init_var qn (Right [0,0,1]) == r

c_array_qual :: Maybe Int -> String -> Bool -> String Source

Qualify name if required. The rf flag indicates if array is a reference or an allocation.

c_array_qual (Vec_Port float_t 3) "a" True == "*a"
c_array_qual (Vec_Port float_t 3) "a" False == "a[3]"

type C_Call = (Maybe String, String, [(Var_Ty, Id)]) Source

C function call. (comment?,function,arguments)

c_call :: C_Call -> String Source

Construct a function/macro call.

c_call (Nothing,"f",["0","1"]) == "f(0,1);"
c_call ("c","f",["0","1"]) == "f(0,1); /* c */"

Variables

data Var_Ty Source

Enumeration of variable types.

Constructors

Rec_Var 
Std_Var 
Buf_Var Int 

Instances

var_ty_char :: Var_Ty -> Char Source

The character prefix for a Var name is given by the Var_Ty.

type Var = (Var_Ty, TypeRep, Id, Maybe Var_Fld) Source

(Type,Array,Label,Initialised)

is_stateful :: Var -> Bool Source

Non-Std_Var are stateful, ie. Rec_Var and Buf_Var.

is_stateful_atom :: Var -> Bool Source

Rec_Var are stateful and atoms.

k_var :: Id -> Var_Ty -> K -> Var Source

Generate Var from K.

buffer_var :: Id -> Vec Float -> Var Source

Generate Buf_Var from Vec.

var_decl :: Bool -> Var -> String Source

Var C declaration, rf determines c_array_qual form.

gen_var_struct :: String -> (Var -> Bool) -> [Var] -> [String] Source

Generate a C struct for Var, predicate determines if array variables are refernces or allocations.

clabel :: (Var_Ty, Id) -> String Source

Construct an identifier.

clabel (Std_Var,0) == "n_0"

std_clabel :: Id -> String Source

clabel of Std_Var.

std_clabel 0 == "n_0"

m_clabel :: (Var_Ty, Id) -> String Source

Variant with m. prefix.

c_const :: (Id, K) -> [String] Source

c_init_var for constant.

c_const (0,I 1) == ["m.n_0 = 1;"]

Code generators

dsp_fun_decl :: [String] Source

C declarations for DSP functions (memreq,init and step).

cmem :: [Var] -> [String] Source

The structure for all memory stores. In the uniform model this is a notational convenience only. In a partioned model it is functional.

cstate :: [Var] -> [String] Source

The structure for stateful Var.

dsp_memreq :: [String] Source

Generate dsp_memreq function.

dsp_init :: [Var] -> [String] Source

Generate dsp_init function.

type Instructions = ([(Id, K)], [Var], [C_Call]) Source

List of constants, list of variables, list of c-calls.

dsp_step :: Instructions -> [String] Source

Generate dsp_step function.

code_gen :: Host -> Instructions -> String Source

Generate C code for graph.

Host

data Host Source

Enumeration of code hosts.

Constructors

JACK 
SC3 
Text 

host_include :: Host -> String Source

Host specific #include file.

host_dsp_fun_decl :: Host -> [String] Source

Host specific form of dsp_fun_decl (extern C where required).

host_compiler_cmd :: (Host, FilePath) -> (String, [String]) Source

Generate compiler command for Host given include directory prefix.

host_compiler_cmd_str :: (Host, FilePath) -> String Source

Format host_compiler_cmd as String.

host_compiler_cmd_str (JACK,"/home/rohan/opt")
host_compiler_cmd_str (SC3,"/home/rohan/opt")
host_compiler_cmd_str (Text,"/home/rohan/opt")

IO

dl_gen :: FilePath -> (Host, FilePath) -> Instructions -> IO () Source

Generate C code, write file to disk and call the GNU C compiler to build shared library.

List

bracket :: (a, a) -> [a] -> [a] Source

Bracket list with elements.

bracket ('<','>') "float" == "<float>"

dx_d :: Num n => [n] -> [n] Source

Integrate, with implicit 0.

dx_d [5,6] == [0,5,11]