csound-expression-dynamic-0.3.3: dynamic core for csound-expression library

Safe HaskellNone
LanguageHaskell98

Csound.Dynamic.Types.Exp

Description

Main types

Synopsis

Documentation

type E = Fix RatedExp Source #

The inner representation of csound expressions.

data RatedExp a Source #

Constructors

RatedExp 

Fields

  • ratedExpRate :: Maybe Rate

    Rate (can be undefined or Nothing, it means that rate should be deduced automatically from the context)

  • ratedExpDepends :: Maybe LineNum

    Dependency (it is used for expressions with side effects, value contains the privious statement)

  • ratedExpExp :: Exp a

    Main expression

Instances

Functor RatedExp Source # 

Methods

fmap :: (a -> b) -> RatedExp a -> RatedExp b #

(<$) :: a -> RatedExp b -> RatedExp a #

Foldable RatedExp Source # 

Methods

fold :: Monoid m => RatedExp m -> m #

foldMap :: Monoid m => (a -> m) -> RatedExp a -> m #

foldr :: (a -> b -> b) -> b -> RatedExp a -> b #

foldr' :: (a -> b -> b) -> b -> RatedExp a -> b #

foldl :: (b -> a -> b) -> b -> RatedExp a -> b #

foldl' :: (b -> a -> b) -> b -> RatedExp a -> b #

foldr1 :: (a -> a -> a) -> RatedExp a -> a #

foldl1 :: (a -> a -> a) -> RatedExp a -> a #

toList :: RatedExp a -> [a] #

null :: RatedExp a -> Bool #

length :: RatedExp a -> Int #

elem :: Eq a => a -> RatedExp a -> Bool #

maximum :: Ord a => RatedExp a -> a #

minimum :: Ord a => RatedExp a -> a #

sum :: Num a => RatedExp a -> a #

product :: Num a => RatedExp a -> a #

Traversable RatedExp Source # 

Methods

traverse :: Applicative f => (a -> f b) -> RatedExp a -> f (RatedExp b) #

sequenceA :: Applicative f => RatedExp (f a) -> f (RatedExp a) #

mapM :: Monad m => (a -> m b) -> RatedExp a -> m (RatedExp b) #

sequence :: Monad m => RatedExp (m a) -> m (RatedExp a) #

Hashable E Source # 

Methods

hashWithSalt :: Int -> E -> Int #

hash :: E -> Int #

Eq a => Eq (RatedExp a) Source # 

Methods

(==) :: RatedExp a -> RatedExp a -> Bool #

(/=) :: RatedExp a -> RatedExp a -> Bool #

Ord a => Ord (RatedExp a) Source # 

Methods

compare :: RatedExp a -> RatedExp a -> Ordering #

(<) :: RatedExp a -> RatedExp a -> Bool #

(<=) :: RatedExp a -> RatedExp a -> Bool #

(>) :: RatedExp a -> RatedExp a -> Bool #

(>=) :: RatedExp a -> RatedExp a -> Bool #

max :: RatedExp a -> RatedExp a -> RatedExp a #

min :: RatedExp a -> RatedExp a -> RatedExp a #

Show a => Show (RatedExp a) Source # 

Methods

showsPrec :: Int -> RatedExp a -> ShowS #

show :: RatedExp a -> String #

showList :: [RatedExp a] -> ShowS #

Generic (RatedExp a) Source # 

Associated Types

type Rep (RatedExp a) :: * -> * #

Methods

from :: RatedExp a -> Rep (RatedExp a) x #

to :: Rep (RatedExp a) x -> RatedExp a #

Hashable a => Hashable (RatedExp a) Source # 

Methods

hashWithSalt :: Int -> RatedExp a -> Int #

hash :: RatedExp a -> Int #

type BooleanOf E # 
type BooleanOf E = E
type Rep (RatedExp a) Source # 
type Rep (RatedExp a)

type RatedVar = Var Rate Source #

RatedVar is for pretty printing of the wiring ports.

ratedVar :: Rate -> Int -> RatedVar Source #

Makes an rated variable.

ratedVarRate :: RatedVar -> Rate Source #

Querries a rate.

ratedVarId :: RatedVar -> Int Source #

Querries an integral identifier.

setRate :: Rate -> E -> E Source #

