csound-expression-typed-0.2.0.1: typed core for the library csound-expression

Safe HaskellNone
LanguageHaskell2010

Csound.Typed.Types.Lift

Contents

Synopsis

Documentation

data GE a Source #

Instances

Monad GE Source # 

Methods

(>>=) :: GE a -> (a -> GE b) -> GE b #

(>>) :: GE a -> GE b -> GE b #

return :: a -> GE a #

fail :: String -> GE a #

Functor GE Source # 

Methods

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

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

Applicative GE Source # 

Methods

pure :: a -> GE a #

(<*>) :: GE (a -> b) -> GE a -> GE b #

(*>) :: GE a -> GE b -> GE b #

(<*) :: GE a -> GE b -> GE a #

MonadIO GE Source # 

Methods

liftIO :: IO a -> GE a #

DirtySingle (SE (GE E)) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE (GE E)

PureSingle (GE E) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> GE E

DirtyMulti b => DirtyMulti (GE [E] -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> GE [E] -> b

DirtyMulti b => DirtyMulti (GE E -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> GE E -> b

PureMulti b => PureMulti (GE [E] -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> GE [E] -> b

PureMulti b => PureMulti (GE E -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> GE E -> b

Procedure b => Procedure (GE [E] -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> GE [E] -> b

Procedure b => Procedure (GE E -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> GE E -> b

DirtySingle b => DirtySingle (GE [E] -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> GE [E] -> b

DirtySingle b => DirtySingle (GE E -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> GE E -> b

PureSingle b => PureSingle (GE [E] -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> GE [E] -> b

PureSingle b => PureSingle (GE E -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> GE E -> b

type E = Fix RatedExp #

The inner representation of csound expressions.

Lifters

Pure single

class PureSingle a Source #

Minimal complete definition

pureSingleGE

Instances

PureSingle Tab Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Tab

PureSingle Wspec Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Wspec

PureSingle Spec Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Spec

PureSingle Str Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Str

PureSingle D Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> D

PureSingle Sig Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Sig

PureSingle (GE E) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> GE E

PureSingle b => PureSingle ([D] -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> [D] -> b

PureSingle b => PureSingle ([Sig] -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> [Sig] -> b

PureSingle b => PureSingle (Msg -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Msg -> b

PureSingle b => PureSingle (GE [E] -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> GE [E] -> b

PureSingle b => PureSingle (GE E -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> GE E -> b

PureSingle b => PureSingle (Tab -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Tab -> b

PureSingle b => PureSingle (Wspec -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Wspec -> b

PureSingle b => PureSingle (Spec -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Spec -> b

PureSingle b => PureSingle (Str -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Str -> b

PureSingle b => PureSingle (D -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> D -> b

PureSingle b => PureSingle (Sig -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Sig -> b

pureSingle :: PureSingle a => ([E] -> E) -> a Source #

Dirty single

class DirtySingle a Source #

Minimal complete definition

dirtySingleGE

Instances

DirtySingle (SE (GE E)) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE (GE E)

DirtySingle (SE Tab) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Tab

DirtySingle (SE Wspec) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Wspec

DirtySingle (SE Spec) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Spec

DirtySingle (SE Str) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Str

DirtySingle (SE D) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE D

DirtySingle (SE Sig) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Sig

DirtySingle b => DirtySingle ([D] -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> [D] -> b

DirtySingle b => DirtySingle ([Sig] -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> [Sig] -> b

DirtySingle b => DirtySingle (Msg -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Msg -> b

DirtySingle b => DirtySingle (GE [E] -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> GE [E] -> b

DirtySingle b => DirtySingle (GE E -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> GE E -> b

DirtySingle b => DirtySingle (Tab -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Tab -> b

DirtySingle b => DirtySingle (Wspec -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Wspec -> b

DirtySingle b => DirtySingle (Spec -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Spec -> b

DirtySingle b => DirtySingle (Str -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Str -> b

DirtySingle b => DirtySingle (D -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> D -> b

DirtySingle b => DirtySingle (Sig -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Sig -> b

dirtySingle :: DirtySingle a => ([E] -> Dep E) -> a Source #

Procedure

class Procedure a Source #

Minimal complete definition

procedureGE

Instances

Procedure (SE ()) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> SE ()

Procedure b => Procedure ([D] -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> [D] -> b

Procedure b => Procedure ([Sig] -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> [Sig] -> b

Procedure b => Procedure (Msg -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> Msg -> b

Procedure b => Procedure (GE [E] -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> GE [E] -> b

Procedure b => Procedure (GE E -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> GE E -> b

Procedure b => Procedure (Tab -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> Tab -> b

Procedure b => Procedure (Wspec -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> Wspec -> b

Procedure b => Procedure (Spec -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> Spec -> b

Procedure b => Procedure (Str -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> Str -> b

Procedure b => Procedure (D -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> D -> b

Procedure b => Procedure (Sig -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> Sig -> b

procedure :: Procedure a => ([E] -> Dep ()) -> a Source #

Pure multi

class PureMulti a Source #

Minimal complete definition

pureMultiGE

Instances

PureMulti Pm Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Pm

PureMulti b => PureMulti ([D] -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> [D] -> b

PureMulti b => PureMulti ([Sig] -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> [Sig] -> b

PureMulti b => PureMulti (Msg -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Msg -> b

PureMulti b => PureMulti (GE [E] -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> GE [E] -> b

PureMulti b => PureMulti (GE E -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> GE E -> b

PureMulti b => PureMulti (Tab -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Tab -> b

PureMulti b => PureMulti (Wspec -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Wspec -> b

PureMulti b => PureMulti (Spec -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Spec -> b

PureMulti b => PureMulti (Str -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Str -> b

PureMulti b => PureMulti (D -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> D -> b

PureMulti b => PureMulti (Sig -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Sig -> b

data Pm Source #

Instances

PureMulti Pm Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Pm

fromPm :: Tuple a => Pm -> a Source #

pureMulti :: PureMulti a => ([E] -> MultiOut [E]) -> a Source #

Dirty multi

class DirtyMulti a Source #

Minimal complete definition

dirtyMultiGE

Instances

DirtyMulti Dm Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Dm

DirtyMulti b => DirtyMulti ([D] -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> [D] -> b

DirtyMulti b => DirtyMulti ([Sig] -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> [Sig] -> b

DirtyMulti b => DirtyMulti (Msg -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Msg -> b

DirtyMulti b => DirtyMulti (GE [E] -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> GE [E] -> b

DirtyMulti b => DirtyMulti (GE E -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> GE E -> b

DirtyMulti b => DirtyMulti (Tab -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Tab -> b

DirtyMulti b => DirtyMulti (Wspec -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Wspec -> b

DirtyMulti b => DirtyMulti (Spec -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Spec -> b

DirtyMulti b => DirtyMulti (Str -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Str -> b

DirtyMulti b => DirtyMulti (D -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> D -> b

DirtyMulti b => DirtyMulti (Sig -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Sig -> b

data Dm Source #

Instances

DirtyMulti Dm Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Dm

fromDm :: Tuple a => Dm -> SE a Source #

dirtyMulti :: DirtyMulti a => ([E] -> MultiOut (Dep [E])) -> a Source #