csound-expression-5.3.3: library to make electronic music

Safe HaskellNone
LanguageHaskell2010

Csound.Control.Instr

Contents

Description

We can convert notes to sound signals with instruments. An instrument is a function:

(Arg a, Sigs b) => a -> SE b

It takes a tuple of primitive Csound values (number, string or array) and converts it to the tuple of signals and it makes some side effects along the way so the output is wrapped in the SE-monad.

There are only three ways of making a sound with an instrument:

  • Suplpy an instrument with notes (Mix-section).
  • Trigger an instrument with event stream (Evt-section).
  • By using midi-instruments (see Csound.Control.Midi).

Sometimes we don't want to produce any sound. Our instrument is just a procedure that makes something useful without being noisy about it. It's type is:

(Arg a) => a -> SE ()

To invoke the procedures there are functions with trailing underscore. For example we have the function trig to convert event stream to sound:

trig :: (Arg a, Sigs b) => (a -> SE b) -> Evts (D, D, a) -> b

and we have a trig with underscore to convert the event stream to the sequence of the procedure invkations:

trig_ :: (Arg a) => (a -> SE ()) -> Evts (D, D, a) -> SE ()

To invoke instruments from another instrumetnts we use artificial closures made with functions with trailing xxxBy. For example:

trigBy :: (Arg a, Arg c, Sigs b) => (a -> SE b) -> (c -> Evts (D, D, a)) -> (c -> b)

Notice that the event stream depends on the argument of the type c. Here goes all the parameters that we want to pass from the outer instrument. Unfortunately we can not just create the closure, because our values are not the real values. It's a text of the programm (a tiny snippet of it) to be executed. For a time being I don't know how to make it better. So we need to pass the values explicitly.

For example, if we want to make an arpeggiator:

pureTone :: D -> SE Sig
pureTone cps = return $ mul env $ osc $ sig cps
   where env = linseg [0, 0.01, 1, 0.25, 0]

majArpeggio :: D -> SE Sig
majArpeggio = return . schedBy pureTone evts
    where evts cps = withDur 0.5 $ fmap (* cps) $ cycleE [1, 5/3, 3/2, 2] $ metroE 5

main = dac $ mul 0.5 $ midi $ onMsg majArpeggio

We should use schedBy to pass the frequency as a parameter to the event stream.

Synopsis

Mix

We can invoke instrument with specified notes. Eqch note happens at some time and lasts for some time. It contains the argument for the instrument.

We can invoke the instrument on the sequence of notes (sco), process the sequence of notes with an effect (eff) and convert everything in the plain sound signals (to send it to speakers or write to file or use it in some another instrument).

The sequence of notes is represented with type class CsdSco. Wich has a very simple methods. So you can use your own favorite library to describe the list of notes. If your type supports the scaling in the time domain (stretching the timeline) you can do it in the Mix-version (after the invokation of the instrument). All notes are rescaled all the way down the Score-structure.

type Sco a = Track Sig a #

data Mix a #

Special type that represents a scores of sound signals. If an instrument is triggered with the scores the result is wrapped in the value of this type.

sco :: (Arg a, Sigs b) => (a -> SE b) -> Sco a -> Sco (Mix b) #

Plays a bunch of notes with the given instrument.

res = sco instrument scores

mix :: Sigs a => Sco (Mix a) -> a #

Renders a scores to the sound signals. we can use it inside the other instruments.

eff :: (Sigs a, Sigs b) => (a -> SE b) -> Sco (Mix a) -> Sco (Mix b) #

Applies an effect to the sound. Effect is applied to the sound on the give track.

res = eff effect sco
  • effect - a function that takes a tuple of signals and produces a tuple of signals.
  • sco - something that is constructed with sco or eff.

With the function eff you can apply a reverb or adjust the level of the signal. It functions like a mixing board but unlike mixing board it produces the value that you can arrange with functions from your favorite Score-generation library. You can delay it or mix with some other track and apply some another effect on top of it!

monoSco :: Sigs a => (MonoArg -> SE a) -> Sco (D, D) -> Sco (Mix a) #

Plays a bunch of notes with the given monophonic instrument. See details on type MonoArg. The scores contain the pairs of amplitude (0 to 1) and frequency (in Hz).

res = monoSco instrument scores

mixLoop :: Sigs a => Sco (Mix a) -> a Source #

Mixes the scores and plays them in the loop.

sco_ :: Arg a => (a -> SE ()) -> Sco a -> Sco (Mix Unit) #

Invokes a procedure for the given bunch of events.

mix_ :: Sco (Mix Unit) -> SE () #

Converts a bunch of procedures scheduled with scores to a single procedure.

mixLoop_ :: Sco (Mix Unit) -> SE () Source #

Mixes the procedures and plays them in the loop.

mixBy :: (Arg a, Sigs b) => (a -> Sco (Mix b)) -> a -> b #

Imitates a closure for a bunch of notes to be played within another instrument.

infiniteDur :: Num a => a #

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

class Semigroup a => Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = '(<>)' since base-4.11.0.0.

mconcat :: [a] -> a #

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances
Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid IntSet 
Instance details

Defined in Data.IntSet.Internal

Monoid Flags 
Instance details

Defined in Csound.Dynamic.Types.Flags

Methods

mempty :: Flags #

mappend :: Flags -> Flags -> Flags #

mconcat :: [Flags] -> Flags #

Monoid AudioFileOutput 
Instance details

Defined in Csound.Dynamic.Types.Flags

Monoid IdTags 
Instance details

Defined in Csound.Dynamic.Types.Flags

Monoid MidiIO 
Instance details

Defined in Csound.Dynamic.Types.Flags

Monoid MidiRT 
Instance details

Defined in Csound.Dynamic.Types.Flags

Monoid Displays 
Instance details

Defined in Csound.Dynamic.Types.Flags

Monoid Config 
Instance details

Defined in Csound.Dynamic.Types.Flags

Monoid Props 
Instance details

Defined in Csound.Typed.Gui.Types

Methods

mempty :: Props #

mappend :: Props -> Props -> Props #

mconcat :: [Props] -> Props #

Monoid Sig 
Instance details

Defined in Csound.Typed.Types.Prim

Methods

mempty :: Sig #

mappend :: Sig -> Sig -> Sig #

mconcat :: [Sig] -> Sig #

Monoid D 
Instance details

Defined in Csound.Typed.Types.Prim

Methods

mempty :: D #

mappend :: D -> D -> D #

mconcat :: [D] -> D #

Monoid Unit 
Instance details

Defined in Csound.Typed.Types.Prim

Methods

mempty :: Unit #

mappend :: Unit -> Unit -> Unit #

mconcat :: [Unit] -> Unit #

Monoid Options 
Instance details