type Exp a = MainExp (PrimOr a) Source #

toPrimOr :: E -> PrimOr E Source #

Constructs PrimOr values from the expressions. It does inlining in case of primitive values.

toPrimOrTfm :: Rate -> E -> PrimOr E Source #

Constructs PrimOr values from the expressions. It does inlining in case of primitive values.

newtype PrimOr a Source #

It's a primitive value or something else. It's used for inlining of the constants (primitive values).

Constructors

PrimOr 

Fields

Instances

Functor PrimOr Source # 

Methods

fmap :: (a -> b) -> PrimOr a -> PrimOr b #

(<$) :: a -> PrimOr b -> PrimOr a #

Foldable PrimOr Source # 

Methods

fold :: Monoid m => PrimOr m -> m #

foldMap :: Monoid m => (a -> m) -> PrimOr a -> m #

foldr :: (a -> b -> b) -> b -> PrimOr a -> b #

foldr' :: (a -> b -> b) -> b -> PrimOr a -> b #

foldl :: (b -> a -> b) -> b -> PrimOr a -> b #

foldl' :: (b -> a -> b) -> b -> PrimOr a -> b #

foldr1 :: (a -> a -> a) -> PrimOr a -> a #

foldl1 :: (a -> a -> a) -> PrimOr a -> a #

toList :: PrimOr a -> [a] #

null :: PrimOr a -> Bool #

length :: PrimOr a -> Int #

elem :: Eq a => a -> PrimOr a -> Bool #

maximum :: Ord a => PrimOr a -> a #

minimum :: Ord a => PrimOr a -> a #

sum :: Num a => PrimOr a -> a #

product :: Num a => PrimOr a -> a #

Traversable PrimOr Source # 

Methods

traverse :: Applicative f => (a -> f b) -> PrimOr a -> f (PrimOr b) #

sequenceA :: Applicative f => PrimOr (f a) -> f (PrimOr a) #

mapM :: Monad m => (a -> m b) -> PrimOr a -> m (PrimOr b) #

sequence :: Monad m => PrimOr (m a) -> m (PrimOr a) #

Eq a => Eq (PrimOr a) Source # 

Methods

(==) :: PrimOr a -> PrimOr a -> Bool #

(/=) :: PrimOr a -> PrimOr a -> Bool #

Ord a => Ord (PrimOr a) Source # 

Methods

compare :: PrimOr a -> PrimOr a -> Ordering #

(<) :: PrimOr a -> PrimOr a -> Bool #

(<=) :: PrimOr a -> PrimOr a -> Bool #

(>) :: PrimOr a -> PrimOr a -> Bool #

(>=) :: PrimOr a -> PrimOr a -> Bool #

max :: PrimOr a -> PrimOr a -> PrimOr a #

min :: PrimOr a -> PrimOr a -> PrimOr a #

Show a => Show (PrimOr a) Source # 

Methods

showsPrec :: Int -> PrimOr a -> ShowS #

show :: PrimOr a -> String #

showList :: [PrimOr a] -> ShowS #

Generic (PrimOr a) Source # 

Associated Types

type Rep (PrimOr a) :: * -> * #

Methods

from :: PrimOr a -> Rep (PrimOr a) x #

to :: Rep (PrimOr a) x -> PrimOr a #

Hashable a => Hashable (PrimOr a) Source # 

Methods

hashWithSalt :: Int -> PrimOr a -> Int #

hash :: PrimOr a -> Int #

type Rep (PrimOr a) Source # 
type Rep (PrimOr a) = D1 * (MetaData "PrimOr" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" True) (C1 * (MetaCons "PrimOr" PrefixI True) (S1 * (MetaSel (Just Symbol "unPrimOr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Either Prim a))))

data MainExp a Source #

Constructors

EmptyExp 
ExpPrim Prim

Primitives

Tfm Info [a]

Application of the opcode: we have opcode information (Info) and the arguments [a]

ConvertRate Rate Rate a

Rate conversion

Select Rate Int a

Selects a cell from the tuple, here argument is always a tuple (result of opcode that returns several outputs)

If (CondInfo a) a a

if-then-else

ExpBool (BoolExp a)

Boolean expressions (rendered in infix notation in the Csound)

ExpNum (NumExp a)

