Bang-0.1.0.6: A Drum Machine DSL for Haskell

Copyright(c) Benjamin Kovach, 2014
LicenseMIT
Maintainerbkovach13@gmail.com
Stabilityexperimental
PortabilityMac OSX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Bang.Music.Operators

Description

Defines a number of operators to effectively piece together Bang compositions.

Synopsis

Documentation

(><) :: Music dur a -> Music dur a -> Music dur a infixr 6 Source

Infix operator for cappend

(!>) :: Rational -> Music a b -> Music a b infixr 0 Source

Set the Tempo of a composition (default 1)

Example (play 4 bass drum hits at double speed):

2 !> (4 #> bd)

(#>) :: Num a => Int -> Music a b -> Music a b infixr 1 Source

Infix operator for repl

Example (play a bass drum twice):

2 #> bd

(>>~) :: Monoid b => (a -> b) -> [a] -> b infixl 1 Source

Map a function over a list of compositions and sequentially compose them. Note: This is just foldMap specialized to the list Monoid.

Example (play sn, t1 and t2 all twice):

(2 #>) >>~ [sn, t1, t2]

(~=~) :: (Dur, Music Dur b) -> (Dur, Music Dur b) -> Music Dur b Source

Infix operator for poly

Example (A 3/4 polyrhythm):

(3, 3 #> bd) ~=~ (4, 4 #> sn)

(~=) :: Music Dur b -> Music Dur b -> Music Dur b infixl 2 Source

Infix operator for fitL

Example (a 3/4 polyrhythm with duration 3/4):

(3 #> bd) ~= (4 #> sn)

(=~) :: Music Dur b -> Music Dur b -> Music Dur b infixr 2 Source

Infix operator for fitR

Example (a 3/4 polyrhythm with duration 1:

(3 #> bd) =~ (4 #> sn)

(~~) :: Dur -> Music Dur b -> Music Dur b infixr 2 Source

Infix operator for withDuration

Example:

2 ~~ mconcat [
   16 #> bd
 , 4 #> sn
 , wr
 ]

(<<~) :: Dur -> Music Dur b -> Music Dur b infixr 2 Source

Infix operator for takeDur

Example (Only play 2 bass drum hits):

(1/2) <<~ (4 #> bd)

(~>>) :: Dur -> Music Dur b -> Music Dur b infixr 2 Source

Infix operator for dropDur

Example (play 2 closed hi-hats):

(1/2) ~>> ( (2 #> bd) <> (2 #> hc) )

(~@>) :: Dur -> Music Dur b -> Music Dur b infixr 2 Source

Infix operator for hushFor

Example (half rest, then two closed hi-hats):

(1/2) ~@> ( (2 #> bd) <> (2 #> hc) )

(<@~) :: Dur -> Music Dur b -> Music Dur b infixr 2 Source

Infix operator for hushFrom

Example (two bass drum hits, then a half rest):

(1/2) <@~ ( (2 #> bd) <> (2 #> hc) )

(<!>) :: Dur -> [Music Dur b] -> Music Dur b infixr 0 Source

Infix operator for normalize

Example (Play 12 bass drum hits, then 4 closed hi-hats, then 3 snares, each within a single measure's time):

1 <!> [
    12 #> bd
  , 4  #> hc
  , 3  #> sn
  ]

(>!<) :: Dur -> [Music Dur b] -> Music Dur b infixr 0 Source

Infix operator for normalizeC

Example: (Play 12 bass drum hits, then 4 closed hi-hats, then 3 snares, all concurrently within a single measure's time):

1 >!< [
    12 #> bd
  , 4  #> hc
  , 3  #> sn
  ]