Defined in Csound.Typed.GlobalState.Options

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Monoid p => Monoid (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p #

mappend :: Par1 p -> Par1 p -> Par1 p #

mconcat :: [Par1 p] -> Par1 p #

(Ord a, Bounded a) => Monoid (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Monoid (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

mconcat :: [Down a] -> Down a #

Num a => Monoid (Colour a) 
Instance details

Defined in Data.Colour.Internal

Methods

mempty :: Colour a #

mappend :: Colour a -> Colour a -> Colour a #

mconcat :: [Colour a] -> Colour a #

Num a => Monoid (AlphaColour a) 
Instance details

Defined in Data.Colour.Internal

Monoid (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

Ord a => Monoid (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid (Evt a) 
Instance details

Defined in Csound.Typed.Types.Evt

Methods

mempty :: Evt a #

mappend :: Evt a -> Evt a -> Evt a #

mconcat :: [Evt a] -> Evt a #

Monoid (DList a) 
Instance details

Defined in Data.DList.Internal

Methods

mempty :: DList a #

mappend :: DList a -> DList a -> DList a #

mconcat :: [DList a] -> DList a #

Monoid (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

mempty :: Doc a #

mappend :: Doc a -> Doc a -> Doc a #

mconcat :: [Doc a] -> Doc a #

Monoid (MergeSet a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: MergeSet a #

mappend :: MergeSet a -> MergeSet a -> MergeSet a #

mconcat :: [MergeSet a] -> MergeSet a #

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

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

mconcat :: [a -> b] -> a -> b #

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

(Monoid a, Monoid b) => Monoid (a, b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Ord k => Monoid (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

Monoid (AbsScene ctx a) 
Instance details

Defined in Csound.Typed.Gui.BoxModel

Methods

mempty :: AbsScene ctx a #

mappend :: AbsScene ctx a -> AbsScene ctx a -> AbsScene ctx a #

mconcat :: [AbsScene ctx a] -> AbsScene ctx a #

(Num t, IfB t, OrdB t) => Monoid (Track t a) 
Instance details

Defined in Temporal.Media

Methods

mempty :: Track t a #

mappend :: Track t a -> Track t a -> Track t a #

mconcat :: [Track t a] -> Track t a #

Monoid (TList t a) 
Instance details

Defined in Temporal.Media

Methods

mempty :: TList t a #

mappend :: TList t a -> TList t a -> TList t a #

mconcat :: [TList t a] -> TList t a #

Monoid (f p) => Monoid (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p #

mconcat :: [Rec1 f p] -> Rec1 f p #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

mconcat :: [Const a b] -> Const a b #

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

Monoid c => Monoid (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p #

mappend :: K1 i c p -> K1 i c p -> K1 i c p #

mconcat :: [K1 i c p] -> K1 i c p #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

Monoid (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

mconcat :: [(f :.: g) p] -> (f :.: g) p #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

newtype First a #

Maybe monoid returning the leftmost non-Nothing value.

First a is isomorphic to Alt Maybe a, but precedes it historically.

>>> getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
Just "hello"

Use of this type is discouraged. Note the following equivalence:

Data.Monoid.First x === Maybe (Data.Semigroup.First x)

In addition to being equivalent in the structural sense, the two also have Monoid instances that behave the same. This type will be marked deprecated in GHC 8.8, and removed in GHC 8.10. Users are advised to use the variant from Data.Semigroup and wrap it in Maybe.

Constructors

First 

Fields

Instances
Monad First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

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

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

return :: a -> First a #

fail :: String -> First a #

Functor First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

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

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

Applicative First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> First a #

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

liftA2 :: (a -> b -> c) -> First a -> First b -> First c #

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

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

Foldable First

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

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

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

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

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

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

Traversable First

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Eq a => Eq (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

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

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

Ord a => Ord (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: First a -> First a -> Ordering #

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

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

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

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

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Read a => Read (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

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

show :: First a -> String #

showList :: [First a] -> ShowS #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type #

Methods

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

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

Semigroup (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Default (First a) 
Instance details

Defined in Data.Default.Class

Methods

def :: First a #

Generic1 First 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 First :: k -> Type #

Methods

from1 :: First a -> Rep1 First a #

to1 :: Rep1 First a -> First a #

type Rep (First a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep (First a) = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))
type Rep1 First

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep1 First = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))

newtype Last a #

Maybe monoid returning the rightmost non-Nothing value.

Last a is isomorphic to Dual (First a), and thus to Dual (Alt Maybe a)

>>> getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))
Just "world"

Use of this type is discouraged. Note the following equivalence:

Data.Monoid.Last x === Maybe (Data.Semigroup.Last x)

In addition to being equivalent in the structural sense, the two also have Monoid instances that behave the same. This type will be marked deprecated in GHC 8.8, and removed in GHC 8.10. Users are advised to use the variant from Data.Semigroup and wrap it in Maybe.

Constructors

Last 

Fields

Instances
Monad Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

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

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

return :: a -> Last a #

fail :: String -> Last a #

Functor Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

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

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

Applicative Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Last a #

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

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c #

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

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

Foldable Last

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

toList :: Last a -> [a] #

null :: Last a -> Bool #

length :: Last a -> Int #

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

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

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

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

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

Traversable Last

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Eq a => Eq (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

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

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

Ord a => Ord (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: Last a -> Last a -> Ordering #

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

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

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

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

max :: Last a -> Last a -> Last a #

min :: Last a -> Last a -> Last a #

Read a => Read (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

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

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

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

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

Semigroup (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Default (Last a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Last a #

Generic1 Last 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 Last :: k -> Type #

Methods

from1 :: Last a -> Rep1 Last a #

to1 :: Rep1 Last a -> Last a #

type Rep (Last a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep (Last a) = D1 (MetaData "Last" "Data.Monoid" "base" True) (C1 (MetaCons "Last" PrefixI True) (S1 (MetaSel (Just "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))
type Rep1 Last

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep1 Last = D1 (MetaData "Last" "Data.Monoid" "base" True) (C1 (MetaCons "Last" PrefixI True) (S1 (MetaSel (Just "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))

newtype Ap (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type #

This data type witnesses the lifting of a Monoid into an Applicative pointwise.

Since: base-4.12.0.0

Constructors

Ap 

Fields

Instances
Generic1 (Ap f :: k -> Type) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 (Ap f) :: k -> Type #

Methods

from1 :: Ap f a -> Rep1 (Ap f) a #

to1 :: Rep1 (Ap f) a -> Ap f a #

Monad f => Monad (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(>>=) :: Ap f a -> (a -> Ap f b) -> Ap f b #

(>>) :: Ap f a -> Ap f b -> Ap f b #

return :: a -> Ap f a #

fail :: String -> Ap f a #

Functor f => Functor (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b #

(<$) :: a -> Ap f b -> Ap f a #

MonadFail f => MonadFail (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fail :: String -> Ap f a #

Applicative f => Applicative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Ap f a #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c #

(*>) :: Ap f a -> Ap f b -> Ap f b #

(<*) :: Ap f a -> Ap f b -> Ap f a #

Foldable f => Foldable (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Ap f m -> m #

foldMap :: Monoid m => (a -> m) -> Ap f a -> m #

foldr :: (a -> b -> b) -> b -> Ap f a -> b #

foldr' :: (a -> b -> b) -> b -> Ap f a -> b #

foldl :: (b -> a -> b) -> b -> Ap f a -> b #

foldl' :: (b -> a -> b) -> b -> Ap f a -> b #

foldr1 :: (a -> a -> a) -> Ap f a -> a #

foldl1 :: (a -> a -> a) -> Ap f a -> a #

toList :: Ap f a -> [a] #

null :: Ap f a -> Bool #

length :: Ap f a -> Int #

elem :: Eq a => a -> Ap f a -> Bool #

maximum :: Ord a => Ap f a -> a #

minimum :: Ord a => Ap f a -> a #

sum :: Num a => Ap f a -> a #

product :: Num a => Ap f a -> a #

Traversable f => Traversable (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f0 => Ap f (f0 a) -> f0 (Ap f a) #

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

sequence :: Monad m => Ap f (m a) -> m (Ap f a) #

Alternative f => Alternative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

empty :: Ap f a #

(<|>) :: Ap f a -> Ap f a -> Ap f a #

some :: Ap f a -> Ap f [a] #

many :: Ap f a -> Ap f [a] #

MonadPlus f => MonadPlus (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mzero :: Ap f a #

mplus :: Ap f a -> Ap f a -> Ap f a #

(Applicative f, Bounded a) => Bounded (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

minBound :: Ap f a #

maxBound :: Ap f a #

Enum (f a) => Enum (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

succ :: Ap f a -> Ap f a #

pred :: Ap f a -> Ap f a #

toEnum :: Int -> Ap f a #

fromEnum :: Ap f a -> Int #

enumFrom :: Ap f a -> [Ap f a] #

enumFromThen :: Ap f a -> Ap f a -> [Ap f a] #

enumFromTo :: Ap f a -> Ap f a -> [Ap f a] #

enumFromThenTo :: Ap f a -> Ap f a -> Ap f a -> [Ap f a] #

Eq (f a) => Eq (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(==) :: Ap f a -> Ap f a -> Bool #

(/=) :: Ap f a -> Ap f a -> Bool #

(Applicative f, Num a) => Num (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(+) :: Ap f a -> Ap f a -> Ap f a #

(-) :: Ap f a -> Ap f a -> Ap f a #

(*) :: Ap f a -> Ap f a -> Ap f a #

negate :: Ap f a -> Ap f a #

abs :: Ap f a -> Ap f a #

signum :: Ap f a -> Ap f a #

fromInteger :: Integer -> Ap f a #

Ord (f a) => Ord (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

compare :: Ap f a -> Ap f a -> Ordering #

(<) :: Ap f a -> Ap f a -> Bool #

(<=) :: Ap f a -> Ap f a -> Bool #

(>) :: Ap f a -> Ap f a -> Bool #

(>=) :: Ap f a -> Ap f a -> Bool #

max :: Ap f a -> Ap f a -> Ap f a #

min :: Ap f a -> Ap f a -> Ap f a #

Read (f a) => Read (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

readsPrec :: Int -> ReadS (Ap f a) #

readList :: ReadS [Ap f a] #

readPrec :: ReadPrec (Ap f a) #

readListPrec :: ReadPrec [Ap f a] #

Show (f a) => Show (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Ap f a -> ShowS #

show :: Ap f a -> String #

showList :: [Ap f a] -> ShowS #

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

(Applicative f, Semigroup a) => Semigroup (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a #

sconcat :: NonEmpty (Ap f a) -> Ap f a #

stimes :: Integral b => b -> Ap f a -> Ap f a #

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

type Rep1 (Ap f :: k -> Type)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

type Rep1 (Ap f :: k -> Type) = D1 (MetaData "Ap" "Data.Monoid" "base" True) (C1 (MetaCons "Ap" PrefixI True) (S1 (MetaSel (Just "getAp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

type Rep (Ap f a) = D1 (MetaData "Ap" "Data.Monoid" "base" True) (C1 (MetaCons "Ap" PrefixI True) (S1 (MetaSel (Just "getAp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

newtype Dual a #

The dual of a Monoid, obtained by swapping the arguments of mappend.

>>> getDual (mappend (Dual "Hello") (Dual "World"))
"WorldHello"

Constructors

Dual 

Fields

Instances
Monad Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

return :: a -> Dual a #

fail :: String -> Dual a #

Functor Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Applicative Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Dual a #

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

liftA2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c #

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

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

Foldable Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

toList :: Dual a -> [a] #

null :: Dual a -> Bool #

length :: Dual a -> Int #

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

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

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

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

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

Traversable Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Bounded a => Bounded (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Dual a #

maxBound :: Dual a #

Eq a => Eq (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Ord a => Ord (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Dual a -> Dual a -> Ordering #

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

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

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

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

max :: Dual a -> Dual a -> Dual a #

min :: Dual a -> Dual a -> Dual a #

Read a => Read (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type #

Methods

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

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

Semigroup a => Semigroup (Dual a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a #

sconcat :: NonEmpty (Dual a) -> Dual a #

stimes :: Integral b => b -> Dual a -> Dual a #

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Default a => Default (Dual a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Dual a #

Generic1 Dual 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Dual :: k -> Type #

Methods

from1 :: Dual a -> Rep1 Dual a #

to1 :: Rep1 Dual a -> Dual a #

type Rep (Dual a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Dual a) = D1 (MetaData "Dual" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Dual" PrefixI True) (S1 (MetaSel (Just "getDual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Dual

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Dual = D1 (MetaData "Dual" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Dual" PrefixI True) (S1 (MetaSel (Just "getDual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Endo a #

The monoid of endomorphisms under composition.

>>> let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>> appEndo computation "Haskell"
"Hello, Haskell!"

Constructors

Endo 

Fields

Instances
Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type #

Methods

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

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

Semigroup (Endo a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a #

sconcat :: NonEmpty (Endo a) -> Endo a #

stimes :: Integral b => b -> Endo a -> Endo a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Default (Endo a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Endo a #

type Rep (Endo a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Endo a) = D1 (MetaData "Endo" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Endo" PrefixI True) (S1 (MetaSel (Just "appEndo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (a -> a))))

newtype All #

Boolean monoid under conjunction (&&).

>>> getAll (All True <> mempty <> All False)
False
>>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
False

Constructors

All 

Fields

Instances
Bounded All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: All #

maxBound :: All #

Eq All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Ord All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering #

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

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

(>) :: All -> All -> Bool #

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

max :: All -> All -> All #

min :: All -> All -> All #

Read All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Semigroup All

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Default All 
Instance details

Defined in Data.Default.Class

Methods

def :: All #

type Rep All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep All = D1 (MetaData "All" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "All" PrefixI True) (S1 (MetaSel (Just "getAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

newtype Any #

Boolean monoid under disjunction (||).

>>> getAny (Any True <> mempty <> Any False)
True
>>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True

Constructors

Any 

Fields

Instances
Bounded Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Any #

maxBound :: Any #

Eq Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Ord Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering #

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

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

(>) :: Any -> Any -> Bool #

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

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Read Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Semigroup Any

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

def :: Any #

type Rep Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep Any = D1 (MetaData "Any" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Any" PrefixI True) (S1 (MetaSel (Just "getAny") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

newtype Sum a #

Monoid under addition.

>>> getSum (Sum 1 <> Sum 2 <> mempty)
3

Constructors

Sum 

Fields

Instances
Monad Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

return :: a -> Sum a #

fail :: String -> Sum a #

Functor Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Applicative Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Sum a #

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

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c #

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

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

Foldable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

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

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

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

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

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

Traversable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Bounded a => Bounded (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Num a => Num (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Sum a -> Sum a -> Sum a #

(-) :: Sum a -> Sum a -> Sum a #

(*) :: Sum a -> Sum a -> Sum a #

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Ord a => Ord (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> Ordering #

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

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

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

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

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Read a => Read (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

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

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

Num a => Semigroup (Sum a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Sum a #

Generic1 Sum 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Sum :: k -> Type #

Methods

from1 :: Sum a -> Rep1 Sum a #

to1 :: Rep1 Sum a -> Sum a #

type Rep (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Sum a) = D1 (MetaData "Sum" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Sum

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Sum = D1 (MetaData "Sum" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Product a #

Monoid under multiplication.

>>> getProduct (Product 3 <> Product 4 <> mempty)
12

Constructors

Product 

Fields

Instances
Monad Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

return :: a -> Product a #

fail :: String -> Product a #

Functor Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Applicative Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Product a #

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

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c #

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

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

Foldable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

toList :: Product a -> [a] #

null :: Product a -> Bool #

length :: Product a -> Int #

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

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

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

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

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

Traversable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Bounded a => Bounded (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Num a => Num (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Product a -> Product a -> Product a #

(-) :: Product a -> Product a -> Product a #

(*) :: Product a -> Product a -> Product a #

negate :: Product a -> Product a #

abs :: Product a -> Product a #

signum :: Product a -> Product a #

fromInteger :: Integer -> Product a #

Ord a => Ord (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Product a -> Product a -> Ordering #

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

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

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

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

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Read a => Read (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

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

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

Num a => Semigroup (Product a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Num a => Default (Product a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Product a #

Generic1 Product 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Product :: k -> Type #

Methods

from1 :: Product a -> Rep1 Product a #

to1 :: Rep1 Product a -> Product a #

type Rep (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Product a) = D1 (MetaData "Product" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Product

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Product = D1 (MetaData "Product" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Alt (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type #

Monoid under <|>.

Since: base-4.8.0.0

Constructors

Alt 

Fields

Instances
Generic1 (Alt f :: k -> Type) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 (Alt f) :: k -> Type #

Methods

from1 :: Alt f a -> Rep1 (Alt f) a #

to1 :: Rep1 (Alt f) a -> Alt f a #

Monad f => Monad (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Alt f a -> (a -> Alt f b) -> Alt f b #

(>>) :: Alt f a -> Alt f b -> Alt f b #

return :: a -> Alt f a #

fail :: String -> Alt f a #

Functor f => Functor (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b #

(<$) :: a -> Alt f b -> Alt f a #

Applicative f => Applicative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Alt f a #

(<*>) :: Alt f (a -> b) -> Alt f a -> Alt f b #

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c #

(*>) :: Alt f a -> Alt f b -> Alt f b #

(<*) :: Alt f a -> Alt f b -> Alt f a #

Foldable f => Foldable (Alt f)

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Alt f m -> m #

foldMap :: Monoid m => (a -> m) -> Alt f a -> m #

foldr :: (a -> b -> b) -> b -> Alt f a -> b #

foldr' :: (a -> b -> b) -> b -> Alt f a -> b #

foldl :: (b -> a -> b) -> b -> Alt f a -> b #

foldl' :: (b -> a -> b) -> b -> Alt f a -> b #

foldr1 :: (a -> a -> a) -> Alt f a -> a #

foldl1 :: (a -> a -> a) -> Alt f a -> a #

toList :: Alt f a -> [a] #

null :: Alt f a -> Bool #

length :: Alt f a -> Int #

elem :: Eq a => a -> Alt f a -> Bool #

maximum :: Ord a => Alt f a -> a #

minimum :: Ord a => Alt f a -> a #

sum :: Num a => Alt f a -> a #

product :: Num a => Alt f a -> a #

Traversable f => Traversable (Alt f)

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f0 => Alt f (f0 a) -> f0 (Alt f a) #

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

sequence :: Monad m => Alt f (m a) -> m (Alt f a) #

Alternative f => Alternative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

empty :: Alt f a #

(<|>) :: Alt f a -> Alt f a -> Alt f a #

some :: Alt f a -> Alt f [a] #

many :: Alt f a -> Alt f [a] #

MonadPlus f => MonadPlus (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mzero :: Alt f a #

mplus :: Alt f a -> Alt f a -> Alt f a #

Enum (f a) => Enum (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

succ :: Alt f a -> Alt f a #

pred :: Alt f a -> Alt f a #

toEnum :: Int -> Alt f a #

fromEnum :: Alt f a -> Int #

enumFrom :: Alt f a -> [Alt f a] #

enumFromThen :: Alt f a -> Alt f a -> [Alt f a] #

enumFromTo :: Alt f a -> Alt f a -> [Alt f a] #

enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] #

Eq (f a) => Eq (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Alt f a -> Alt f a -> Bool #

(/=) :: Alt f a -> Alt f a -> Bool #

Num (f a) => Num (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Alt f a -> Alt f a -> Alt f a #

(-) :: Alt f a -> Alt f a -> Alt f a #

(*) :: Alt f a -> Alt f a -> Alt f a #

negate :: Alt f a -> Alt f a #

abs :: Alt f a -> Alt f a #

signum :: Alt f a -> Alt f a #

fromInteger :: Integer -> Alt f a #

Ord (f a) => Ord (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Alt f a -> Alt f a -> Ordering #

(<) :: Alt f a -> Alt f a -> Bool #

(<=) :: Alt f a -> Alt f a -> Bool #

(>) :: Alt f a -> Alt f a -> Bool #

(>=) :: Alt f a -> Alt f a -> Bool #

max :: Alt f a -> Alt f a -> Alt f a #

min :: Alt f a -> Alt f a -> Alt f a #

Read (f a) => Read (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

readsPrec :: Int -> ReadS (Alt f a) #

readList :: ReadS [Alt f a] #

readPrec :: ReadPrec (Alt f a) #

readListPrec :: ReadPrec [Alt f a] #

Show (f a) => Show (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowS #

show :: Alt f a -> String #

showList :: [Alt f a] -> ShowS #

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type #

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Alternative f => Semigroup (Alt f a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a #

sconcat :: NonEmpty (Alt f a) -> Alt f a #

stimes :: Integral b => b -> Alt f a -> Alt f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

type Rep1 (Alt f :: k -> Type)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 (Alt f :: k -> Type) = D1 (MetaData "Alt" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Alt" PrefixI True) (S1 (MetaSel (Just "getAlt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Alt f a) = D1 (MetaData "Alt" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Alt" PrefixI True) (S1 (MetaSel (Just "getAlt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))

linfunRel :: (Ord t, Fractional t) => t -> [t] -> t -> t #

With linfunRel you can make linear interpolation function that has equal distance between points. First argument gives total length of the interpolation function and second argument gives list of values. So call

linfunRel dur [a1, a2, a3, ..., aN]

is equivalent to:

linfun [a1, dur/N, a2, dur/N, a3, ..., dur/N, aN]

linfun :: (Ord t, Fractional t) => [t] -> t -> t #

Linear interpolation. Can be useful with mapEvents for envelope changes.

linfun [a, da, b, db, c, ... ]

a, b, c ... - values

da, db, ... - duration of segments

sortEvents :: Ord t => [Event t a] -> [Event t a] #

Sorts all events by start time.

alignByZero :: Real t => [Event t a] -> [Event t a] #

Shifts all events so that minimal start time equals to zero if first event has negative start time.

sustainT :: (Ord t, Num t) => t -> Track t a -> Track t a #

Prolongated events can not exceed total track duration. All event are sustained but those that are close to end of the track are sliced. It resembles sustain on piano, when track ends you release the pedal.

sustain :: Num t => t -> Track t a -> Track t a #

After this transformation events last longer by some constant amount of time.

tmapRel :: RealFrac t => (Event t a -> b) -> Track t a -> Track t b #

Relative tmap. Time values are normalized by argument's duration.

tmap :: Real t => (Event t a -> b) -> Track t a -> Track t b #

Maps values and time stamps.

filterEvents :: Real t => (Event t a -> Bool) -> Track t a -> Track t a #

Filter track.

traverseEvents :: (Num t1, Applicative f) => (t1 -> f t2) -> (Event t1 a -> f (Event t2 b)) -> Track t1 a -> f (Track t2 b) #

mapEvents :: Num t => (Event t a -> Event t b) -> Track t a -> Track t b #

General mapping. Maps not only values but events.

within :: Real t => t -> t -> Event t a -> Bool #

Tests if given Event happens between two time stamps.

eventEnd :: Num t => Event t a -> t #

End point of event (start time plus duration).

render :: Num t => Track t a -> [Event t a] #

Get all events on recordered on the track.

singleEvent :: Num t => t -> t -> a -> Track t a #

Constructs a track that contains a single event.

singleEvent start duration content

fromEvent :: Num t => Event t a -> Track t a #

Constructs a track that contains a single event.

temp :: Num t => a -> Track t a #

temp constructs just an event. Value of type a lasts for one time unit and starts at zero.

dropT :: Real t => t -> Track t a -> Track t a #

(dropT t m) is equivalent to (slice t (dur a) a).

takeT :: Real t => t -> Track t a -> Track t a #

(takeT t) is equivalent to (slice 0 t).

slice :: Real t => t -> t -> Track t a -> Track t a #

slice cuts piece of value within given time interval. for (slice t0 t1 m), if t1 < t0 result is reversed. If t0 is negative or t1 goes beyond dur m blocks of nothing inserted so that duration of result equals to abs (t0 - t1).

reflect :: (Num t, IfB t, OrdB t) => Track t a -> Track t a #

Reversing the tracks

harTMap :: (Real t, IfB t, OrdB t) => (a -> Track t b) -> [a] -> Track t b #

Transforms a sequence and then applies a harT.

harTemp :: (Num t, IfB t, OrdB t) => [a] -> Track t a #

A chord of events. Each of them lasts for one second.

melTemp :: (Num t, IfB t, OrdB t) => [a] -> Track t a #

Analog of replicate function for tracks. Replicated tracks are played sequentially.

A melody of events. Each of them lasts for one second.

harT :: (Real t, IfB t, OrdB t) => [Track t a] -> Track t a #

Turncating parallel composition on list of tracks.

(=:/) :: (Real t, IfB t, OrdB t) => Track t a -> Track t a -> Track t a #

Turncating parallel composition. Total duration equals to minimum of the two tracks. All events that goes beyond the limit are dropped.

nil :: Monoid a => a #

Synonym for method mempty.

data Track t a #

Track is a set of Event s. There is total duration of the track, but Events can go beyond the scope of total duration (as a result of mapEvents function). Total duration is used in sequent composition of tracks.

Instances
Functor (Track t) 
Instance details

Defined in Temporal.Media

Methods

fmap :: (a -> b) -> Track t a -> Track t b #

(<$) :: a -> Track t b -> Track t a #

Foldable (Track t) 
Instance details

Defined in Temporal.Media

Methods

fold :: Monoid m => Track t m -> m #

foldMap :: Monoid m => (a -> m) -> Track t a -> m #

foldr :: (a -> b -> b) -> b -> Track t a -> b #

foldr' :: (a -> b -> b) -> b -> Track t a -> b #

foldl :: (b -> a -> b) -> b -> Track t a -> b #

foldl' :: (b -> a -> b) -> b -> Track t a -> b #

foldr1 :: (a -> a -> a) -> Track t a -> a #

foldl1 :: (a -> a -> a) -> Track t a -> a #

toList :: Track t a -> [a] #

null :: Track t a -> Bool #

length :: Track t a -> Int #

elem :: Eq a => a -> Track t a -> Bool #

maximum :: Ord a => Track t a -> a #

minimum :: Ord a => Track t a -> a #

sum :: Num a => Track t a -> a #

product :: Num a => Track t a -> a #

Traversable (Track t) 
Instance details

Defined in Temporal.Media

Methods

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

sequenceA :: Applicative f => Track t (f a) -> f (Track t a) #

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

sequence :: Monad m => Track t (m a) -> m (Track t a) #

(Eq t, Eq a) => Eq (Track t a) 
Instance details

Defined in Temporal.Media

Methods

(==) :: Track t a -> Track t a -> Bool #

(/=) :: Track t a -> Track t a -> Bool #

(Show t, Show a) => Show (Track t a) 
Instance details

Defined in Temporal.Media

Methods

showsPrec :: Int -> Track t a -> ShowS #

show :: Track t a -> String #

showList :: [Track t a] -> ShowS #

(Num t, IfB t, OrdB t) => Semigroup (Track t a) 
Instance details

Defined in Temporal.Media

Methods

(<>) :: Track t a -> Track t a -> Track t a #

sconcat :: NonEmpty (Track t a) -> Track t a #

stimes :: Integral b => b -> Track t a -> Track t a #

(Num t, IfB t, OrdB t) => Monoid (Track t a) 
Instance details

Defined in Temporal.Media

Methods

mempty :: Track t a #

mappend :: Track t a -> Track t a -> Track t a #

mconcat :: [Track t a] -> Track t a #

Duration (Track t a) 
Instance details

Defined in Temporal.Media

Methods

dur :: Track t a -> DurOf (Track t a) #

(Num t, IfB t, OrdB t) => Melody (Track t a) 
Instance details

Defined in Temporal.Media

Methods

mel :: [Track t a] -> Track t a #

(+:+) :: Track t a -> Track t a -> Track t a #

(Num t, IfB t, OrdB t) => Harmony (Track t a) 
Instance details

Defined in Temporal.Media

Methods

har :: [Track t a] -> Track t a #

(=:=) :: Track t a -> Track t a -> Track t a #

(Num t, IfB t, OrdB t) => Compose (Track t a) 
Instance details

Defined in Temporal.Media

Num t => Delay (Track t a)

Delays all events by given duration.

Instance details

Defined in Temporal.Media

Methods

del :: DurOf (Track t a) -> Track t a -> Track t a #

Num t => Stretch (Track t a)

Stretches track in time domain.

Instance details

Defined in Temporal.Media

Methods

str :: DurOf (Track t a) -> Track t a -> Track t a #

(Num t, IfB t, OrdB t) => Rest (Track t a)

Empty track that lasts for some time.

Instance details

Defined in Temporal.Media

Methods

rest :: DurOf (Track t a) -> Track t a #

type DurOf (Track t a) 
Instance details

Defined in Temporal.Media

type DurOf (Track t a) = t

data Event t a #

Constant time events. Value a starts at some time and lasts for some time.

Constructors

Event 

Fields

Instances
Functor (Event t) 
Instance details

Defined in Temporal.Media

Methods

fmap :: (a -> b) -> Event t a -> Event t b #

(<$) :: a -> Event t b -> Event t a #

(Eq t, Eq a) => Eq (Event t a) 
Instance details

Defined in Temporal.Media

Methods

(==) :: Event t a -> Event t a -> Bool #

(/=) :: Event t a -> Event t a -> Bool #

(Show t, Show a) => Show (Event t a) 
Instance details

Defined in Temporal.Media

Methods

showsPrec :: Int -> Event t a -> ShowS #

show :: Event t a -> String #

showList :: [Event t a] -> ShowS #

harMap :: Harmony b => (a -> b) -> [a] -> b #

Transforms a sequence and then applies a har.

melMap :: Melody b => (a -> b) -> [a] -> b #

Transforms a sequence and then applies a mel.

(*|) :: Stretch a => DurOf a -> a -> a #

Infix str function.

(+|) :: Delay a => DurOf a -> a -> a #

Infix del function.

loopBy :: Melody a => Int -> a -> a #

Repeats the given audio segment several times.

class Duration a where #

Calculates duration.

Methods

dur :: a -> DurOf a #

Instances
Duration Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

dur :: Seq -> DurOf Seq #

Duration (Track t a) 
Instance details

Defined in Temporal.Media

Methods

dur :: Track t a -> DurOf (Track t a) #

type family DurOf a :: Type #

Duration for the given type.

Instances
type DurOf Seq Source # 
Instance details

Defined in Csound.Air.Envelope

type DurOf Seq = Sig
type DurOf (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

type DurOf (Seg a) = Tick
type DurOf (Track t a) 
Instance details

Defined in Temporal.Media

type DurOf (Track t a) = t

class Melody a where #

Minimal complete definition

mel | (+:+)

Methods

mel :: [a] -> a #

Sequent composition for a list of values (melody).

(+:+) :: a -> a -> a #

Sequent composition. Play first track then second.

Instances
Melody Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

mel :: [Seq] -> Seq #

(+:+) :: Seq -> Seq -> Seq #

Sigs a => Melody (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

Methods

mel :: [Seg a] -> Seg a #

(+:+) :: Seg a -> Seg a -> Seg a #

(Num t, IfB t, OrdB t) => Melody (Track t a) 
Instance details

Defined in Temporal.Media

Methods

mel :: [Track t a] -> Track t a #

(+:+) :: Track t a -> Track t a -> Track t a #

class Harmony a where #

Minimal complete definition

har | (=:=)

Methods

har :: [a] -> a #

Parallel composition for a list of values (harmony).

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

Parallel composition. Play two tracks simultaneously.

Instances
Sigs a => Harmony (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

Methods

har :: [Seg a] -> Seg a #

(=:=) :: Seg a -> Seg a -> Seg a #

(Num t, IfB t, OrdB t) => Harmony (Track t a) 
Instance details

Defined in Temporal.Media

Methods

har :: [Track t a] -> Track t a #

(=:=) :: Track t a -> Track t a -> Track t a #

class (Melody a, Harmony a) => Compose a #

Instances
Sigs a => Compose (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

(Num t, IfB t, OrdB t) => Compose (Track t a) 
Instance details

Defined in Temporal.Media

class Delay a where #

Methods

del :: DurOf a -> a -> a #

Delays the sound source by the given duration.

Instances
Delay Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

del :: DurOf Seq -> Seq -> Seq #

Sigs a => Delay (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

Methods

del :: DurOf (Seg a) -> Seg a -> Seg a #

Num t => Delay (Track t a)

Delays all events by given duration.

Instance details

Defined in Temporal.Media

Methods

del :: DurOf (Track t a) -> Track t a -> Track t a #

class Stretch a where #

Methods

str :: DurOf a -> a -> a #

Delays the sound source by the given duration factor.

Instances
Stretch Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

str :: DurOf Seq -> Seq -> Seq #

Num t => Stretch (Track t a)

Stretches track in time domain.

Instance details

Defined in Temporal.Media

Methods

str :: DurOf (Track t a) -> Track t a -> Track t a #

class Rest a where #

Methods

rest :: DurOf a -> a #

Instances
Rest Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

rest :: DurOf Seq -> Seq #

(Sigs a, Num a) => Rest (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

Methods

rest :: DurOf (Seg a) -> Seg a #

(Num t, IfB t, OrdB t) => Rest (Track t a)

Empty track that lasts for some time.

Instance details

Defined in Temporal.Media

Methods

rest :: DurOf (Track t a) -> Track t a #

class Limit a where #

Methods

lim :: DurOf a -> a -> a #

Limits the duration of the sound source.

Instances
Sigs a => Limit (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

Methods

lim :: DurOf (Seg a) -> Seg a -> Seg a #

class Loop a where #

Methods

loop :: a -> a #

Loops over the sound

Instances
Sigs a => Loop (Seg a) Source # 
Instance details

Defined in Csound.Air.Seg

Methods

loop :: Seg a -> Seg a #

Evt

sched :: (Arg a, Sigs b) => (a -> SE b) -> Evt (Sco a) -> b #

retrig :: (Arg a, Sigs b) => (a -> SE b) -> Evt a -> b Source #

schedHarp :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b #

An instrument is triggered with event stream and delay time is set to zero (event fires immediately) and duration is set to inifinite time. The note is held while the instrument is producing something. If the instrument is silent for some seconds (specified in the first argument) then it's turned off.

schedUntil :: (Arg a, Sigs b) => (a -> SE b) -> Evt a -> Evt c -> b Source #

Invokes an instrument with first event stream and holds the note until the second event stream is active.

schedToggle :: Sigs b => SE b -> Evt D -> b Source #

Invokes an instrument with toggle event stream (1 stands for on and 0 stands for off).

sched_ :: Arg a => (a -> SE ()) -> Evt (Sco a) -> SE () #

Triggers a procedure on the event stream.

schedUntil_ :: Arg a => (a -> SE ()) -> Evt a -> Evt c -> SE () Source #

Invokes an instrument with first event stream and holds the note until the second event stream is active.

schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (Sco a)) -> c -> b #

A closure to trigger an instrument inside the body of another instrument.

schedHarpBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b #

A closure to trigger an instrument inside the body of another instrument.

withDur :: Sig -> Evt a -> Evt (Sco a) Source #

Sets the same duration for all events. It's useful with the functions sched, schedBy, sched_.

monoSched :: Evt (Sco (D, D)) -> SE MonoArg #

Turns

Api

We can create named instruments. then we can trigger the named instruments with Csound API. Csound can be used not as a text to audio converter but also as a shared C-library. There are many bindings to many languages. For example we can use Python or Android SDK to create UI and under the hood we can use the audio engine created with Haskell. The concept of named instruments is the bridge for other lnguages to use our haskell-generated code.

trigByName :: (Arg a, Sigs b) => String -> (a -> SE b) -> SE b #

Creates an instrument that can be triggered by name with Csound API. The arguments are determined from the structure of the input for the instrument. If we have a tuple of arguments: (D, D, Tab) The would be rendered to instrument arguments that strts from p4. p1 is the name of teh instrument, p2 is the start time of the note, p3 is the duration of the note. Then p4 and p5 are going to be doubles and p6 is an integer that denotes a functional table.

trigByName_ :: Arg a => String -> (a -> SE ()) -> SE () #

Creates an instrument that can be triggered by name with Csound API. The arguments are determined from the structure of the input for the instrument.

With Csound API we can send messages

i "name" time duration arg1 arg2 arg3

trigByNameMidi :: (Arg a, Sigs b) => String -> ((D, D, a) -> SE b) -> SE b #

Creates an instrument that can be triggered by name with Csound API.

It's intended to be used like a midi instrument. It simulates a simplified midi protocol. We can trigger notes:

i "givenName" delay duration 1 pitchKey volumeKey auxParams     -- note on
i "givenName" delay duration 0 pitchKey volumeKey auxParams     -- note off

The arguments are

trigByNameMidi name instrument

The instrument takes a triplet of (pitchKey, volumeKey, auxilliaryTuple). The order does matter. Please don't pass the volumeKey as the first argument. The instrument expects the pitch key to be a first argument.

trigByNameMidi_ :: Arg a => String -> ((D, D, a) -> SE ()) -> SE () #

It behaves just like the function trigByNameMidi. Only it doesn't produce an audio signal. It performs some procedure on note on and stops doing the precedure on note off.

turnoffByName :: String -> Sig -> Sig -> SE () Source #

Turns off named instruments.

turnoffNamedInstr name kmode krelease

name of the instrument (should be defined with trigByName or smth like that).

kmode -- sum of the following values:

0, 1, or 2: turn off all instances (0), oldest only (1), or newest only (2)

4: only turn off notes with exactly matching (fractional) instrument number, rather than ignoring fractional part

8: only turn off notes with indefinite duration (p3 < 0 or MIDI)

krelease -- if non-zero, the turned off instances are allowed to release, otherwise are deactivated immediately (possibly resulting in clicks)

Misc

alwaysOn :: SE () -> SE () Source #

Executes some procedure for the whole lifespan of the program,

playWhen :: forall a b. Sigs a => BoolSig -> (b -> SE a) -> b -> SE a Source #

Transforms an instrument from always on to conditional one. The routput instrument plays only when condition is true otherwise it produces silence.

Overload

Converters to make it easier a construction of the instruments.

class Sigs (SigOuts a) => Outs a where Source #

Associated Types

type SigOuts a :: * Source #

Methods

toOuts :: a -> SE (SigOuts a) Source #

Instances
Outs Sig Source # 
Instance details

Defined in Csound.Control.Overload.Outs

Associated Types

type SigOuts Sig :: Type Source #

Methods

toOuts :: Sig -> SE (SigOuts Sig) Source #

Outs (SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.Outs

Associated Types

type SigOuts (SE (Sig, Sig)) :: Type Source #

Methods

toOuts :: SE (Sig, Sig) -> SE (SigOuts (SE (Sig, Sig))) Source #

Outs (SE (Sig, Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.Outs

Associated Types

type SigOuts (SE (Sig, Sig, Sig, Sig)) :: Type Source #

Methods

toOuts :: SE (Sig, Sig, Sig, Sig) -> SE (SigOuts (SE (Sig, Sig, Sig, Sig))) Source #

Outs (SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.Outs

Associated Types

type SigOuts (SE Sig) :: Type Source #

Methods

toOuts :: SE Sig -> SE (SigOuts (SE Sig)) Source #

Outs (Sig, Sig) Source # 
Instance details

Defined in Csound.Control.Overload.Outs

Associated Types

type SigOuts (Sig, Sig) :: Type Source #

Methods

toOuts :: (Sig, Sig) -> SE (SigOuts (Sig, Sig)) Source #

Outs (Sig, Sig, Sig, Sig) Source # 
Instance details

Defined in Csound.Control.Overload.Outs

Associated Types

type SigOuts (Sig, Sig, Sig, Sig) :: Type Source #

Methods

toOuts :: (Sig, Sig, Sig, Sig) -> SE (SigOuts (Sig, Sig, Sig, Sig)) Source #

onArg :: Outs b => (a -> b) -> a -> SE (SigOuts b) Source #

class AmpInstr a where Source #

Constructs a drum-like instrument. Drum like instrument has a single argument that signifies an amplitude.

Associated Types

type AmpInstrOut a :: * Source #

Methods

onAmp :: a -> D -> SE (AmpInstrOut a) Source #

Instances
AmpInstr Sig Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut Sig :: Type Source #

Methods

onAmp :: Sig -> D -> SE (AmpInstrOut Sig) Source #

AmpInstr (SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (SE (Sig, Sig)) :: Type Source #

Methods

onAmp :: SE (Sig, Sig) -> D -> SE (AmpInstrOut (SE (Sig, Sig))) Source #

AmpInstr (SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (SE Sig) :: Type Source #

Methods

onAmp :: SE Sig -> D -> SE (AmpInstrOut (SE Sig)) Source #

AmpInstr (Sig -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (Sig -> (Sig, Sig)) :: Type Source #

Methods

onAmp :: (Sig -> (Sig, Sig)) -> D -> SE (AmpInstrOut (Sig -> (Sig, Sig))) Source #

AmpInstr (Sig -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (Sig -> Sig) :: Type Source #

Methods

onAmp :: (Sig -> Sig) -> D -> SE (AmpInstrOut (Sig -> Sig)) Source #

AmpInstr (Sig -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (Sig -> SE (Sig, Sig)) :: Type Source #

Methods

onAmp :: (Sig -> SE (Sig, Sig)) -> D -> SE (AmpInstrOut (Sig -> SE (Sig, Sig))) Source #

AmpInstr (Sig -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (Sig -> SE Sig) :: Type Source #

Methods

onAmp :: (Sig -> SE Sig) -> D -> SE (AmpInstrOut (Sig -> SE Sig)) Source #

AmpInstr (D -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (D -> (Sig, Sig)) :: Type Source #

Methods

onAmp :: (D -> (Sig, Sig)) -> D -> SE (AmpInstrOut (D -> (Sig, Sig))) Source #

AmpInstr (D -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (D -> Sig) :: Type Source #

Methods

onAmp :: (D -> Sig) -> D -> SE (AmpInstrOut (D -> Sig)) Source #

AmpInstr (D -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (D -> SE (Sig, Sig)) :: Type Source #

Methods

onAmp :: (D -> SE (Sig, Sig)) -> D -> SE (AmpInstrOut (D -> SE (Sig, Sig))) Source #

AmpInstr (D -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (D -> SE Sig) :: Type Source #

Methods

onAmp :: (D -> SE Sig) -> D -> SE (AmpInstrOut (D -> SE Sig)) Source #

AmpInstr (Sig, Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type AmpInstrOut (Sig, Sig) :: Type Source #

Methods

onAmp :: (Sig, Sig) -> D -> SE (AmpInstrOut (Sig, Sig)) Source #

class CpsInstr a where Source #

Constructs a simple instrument that takes in a tuple of two arguments. They are amplitude and the frequency (in Hz or cycles per second).

Associated Types

type CpsInstrOut a :: * Source #

Methods

onCps :: a -> (D, D) -> SE (CpsInstrOut a) Source #

Instances
CpsInstr ((Sig, Sig) -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, Sig) -> (Sig, Sig)) :: Type Source #

Methods

onCps :: ((Sig, Sig) -> (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((Sig, Sig) -> (Sig, Sig))) Source #

CpsInstr ((Sig, Sig) -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, Sig) -> Sig) :: Type Source #

Methods

onCps :: ((Sig, Sig) -> Sig) -> (D, D) -> SE (CpsInstrOut ((Sig, Sig) -> Sig)) Source #

CpsInstr ((Sig, Sig) -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, Sig) -> SE (Sig, Sig)) :: Type Source #

Methods

onCps :: ((Sig, Sig) -> SE (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((Sig, Sig) -> SE (Sig, Sig))) Source #

CpsInstr ((Sig, Sig) -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, Sig) -> SE Sig) :: Type Source #

Methods

onCps :: ((Sig, Sig) -> SE Sig) -> (D, D) -> SE (CpsInstrOut ((Sig, Sig) -> SE Sig)) Source #

CpsInstr ((Sig, D) -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, D) -> (Sig, Sig)) :: Type Source #

Methods

onCps :: ((Sig, D) -> (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((Sig, D) -> (Sig, Sig))) Source #

CpsInstr ((Sig, D) -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, D) -> Sig) :: Type Source #

Methods

onCps :: ((Sig, D) -> Sig) -> (D, D) -> SE (CpsInstrOut ((Sig, D) -> Sig)) Source #

CpsInstr ((Sig, D) -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, D) -> SE (Sig, Sig)) :: Type Source #

Methods

onCps :: ((Sig, D) -> SE (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((Sig, D) -> SE (Sig, Sig))) Source #

CpsInstr ((Sig, D) -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((Sig, D) -> SE Sig) :: Type Source #

Methods

onCps :: ((Sig, D) -> SE Sig) -> (D, D) -> SE (CpsInstrOut ((Sig, D) -> SE Sig)) Source #

CpsInstr ((D, Sig) -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, Sig) -> (Sig, Sig)) :: Type Source #

Methods

onCps :: ((D, Sig) -> (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((D, Sig) -> (Sig, Sig))) Source #

CpsInstr ((D, Sig) -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, Sig) -> Sig) :: Type Source #

Methods

onCps :: ((D, Sig) -> Sig) -> (D, D) -> SE (CpsInstrOut ((D, Sig) -> Sig)) Source #

CpsInstr ((D, Sig) -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, Sig) -> SE (Sig, Sig)) :: Type Source #

Methods

onCps :: ((D, Sig) -> SE (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((D, Sig) -> SE (Sig, Sig))) Source #

CpsInstr ((D, Sig) -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, Sig) -> SE Sig) :: Type Source #

Methods

onCps :: ((D, Sig) -> SE Sig) -> (D, D) -> SE (CpsInstrOut ((D, Sig) -> SE Sig)) Source #

CpsInstr ((D, D) -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, D) -> (Sig, Sig)) :: Type Source #

Methods

onCps :: ((D, D) -> (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((D, D) -> (Sig, Sig))) Source #

CpsInstr ((D, D) -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, D) -> Sig) :: Type Source #

Methods

onCps :: ((D, D) -> Sig) -> (D, D) -> SE (CpsInstrOut ((D, D) -> Sig)) Source #

CpsInstr ((D, D) -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, D) -> SE (Sig, Sig)) :: Type Source #

Methods

onCps :: ((D, D) -> SE (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut ((D, D) -> SE (Sig, Sig))) Source #

CpsInstr ((D, D) -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut ((D, D) -> SE Sig) :: Type Source #

Methods

onCps :: ((D, D) -> SE Sig) -> (D, D) -> SE (CpsInstrOut ((D, D) -> SE Sig)) Source #

CpsInstr (Sig -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (Sig -> (Sig, Sig)) :: Type Source #

Methods

onCps :: (Sig -> (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut (Sig -> (Sig, Sig))) Source #

CpsInstr (Sig -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (Sig -> Sig) :: Type Source #

Methods

onCps :: (Sig -> Sig) -> (D, D) -> SE (CpsInstrOut (Sig -> Sig)) Source #

CpsInstr (Sig -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (Sig -> SE (Sig, Sig)) :: Type Source #

Methods

onCps :: (Sig -> SE (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut (Sig -> SE (Sig, Sig))) Source #

CpsInstr (Sig -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (Sig -> SE Sig) :: Type Source #

Methods

onCps :: (Sig -> SE Sig) -> (D, D) -> SE (CpsInstrOut (Sig -> SE Sig)) Source #

CpsInstr (D -> (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (D -> (Sig, Sig)) :: Type Source #

Methods

onCps :: (D -> (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut (D -> (Sig, Sig))) Source #

CpsInstr (D -> Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (D -> Sig) :: Type Source #

Methods

onCps :: (D -> Sig) -> (D, D) -> SE (CpsInstrOut (D -> Sig)) Source #

CpsInstr (D -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (D -> SE (Sig, Sig)) :: Type Source #

Methods

onCps :: (D -> SE (Sig, Sig)) -> (D, D) -> SE (CpsInstrOut (D -> SE (Sig, Sig))) Source #

CpsInstr (D -> SE Sig) Source # 
Instance details

Defined in Csound.Control.Overload.SpecInstr

Associated Types

type CpsInstrOut (D -> SE Sig) :: Type Source #

Methods

onCps :: (D -> SE Sig) -> (D, D) -> SE (CpsInstrOut (D -> SE Sig)) Source #

Imperative instruments

data InstrRef a #

Instrument reference. we can invoke or stop the instrument by the identifier.

newInstr :: Arg a => (a -> SE ()) -> SE (InstrRef a) #

Creates a new instrument and generates a unique identifier.

scheduleEvent :: Arg a => InstrRef a -> D -> D -> a -> SE () #

Schedules an event for the instrument.

scheduleEvent instrRef delay duration args

The arguments for time values are set in seconds.

turnoff2 :: InstrRef a -> Sig -> Sig -> SE () #

Turns off the note played on the given instrument. Use fractional instrument reference to turn off specific instance.

turnoff2 instrRef mode releaseTime

The mode is sum of the following values:

  • 0, 1, or 2: turn off all instances (0), oldest only (1), or newest only (2)
  • 4: only turn off notes with exactly matching (fractional) instrument number, rather than ignoring fractional part
  • 8: only turn off notes with indefinite duration (idur < 0 or MIDI)

releaseTime if non-zero, the turned off instances are allowed to release, otherwise are deactivated immediately (possibly resulting in clicks).

negateInstrRef :: InstrRef a -> InstrRef a #

Negates the instrument identifier. This trick is used in Csound to update the instrument arguments while instrument is working.

addFracInstrRef :: D -> D -> InstrRef a -> InstrRef a #

Adds fractional part to the instrument reference. This trick is used in Csound to identify the notes (or specific instrument invokation).

newOutInstr :: (Arg a, Sigs b) => (a -> SE b) -> SE (InstrRef a, b) #

Creates an insturment that produces a value.

noteOn :: Arg a => D -> D -> InstrRef a -> a -> SE () #

Triggers a note with fractional instrument reference. We can later stop the instrument on specific note with function noteOff.

noteOff :: (Default a, Arg a) => D -> D -> InstrRef a -> SE () #

Stops a note with fractional instrument reference.