Numerical expressions (rendered in infix notation in the Csound)

InitVar Var a

Reading/writing a named variable

ReadVar Var 
WriteVar Var a 
InitArr Var (ArrSize a)

Arrays

ReadArr Var (ArrIndex a) 
WriteArr Var (ArrIndex a) a 
WriteInitArr Var (ArrIndex a) a 
TfmArr IsArrInit Var Info [a] 
IfBegin Rate (CondInfo a)

Imperative If-then-else

ElseBegin 
IfEnd 
UntilBegin (CondInfo a)

looping constructions

UntilEnd 
WhileBegin (CondInfo a) 
WhileRefBegin Var 
WhileEnd 
Verbatim String

Verbatim stmt

Starts

Dependency tracking

Seq a a 
Ends a 
InitMacrosInt String Int

read macros arguments

InitMacrosDouble String Double 
InitMacrosString String String 
ReadMacrosInt String 
ReadMacrosDouble String 
ReadMacrosString String 

Instances

Functor MainExp Source # 

Methods

fmap :: (a -> b) -> MainExp a -> MainExp b #

(<$) :: a -> MainExp b -> MainExp a #

Foldable MainExp Source # 

Methods

fold :: Monoid m => MainExp m -> m #

foldMap :: Monoid m => (a -> m) -> MainExp a -> m #

foldr :: (a -> b -> b) -> b -> MainExp a -> b #

foldr' :: (a -> b -> b) -> b -> MainExp a -> b #

foldl :: (b -> a -> b) -> b -> MainExp a -> b #

foldl' :: (b -> a -> b) -> b -> MainExp a -> b #

foldr1 :: (a -> a -> a) -> MainExp a -> a #

foldl1 :: (a -> a -> a) -> MainExp a -> a #

toList :: MainExp a -> [a] #

null :: MainExp a -> Bool #

length :: MainExp a -> Int #

elem :: Eq a => a -> MainExp a -> Bool #

maximum :: Ord a => MainExp a -> a #

minimum :: Ord a => MainExp a -> a #

sum :: Num a => MainExp a -> a #

product :: Num a => MainExp a -> a #

Traversable MainExp Source # 

Methods

traverse :: Applicative f => (a -> f b) -> MainExp a -> f (MainExp b) #

sequenceA :: Applicative f => MainExp (f a) -> f (MainExp a) #

mapM :: Monad m => (a -> m b) -> MainExp a -> m (MainExp b) #

sequence :: Monad m => MainExp (m a) -> m (MainExp a) #

Eq a => Eq (MainExp a) Source # 

Methods

(==) :: MainExp a -> MainExp a -> Bool #

(/=) :: MainExp a -> MainExp a -> Bool #

Ord a => Ord (MainExp a) Source # 

Methods

compare :: MainExp a -> MainExp a -> Ordering #

(<) :: MainExp a -> MainExp a -> Bool #

(<=) :: MainExp a -> MainExp a -> Bool #

(>) :: MainExp a -> MainExp a -> Bool #

(>=) :: MainExp a -> MainExp a -> Bool #

max :: MainExp a -> MainExp a -> MainExp a #

min :: MainExp a -> MainExp a -> MainExp a #

Show a => Show (MainExp a) Source # 

Methods

showsPrec :: Int -> MainExp a -> ShowS #

show :: MainExp a -> String #

showList :: [MainExp a] -> ShowS #

Generic (MainExp a) Source # 

Associated Types

type Rep (MainExp a) :: * -> * #

Methods

from :: MainExp a -> Rep (MainExp a) x #

to :: Rep (MainExp a) x -> MainExp a #

Hashable a => Hashable (MainExp a) Source # 

Methods

hashWithSalt :: Int -> MainExp a -> Int #

hash :: MainExp a -> Int #

type Rep (MainExp a) Source # 
type Rep (MainExp a) = D1 * (MetaData "MainExp" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "EmptyExp" PrefixI False) (U1 *)) (C1 * (MetaCons "ExpPrim" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Prim)))) ((:+:) * (C1 * (MetaCons "Tfm" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Info)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [a])))) (C1 * (MetaCons "ConvertRate" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Rate)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Rate)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Select" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Rate)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))) (C1 * (MetaCons "If" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (CondInfo a))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))))) ((:+:) * (C1 * (MetaCons "ExpBool" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (BoolExp a)))) (C1 * (MetaCons "ExpNum" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NumExp a))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "InitVar" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))) (C1 * (MetaCons "ReadVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)))) ((:+:) * (C1 * (MetaCons "WriteVar" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))) (C1 * (MetaCons "InitArr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ArrSize a))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ReadArr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ArrIndex a))))) (C1 * (MetaCons "WriteArr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ArrIndex a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))))) ((:+:) * (C1 * (MetaCons "WriteInitArr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ArrIndex a))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))) ((:+:) * (C1 * (MetaCons "TfmArr" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IsArrInit)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Info)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [a]))))) (C1 * (MetaCons "IfBegin" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Rate)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (CondInfo a)))))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ElseBegin" PrefixI False) (U1 *)) (C1 * (MetaCons "IfEnd" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "UntilBegin" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (CondInfo a)))) (C1 * (MetaCons "UntilEnd" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "WhileBegin" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (CondInfo a)))) (C1 * (MetaCons "WhileRefBegin" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Var)))) ((:+:) * (C1 * (MetaCons "WhileEnd" PrefixI False) (U1 *)) (C1 * (MetaCons "Verbatim" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Starts" PrefixI False) (U1 *)) (C1 * (MetaCons "Seq" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))) ((:+:) * (C1 * (MetaCons "Ends" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))) (C1 * (MetaCons "InitMacrosInt" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "InitMacrosDouble" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))) (C1 * (MetaCons "InitMacrosString" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))) ((:+:) * (C1 * (MetaCons "ReadMacrosInt" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:+:) * (C1 * (MetaCons "ReadMacrosDouble" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "ReadMacrosString" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))))))

data InstrId Source #

An instrument identifier

Instances

Eq InstrId Source # 

Methods

(==) :: InstrId -> InstrId -> Bool #

(/=) :: InstrId -> InstrId -> Bool #

Ord InstrId Source # 
Show InstrId Source # 
Generic InstrId Source # 

Associated Types

type Rep InstrId :: * -> * #

Methods

from :: InstrId -> Rep InstrId x #

to :: Rep InstrId x -> InstrId #

Hashable InstrId Source # 

Methods

hashWithSalt :: Int -> InstrId -> Int #

hash :: InstrId -> Int #

type Rep InstrId Source # 
type Rep InstrId = D1 * (MetaData "InstrId" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * (C1 * (MetaCons "InstrId" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "instrIdFrac") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "instrIdCeil") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) (C1 * (MetaCons "InstrLabel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

intInstrId :: Int -> InstrId Source #

Constructs an instrument id with the integer.

ratioInstrId :: Int -> Int -> InstrId Source #

Constructs an instrument id with fractional part.

stringInstrId :: String -> InstrId Source #

Constructs an instrument id with the string label.

data VarType Source #

Constructors

LocalVar 
GlobalVar 

Instances

Eq VarType Source # 

Methods

(==) :: VarType -> VarType -> Bool #

(/=) :: VarType -> VarType -> Bool #

Ord VarType Source # 
Show VarType Source # 
Generic VarType Source # 

Associated Types

type Rep VarType :: * -> * #

Methods

from :: VarType -> Rep VarType x #

to :: Rep VarType x -> VarType #

Hashable VarType Source # 

Methods

hashWithSalt :: Int -> VarType -> Int #

hash :: VarType -> Int #

type Rep VarType Source # 
type Rep VarType = D1 * (MetaData "VarType" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * (C1 * (MetaCons "LocalVar" PrefixI False) (U1 *)) (C1 * (MetaCons "GlobalVar" PrefixI False) (U1 *)))

data Var Source #

Constructors

Var 

Fields

VarVerbatim 

Fields

Instances

Eq Var Source # 

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Ord Var Source # 

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Show Var Source # 

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Generic Var Source # 

Associated Types

type Rep Var :: * -> * #

Methods

from :: Var -> Rep Var x #

to :: Rep Var x -> Var #

Hashable Var Source # 

Methods

hashWithSalt :: Int -> Var -> Int #

hash :: Var -> Int #

type Rep Var Source # 

data Info Source #

Instances

Eq Info Source # 

Methods

(==) :: Info -> Info -> Bool #

(/=) :: Info -> Info -> Bool #

Ord Info Source # 

Methods

compare :: Info -> Info -> Ordering #

(<) :: Info -> Info -> Bool #

(<=) :: Info -> Info -> Bool #

(>) :: Info -> Info -> Bool #

(>=) :: Info -> Info -> Bool #

max :: Info -> Info -> Info #

min :: Info -> Info -> Info #

Show Info Source # 

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Generic Info Source # 

Associated Types

type Rep Info :: * -> * #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Hashable Info Source # 

Methods

hashWithSalt :: Int -> Info -> Int #

hash :: Info -> Int #

type Rep Info Source # 
type Rep Info = D1 * (MetaData "Info" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) (C1 * (MetaCons "Info" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "infoName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) ((:*:) * (S1 * (MetaSel (Just Symbol "infoSignature") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Signature)) (S1 * (MetaSel (Just Symbol "infoOpcFixity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OpcFixity)))))

data OpcFixity Source #

Constructors

Prefix 
Infix 
Opcode 

Instances

Eq OpcFixity Source # 
Ord OpcFixity Source # 
Show OpcFixity Source # 
Generic OpcFixity Source # 

Associated Types

type Rep OpcFixity :: * -> * #

Hashable OpcFixity Source # 
type Rep OpcFixity Source # 
type Rep OpcFixity = D1 * (MetaData "OpcFixity" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * (C1 * (MetaCons "Prefix" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Infix" PrefixI False) (U1 *)) (C1 * (MetaCons "Opcode" PrefixI False) (U1 *))))

data Rate Source #

The Csound rates.

Constructors

Xr 
Ar 
Kr 
Ir 
Sr 
Fr 
Wr 
Tvar 

Instances

Bounded Rate Source # 
Enum Rate Source # 

Methods

succ :: Rate -> Rate #

pred :: Rate -> Rate #

toEnum :: Int -> Rate #

fromEnum :: Rate -> Int #

enumFrom :: Rate -> [Rate] #

enumFromThen :: Rate -> Rate -> [Rate] #

enumFromTo :: Rate -> Rate -> [Rate] #

enumFromThenTo :: Rate -> Rate -> Rate -> [Rate] #

Eq Rate Source # 

Methods

(==) :: Rate -> Rate -> Bool #

(/=) :: Rate -> Rate -> Bool #

Ord Rate Source # 

Methods

compare :: Rate -> Rate -> Ordering #

(<) :: Rate -> Rate -> Bool #

(<=) :: Rate -> Rate -> Bool #

(>) :: Rate -> Rate -> Bool #

(>=) :: Rate -> Rate -> Bool #

max :: Rate -> Rate -> Rate #

min :: Rate -> Rate -> Rate #

Show Rate Source # 

Methods

showsPrec :: Int -> Rate -> ShowS #

show :: Rate -> String #

showList :: [Rate] -> ShowS #

Generic Rate Source # 

Associated Types

type Rep Rate :: * -> * #

Methods

from :: Rate -> Rep Rate x #

to :: Rep Rate x -> Rate #

Hashable Rate Source # 

Methods

hashWithSalt :: Int -> Rate -> Int #

hash :: Rate -> Int #

type Rep Rate Source # 
type Rep Rate = D1 * (MetaData "Rate" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Xr" PrefixI False) (U1 *)) (C1 * (MetaCons "Ar" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Kr" PrefixI False) (U1 *)) (C1 * (MetaCons "Ir" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Sr" PrefixI False) (U1 *)) (C1 * (MetaCons "Fr" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Wr" PrefixI False) (U1 *)) (C1 * (MetaCons "Tvar" PrefixI False) (U1 *)))))

data Prim Source #

Instances

Eq Prim Source # 

Methods

(==) :: Prim -> Prim -> Bool #

(/=) :: Prim -> Prim -> Bool #

Ord Prim Source # 

Methods

compare :: Prim -> Prim -> Ordering #

(<) :: Prim -> Prim -> Bool #

(<=) :: Prim -> Prim -> Bool #

(>) :: Prim -> Prim -> Bool #

(>=) :: Prim -> Prim -> Bool #

max :: Prim -> Prim -> Prim #

min :: Prim -> Prim -> Prim #

Show Prim Source # 

Methods

showsPrec :: Int -> Prim -> ShowS #

show :: Prim -> String #

showList :: [Prim] -> ShowS #

Generic Prim Source # 

Associated Types

type Rep Prim :: * -> * #

Methods

from :: Prim -> Rep Prim x #

to :: Rep Prim x -> Prim #

Hashable Prim Source # 

Methods

hashWithSalt :: Int -> Prim -> Int #

hash :: Prim -> Int #

type Rep Prim Source # 

data Gen Source #

Constructors

Gen 

Instances

Eq Gen Source # 

Methods

(==) :: Gen -> Gen -> Bool #

(/=) :: Gen -> Gen -> Bool #

Ord Gen Source # 

Methods

compare :: Gen -> Gen -> Ordering #

(<) :: Gen -> Gen -> Bool #

(<=) :: Gen -> Gen -> Bool #

(>) :: Gen -> Gen -> Bool #

(>=) :: Gen -> Gen -> Bool #

max :: Gen -> Gen -> Gen #

min :: Gen -> Gen -> Gen #

Show Gen Source # 

Methods

showsPrec :: Int -> Gen -> ShowS #

show :: Gen -> String #

showList :: [Gen] -> ShowS #

Generic Gen Source # 

Associated Types

type Rep Gen :: * -> * #

Methods

from :: Gen -> Rep Gen x #

to :: Rep Gen x -> Gen #

Hashable Gen Source # 

Methods

hashWithSalt :: Int -> Gen -> Int #

hash :: Gen -> Int #

type Rep Gen Source # 

data GenId Source #

Instances

Eq GenId Source # 

Methods

(==) :: GenId -> GenId -> Bool #

(/=) :: GenId -> GenId -> Bool #

Ord GenId Source # 

Methods

compare :: GenId -> GenId -> Ordering #

(<) :: GenId -> GenId -> Bool #

(<=) :: GenId -> GenId -> Bool #

(>) :: GenId -> GenId -> Bool #

(>=) :: GenId -> GenId -> Bool #

max :: GenId -> GenId -> GenId #

min :: GenId -> GenId -> GenId #

Show GenId Source # 

Methods

showsPrec :: Int -> GenId -> ShowS #

show :: GenId -> String #

showList :: [GenId] -> ShowS #

Generic GenId Source # 

Associated Types

type Rep GenId :: * -> * #

Methods

from :: GenId -> Rep GenId x #

to :: Rep GenId x -> GenId #

Hashable GenId Source # 

Methods

hashWithSalt :: Int -> GenId -> Int #

hash :: GenId -> Int #

type Rep GenId Source # 
type Rep GenId = D1 * (MetaData "GenId" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * (C1 * (MetaCons "IntGenId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "StringGenId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

data Inline a b Source #

Constructors

Inline 

Fields

Instances

Functor (Inline a) Source # 

Methods

fmap :: (a -> b) -> Inline a a -> Inline a b #

(<$) :: a -> Inline a b -> Inline a a #

Foldable (Inline a) Source # 

Methods

fold :: Monoid m => Inline a m -> m #

foldMap :: Monoid m => (a -> m) -> Inline a a -> m #

foldr :: (a -> b -> b) -> b -> Inline a a -> b #

foldr' :: (a -> b -> b) -> b -> Inline a a -> b #

foldl :: (b -> a -> b) -> b -> Inline a a -> b #

foldl' :: (b -> a -> b) -> b -> Inline a a -> b #

foldr1 :: (a -> a -> a) -> Inline a a -> a #

foldl1 :: (a -> a -> a) -> Inline a a -> a #

toList :: Inline a a -> [a] #

null :: Inline a a -> Bool #

length :: Inline a a -> Int #

elem :: Eq a => a -> Inline a a -> Bool #

maximum :: Ord a => Inline a a -> a #

minimum :: Ord a => Inline a a -> a #

sum :: Num a => Inline a a -> a #

product :: Num a => Inline a a -> a #

Traversable (Inline a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Inline a a -> f (Inline a b) #

sequenceA :: Applicative f => Inline a (f a) -> f (Inline a a) #

mapM :: Monad m => (a -> m b) -> Inline a a -> m (Inline a b) #

sequence :: Monad m => Inline a (m a) -> m (Inline a a) #

(Eq b, Eq a) => Eq (Inline a b) Source # 

Methods

(==) :: Inline a b -> Inline a b -> Bool #

(/=) :: Inline a b -> Inline a b -> Bool #

(Ord b, Ord a) => Ord (Inline a b) Source # 

Methods

compare :: Inline a b -> Inline a b -> Ordering #

(<) :: Inline a b -> Inline a b -> Bool #

(<=) :: Inline a b -> Inline a b -> Bool #

(>) :: Inline a b -> Inline a b -> Bool #

(>=) :: Inline a b -> Inline a b -> Bool #

max :: Inline a b -> Inline a b -> Inline a b #

min :: Inline a b -> Inline a b -> Inline a b #

(Show b, Show a) => Show (Inline a b) Source # 

Methods

showsPrec :: Int -> Inline a b -> ShowS #

show :: Inline a b -> String #

showList :: [Inline a b] -> ShowS #

(Hashable a, Hashable b) => Hashable (Inline a b) Source # 

Methods

hashWithSalt :: Int -> Inline a b -> Int #

hash :: Inline a b -> Int #

data InlineExp a Source #

Constructors

InlinePrim Int 
InlineExp a [InlineExp a] 

Instances

Eq a => Eq (InlineExp a) Source # 

Methods

(==) :: InlineExp a -> InlineExp a -> Bool #

(/=) :: InlineExp a -> InlineExp a -> Bool #

Ord a => Ord (InlineExp a) Source # 
Show a => Show (InlineExp a) Source # 
Generic (InlineExp a) Source # 

Associated Types

type Rep (InlineExp a) :: * -> * #

Methods

from :: InlineExp a -> Rep (InlineExp a) x #

to :: Rep (InlineExp a) x -> InlineExp a #

Hashable a => Hashable (InlineExp a) Source # 

Methods

hashWithSalt :: Int -> InlineExp a -> Int #

hash :: InlineExp a -> Int #

type Rep (InlineExp a) Source # 
type Rep (InlineExp a) = D1 * (MetaData "InlineExp" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * (C1 * (MetaCons "InlinePrim" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "InlineExp" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [InlineExp a])))))

data PreInline a b Source #

Constructors

PreInline a [b] 

Instances

Functor (PreInline a) Source # 

Methods

fmap :: (a -> b) -> PreInline a a -> PreInline a b #

(<$) :: a -> PreInline a b -> PreInline a a #

Foldable (PreInline a) Source # 

Methods

fold :: Monoid m => PreInline a m -> m #

foldMap :: Monoid m => (a -> m) -> PreInline a a -> m #

foldr :: (a -> b -> b) -> b -> PreInline a a -> b #

foldr' :: (a -> b -> b) -> b -> PreInline a a -> b #

foldl :: (b -> a -> b) -> b -> PreInline a a -> b #

foldl' :: (b -> a -> b) -> b -> PreInline a a -> b #

foldr1 :: (a -> a -> a) -> PreInline a a -> a #

foldl1 :: (a -> a -> a) -> PreInline a a -> a #

toList :: PreInline a a -> [a] #

null :: PreInline a a -> Bool #

length :: PreInline a a -> Int #

elem :: Eq a => a -> PreInline a a -> Bool #

maximum :: Ord a => PreInline a a -> a #

minimum :: Ord a => PreInline a a -> a #

sum :: Num a => PreInline a a -> a #

product :: Num a => PreInline a a -> a #

Traversable (PreInline a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> PreInline a a -> f (PreInline a b) #

sequenceA :: Applicative f => PreInline a (f a) -> f (PreInline a a) #

mapM :: Monad m => (a -> m b) -> PreInline a a -> m (PreInline a b) #

sequence :: Monad m => PreInline a (m a) -> m (PreInline a a) #

(Eq b, Eq a) => Eq (PreInline a b) Source # 

Methods

(==) :: PreInline a b -> PreInline a b -> Bool #

(/=) :: PreInline a b -> PreInline a b -> Bool #

(Ord b, Ord a) => Ord (PreInline a b) Source # 

Methods

compare :: PreInline a b -> PreInline a b -> Ordering #

(<) :: PreInline a b -> PreInline a b -> Bool #

(<=) :: PreInline a b -> PreInline a b -> Bool #

(>) :: PreInline a b -> PreInline a b -> Bool #

(>=) :: PreInline a b -> PreInline a b -> Bool #

max :: PreInline a b -> PreInline a b -> PreInline a b #

min :: PreInline a b -> PreInline a b -> PreInline a b #

(Show b, Show a) => Show (PreInline a b) Source # 

Methods

showsPrec :: Int -> PreInline a b -> ShowS #

show :: PreInline a b -> String #

showList :: [PreInline a b] -> ShowS #

Generic (PreInline a b) Source # 

Associated Types

type Rep (PreInline a b) :: * -> * #

Methods

from :: PreInline a b -> Rep (PreInline a b) x #

to :: Rep (PreInline a b) x -> PreInline a b #

(Hashable a, Hashable b) => Hashable (PreInline a b) Source # 

Methods

hashWithSalt :: Int -> PreInline a b -> Int #

hash :: PreInline a b -> Int #

type Rep (PreInline a b) Source # 
type Rep (PreInline a b) = D1 * (MetaData "PreInline" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) (C1 * (MetaCons "PreInline" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [b]))))

data CondOp Source #

Instances

Eq CondOp Source # 

Methods

(==) :: CondOp -> CondOp -> Bool #

(/=) :: CondOp -> CondOp -> Bool #

Ord CondOp Source # 
Show CondOp Source # 
Generic CondOp Source # 

Associated Types

type Rep CondOp :: * -> * #

Methods

from :: CondOp -> Rep CondOp x #

to :: Rep CondOp x -> CondOp #

Hashable CondOp Source # 

Methods

hashWithSalt :: Int -> CondOp -> Int #

hash :: CondOp -> Int #

type Rep CondOp Source # 
type Rep CondOp = D1 * (MetaData "CondOp" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "TrueOp" PrefixI False) (U1 *)) (C1 * (MetaCons "FalseOp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "And" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Or" PrefixI False) (U1 *)) (C1 * (MetaCons "Equals" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NotEquals" PrefixI False) (U1 *)) (C1 * (MetaCons "Less" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Greater" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LessEquals" PrefixI False) (U1 *)) (C1 * (MetaCons "GreaterEquals" PrefixI False) (U1 *))))))

data NumOp Source #

Constructors

Add 
Sub 
Neg 
Mul 
Div 
Pow 
Mod 

Instances

Eq NumOp Source # 

Methods

(==) :: NumOp -> NumOp -> Bool #

(/=) :: NumOp -> NumOp -> Bool #

Ord NumOp Source # 

Methods

compare :: NumOp -> NumOp -> Ordering #

(<) :: NumOp -> NumOp -> Bool #

(<=) :: NumOp -> NumOp -> Bool #

(>) :: NumOp -> NumOp -> Bool #

(>=) :: NumOp -> NumOp -> Bool #

max :: NumOp -> NumOp -> NumOp #

min :: NumOp -> NumOp -> NumOp #

Show NumOp Source # 

Methods

showsPrec :: Int -> NumOp -> ShowS #

show :: NumOp -> String #

showList :: [NumOp] -> ShowS #

Generic NumOp Source # 

Associated Types

type Rep NumOp :: * -> * #

Methods

from :: NumOp -> Rep NumOp x #

to :: Rep NumOp x -> NumOp #

Hashable NumOp Source # 

Methods

hashWithSalt :: Int -> NumOp -> Int #

hash :: NumOp -> Int #

type Rep NumOp Source # 
type Rep NumOp = D1 * (MetaData "NumOp" "Csound.Dynamic.Types.Exp" "csound-expression-dynamic-0.3.3-Ah2yDN32ZW47UJrEVhMUCq" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Add" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Sub" PrefixI False) (U1 *)) (C1 * (MetaCons "Neg" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Mul" PrefixI False) (U1 *)) (C1 * (MetaCons "Div" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Pow" PrefixI False) (U1 *)) (C1 * (MetaCons "Mod" PrefixI False) (U1 *)))))

type Note = [Prim] Source #

type MultiOut a = Int -> a Source #

Multiple output. Specify the number of outputs to get the result.

type ArrSize a = [a] Source #

type ArrIndex a = [a] Source #