Compositional Functional Programming with the Haskore Music

Slides:



Advertisements
Similar presentations
Musical Instruments.
Advertisements

Haskore Musikbearbeitung mit Haskell Paul Hudak, Yale University, USA
Chapter 20 Functional Music Composition. MDL: Music Description Language MDL is a DSL for computer music composition that is even simpler than FAL and.
Peter Rademaker & Robert Stremler. Preview 1.Introduction 2.The Basics 3.Simple Examples 4.Interpretation and Performance 5.MIDI 6.Algebraic Properties.
Final Review 8th grade Band 4th quarter Time Signature Indicates the of beats per measure.
MUSIC Elements, History, and Performance. Timbre- Sound Quality Instrument Families STRINGS Violin Viola Cello Bass Harp Guitar Banjo Piano WIND Saxaphone.
What is the purpose of learning musical elements?
For your Information: Slide 2 is the title card. You can use it to print on the back side of each card. Helps to give the cards a professional look. Slides.
GRADE 4/5 AH-E AH-E When I present this PowerPoint project, I bring instruments in for the kids to see, and I play a CD from the instrument.
Instrumental Families
Timbre A description of the actual sounds that you hear. “Tone color” or “quality”
Understanding Music - Instrumental Music. What we will be learning about in this topic...
Families and Classifications of Instruments
Music Appreciation Musical Instruments.
Sorting Instruments ■ ██████████ ██████████ ██████████ █████████
Music This is a topic on musical instruments. Instruments String instruments Woodwind instruments Percussion instruments Brass instruments.
Music JEOPARDY Family of Instruments By A. Vilcins
Instruments of the Orchestra
MGC (Music Generator for Composing). Pronunciation MGC MGC mmmmGiC mmmmGiC Magic Magic.
Elements of Music. Harmony Two or more notes together Two or more notes together Chord – three or more notes at one time Chord – three or more notes at.
Cse536 Functional Programming 1 5/16/2015 Lecture #19, Dec 1 & 6, 2004 Todays Topics – Haskore System –The Music datatype –MIDI Instruments –Pitch & absolute.
The Stars and Stripes Forever
Cse536 Functional Programming 1 6/17/2015 Lecture #19, Dec 1 & 6, 2004 Todays Topics – Haskore System –The Music datatype –MIDI Instruments –Pitch & absolute.
Cse536 Functional Programming 1 6/26/2015 Lecture #19, Dec. 6, 2004 Todays Topics –Interpreting Music –Performance –MidiFile Read – Chapters 21 - Interpreting.
ElementsSoundHistory Note equal in value to 1/4 that of a whole note.
MGC (Music Generator for Composing). Pronunciation MGC MGC mmmmGiC mmmmGiC Magic Magic.
MUSICAL INSTRUMENTS CLASSIFICATION. 1. STRING INSTRUMENTS A string instrument is a musical instrument that produces sound by string that vibrates. They.
Sound and Vibration The PERCUSSION Family. Sound and Vibration  Sound is made by air vibrating. The same is true for sounds made by musical instruments.
Music Core Content.
Christmas Final Review 2nd quarter Band Time Signature Indicates the number of beats per measure.
Making music Consider music as structured sound Components include –Pitch –Duration –Instrument –Stereo direction Each attribute has a set of possible.
Mrs. Schroerlucke with help from Roger Kaimien Music and Appreciation
The Instruments of the Orchestra 4 Families of Instruments Strings Winds Brass Percussion.
Elements of Music. When you listen to a piece of music, you'll notice that it has several different characteristics; it may be soft or loud, slow or fast,
Musical Instrument Families. Why are there different families Each instrument family has their own unique TIMBRE or sound How is sound produced –By vibrations!
Aim: How do the musical instruments of the orchestra work?
CATEGORIES OF MUSICAL INSTRUMENTS DESCRIPTION AND IDENTIFICATION FOR CLASSES 4TH -8 TH Prepared by : A.P. Vinayak.
Chapter 7 Western Musical Instruments. Strings They are bowed and plucked – Violin – Viola – Cello (also Violoncello) – Double Bass.
SPELLING PRACTISE. ORCHESTRA 1. Write the word. Spell it, Study it, Remember it.
Music By: Raegan Light.
Instruments are grouped into 4 major families  Brass instruments all share these characteristics  They are made of metal and have a brass finish 
Computing with Music: Creating Musical Patterns Campy, 2005 Quinnipiac University Computing with Music: Creating Musical Patterns John Peterson No Longer.
1. Woodwind 2. Brass 3. Strings 4. Percussion/Keyboard.
Music Core Content Instrument Families Voice Parts Brass S oprano Woodwind A lto String T enor Percussion Bass How each instrument or voice sounds.
Each corner of the room is a different answer (A, B, C, or D)
Musical Instruments.
Instruments of the H R O S C A E T R.
ELEMENTS OF MUSIC.  Listening to music for a music class is different than just listening to your favourite song on the radio.  You need to listen for.
KS3 End of Year Exams Music Revision.
Performance media INSTRUMENTS = mechanism other than a voice that produces musical sounds. (single note or multi) CLASSES OF INSTRUMENTS 1 WOODWIND 2 BRASS.
Chapter 2: Rhythm and Pitch

Music Quiz By Mrs. Zargarpur.
The Orchestra.
Musical instrument families
Types of Musical Groups and Ensembles
Music Appreciation Musical Instruments.
Christmas Final Review
Instrumentation and Transposition
The Instrument Families
MUSICAL STRUCTURE ELEMENTS OF MUSIC.
A Variety of Instruments and the Families in Which They Belong
Family Of Instruments Test
Musical Instruments Marion Leen
KS3 Knowledge Organiser: Year 7 Instruments of the Orchestra
Instruments of the Orchestra
Compositional Functional Programming with the Haskore Music
INSTRUMENTS OF THE ORCHESTRA AND CONCERT BAND
Chapter 2: Rhythm and Pitch
Performing Media: Voices & Instruments
Presentation transcript:

Compositional Functional Programming with the Haskore Music Todays Topics The Haskore System The Music datatype MIDI Instruments Pitch & absolute Pitch Composing Music Delay Repeating Transposing Manipulating Music Duration Cutting Reversing Percussion Presentation and the MIDI file format

Haskore Haskore is a Haskell library for constructing digital music It supports an abstract high-level description of musical concepts Maps into the Midi (Musical Instrument Digital Interface) standard a low-level binary bit based encoding of music can be “played” by “Media-Players” Haskell Haskore Haskore Abstract High Level Implementation independent MIDI low level bit based implementation standard presentation

Musical Basics in Haskore type Pitch = (PitchClass, Octave) data PitchClass = Cf | C | Cs | Df | D | Ds | Ef | E | Es | Ff | F | Fs | Gf | G | Gs | Af | A | As | Bf | B | Bs deriving (Eq,Show) type Octave = Int Middle C Octave 4 Octave 2 Octave 3 Cs Ds Fs Gs As Df Ef Gf Af Bf Cf Ff Es Cf Bs C D E F G A B C

Music data Music = Note Pitch Dur | Rest Dur | Music :+: Music | Tempo (Ratio Int) Music | Trans Int Music | Instr IName Music

Midi Standard supports lots of instruments data IName = AcousticGrandPiano | BrightAcousticPiano | ElectricGrandPiano | HonkyTonkPiano | RhodesPiano | ChorusedPiano | Harpsichord | Clavinet | Celesta | Glockenspiel | MusicBox | Vibraphone | Marimba | Xylophone | TubularBells | Dulcimer | HammondOrgan | PercussiveOrgan | RockOrgan | ChurchOrgan | ReedOrgan | Accordion | Harmonica | TangoAccordion | AcousticGuitarNylon | AcousticGuitarSteel | ElectricGuitarJazz | ElectricGuitarClean | ElectricGuitarMuted | OverdrivenGuitar | DistortionGuitar | GuitarHarmonics | AcousticBass | ElectricBassFingered | ElectricBassPicked | FretlessBass | SlapBass1 | SlapBass2 | SynthBass1 | SynthBass2 | Violin | Viola | Cello | Contrabass | TremoloStrings | PizzicatoStrings | OrchestralHarp | Timpani | StringEnsemble1 | StringEnsemble2 | SynthStrings1 | SynthStrings2 | ChoirAahs | VoiceOohs | SynthVoice | OrchestraHit | Trumpet | Trombone | Tuba | MutedTrumpet | FrenchHorn | BrassSection | SynthBrass1 | SynthBrass2 | SopranoSax | AltoSax | TenorSax | BaritoneSax | Oboe | Bassoon | EnglishHorn | Clarinet | Piccolo | Flute | Recorder | PanFlute | BlownBottle | Shakuhachi | Whistle | Ocarina | Lead1Square | Lead2Sawtooth | Lead3Calliope | Lead4Chiff | Lead5Charang | Lead6Voice | Lead7Fifths | Lead8BassLead | Pad1NewAge | Pad2Warm | Pad3Polysynth | Pad4Choir | Pad5Bowed | Pad6Metallic | Pad7Halo | Pad8Sweep | FX1Train | FX2Soundtrack | FX3Crystal | FX4Atmosphere | FX5Brightness | FX6Goblins | FX7Echoes | FX8SciFi | Sitar | Banjo | Shamisen | Koto | Kalimba | Bagpipe | Fiddle | Shanai | TinkleBell | Agogo | SteelDrums | Woodblock | TaikoDrum | MelodicDrum | SynthDrum | ReverseCymbal | GuitarFretNoise | BreathNoise | Seashore | BirdTweet | TelephoneRing | Helicopter | Applause | Gunshot | Percussion deriving (Show,Eq,Ord,Enum)

Duration & Absolute Pitch type Dur = Ratio Int fractions of Integers such as 3 /4. We write (3 % 4) in Haskell. type AbsPitch = Int absPitch :: Pitch -> AbsPitch absPitch (pc,oct) = 12*oct + pcToInt pc 0 1 2 3 4 5 6 7 8 9 10 11 12 24 36 . . . (C,0) (C,1) (C,2) (C,3)

Pitch to integer pcToInt :: PitchClass -> Int pcToInt pc = case pc of Cf -> -1 -- should Cf be 11? C -> 0 ; Cs -> 1 Df -> 1 ; D -> 2 ; Ds -> 3 Ef -> 3 ; E -> 4 ; Es -> 5 Ff -> 4 ; F -> 5 ; Fs -> 6 Gf -> 6 ; G -> 7 ; Gs -> 8 Af -> 8 ; A -> 9 ; As -> 10 Bf -> 10 ; B -> 11 ; Bs -> 12 -- maybe 0? Note how several different pitches have the same absolute pitch. This is because the “flat” of some notes is the “sharp” of another. Cs Ds Fs Gs As Df Ef Gf Af Bf Cf Ff Es Cf Bs C D E F G A B C

From AbsPitch to Pitch pitch12 = [C,Cs,D,Ds,E,F,Fs,G,Gs,A,As,B] pitch :: AbsPitch -> Pitch pitch a = (pitch12 !! mod a 12, quot a 12) trans :: Int -> Pitch -> Pitch trans i p = pitch (absPitch p + i) Dist above C octave 0 1 2 3 4 5 6 7 8 9 10 11 12 24 36 . . . (C,0) (C,1) (C,2) (C,3)

Generic Music - Notes cf,c,cs,df,d,ds,ef,e,es,ff,f,fs,gf,g,gs,af,a,as,bf,b,bs :: Octave -> Dur -> Music cf o = Note(Cf,o); c o = Note(C,o); cs o = Note(Cs,o) df o = Note(Df,o); d o = Note(D,o); ds o = Note(Ds,o) ef o = Note(Ef,o); e o = Note(E,o); es o = Note(Es,o) ff o = Note(Ff,o); f o = Note(F,o); fs o = Note(Fs,o) gf o = Note(Gf,o); g o = Note(G,o); gs o = Note(Gs,o) af o = Note(Af,o); a o = Note(A,o); as o = Note(As,o) bf o = Note(Bf,o); b o = Note(B,o); bs o = Note(Bs,o) Given an Octave creates a function from Dur to Music in that octave. Note that Note :: Pitch -> Dur -> Music These functions have the same names as the constructors of the PitchClass but they’re not capitalized.

Generic Music - Rests wn, hn, qn, en, sn, tn :: Dur dhn, dqn, den, dsn :: Dur wnr, hnr, qnr, enr, snr, tnr :: Music dhnr, dqnr, denr, dsnr :: Music wn = 1 ; wnr = Rest wn -- whole hn = 1%2 ; hnr = Rest hn -- half qn = 1%4 ; qnr = Rest qn -- quarter en = 1%8 ; enr = Rest en -- eight sn = 1%16 ; snr = Rest sn -- sixteenth tn = 1%32 ; tnr = Rest tn -- thirty-second dhn = 3%4 ; dhnr = Rest dhn -- dotted half dqn = 3%8 ; dqnr = Rest dqn -- dotted quarter den = 3%16 ; denr = Rest den -- dotted eighth dsn = 3%32 ; dsnr = Rest dsn -- dotted sixteenth

Lets Write Some Music! line, chord :: [Music] -> Music line = foldr (:+:) (Rest 0) chord = foldr (:=:) (Rest 0) Example 1 cScale = line [c 4 qn, d 4 qn, e 4 qn, f 4 qn, g 4 qn, a 4 qn, b 4 qn, c 5 qn] Note the change in Octave

More Examples Example 2 Example 3 Example 4 cMaj = [ n 4 hn | n <- [c,e,g] ] cMin = [ n 4 wn | n <- [c,ef, g] ] Example 2 cMajArp = line cMaj Example 3 cMajChd = chord cMaj Example 4 ex4 = line [ chord cMaj, chord cMin ]

Time Delaying Music delay :: Dur -> Music -> Music delay d m = Rest d :+: m ex5 = cScale :=: (delay dhn cScale)

Transposing Music ex6 = line [line cMaj,Trans 12 (line cMaj)] 12 tone difference

Repeating Music repeatM :: Music -> Music repeatM m = m :+: repeatM m nBeatsRest n note = line ((take n (repeat note)) ++ [qnr]) ex7 = line [e 4 qn, d 4 qn, c 4 qn, d 4 qn, line [ nBeatsRest 3 (n 4 qn) | n <- [e,d] ], e 4 qn, nBeatsRest 2 (g 4 qn) ]

Fancy Stuff pr1, pr2 :: Pitch -> Music pr1 p = Tempo (5%6) (Tempo (4%3) (mkLn 1 p qn :+: Tempo (3%2) (mkLn 3 p en :+: mkLn 2 p sn :+: mkLn 1 p qn ) :+: mkLn 1 p qn) :+: Tempo (3%2) (mkLn 6 p en)) pr2 p = Tempo (7%6) (m1 :+: Tempo (5%4) (mkLn 5 p en) :+: m1 :+: Tempo (3%2) m2) where m1 = Tempo (5%4) (Tempo (3%2) m2 :+: m2) m2 = mkLn 3 p en mkLn n p d = line (take n (repeat (Note p d))) pr12 :: Music pr12 = pr1 (C,5) :=: pr2 (G,5)

How long is a piece of music? dur :: Music -> Dur dur (Note _ d) = d dur (Rest d) = d dur (m1 :+: m2) = dur m1 + dur m2 dur (m1 :=: m2) = dur m1 `max` dur m2 dur (Tempo a m) = dur m / a dur (Trans _ m) = dur m dur (Instr _ m) = dur m

Reversing a piece of music revM :: Music -> Music revM n@(Note _ _) = n revM r@(Rest _) = r revM (Tempo a m) = Tempo a (revM m) revM (Trans i m) = Trans i (revM m) revM (Instr i m) = Instr i (revM m) revM (m1 :+: m2) = revM m2 :+: revM m1 revM (m1 :=: m2) = let d1 = dur m1 d2 = dur m2 in if d1>d2 then revM m1 :=: (Rest (d1-d2) :+: revM m2) else (Rest (d2-d1) :+: revM m1) :=: revM m2

Cutting a piece of music short cut :: Dur -> Music -> Music cut d m | d <= 0 = Rest 0 cut d (Note x d0) = Note x (min d0 d) cut d (Rest d0) = Rest (min d0 d) cut d (m1 :=: m2) = cut d m1 :=: cut d m2 cut d (Tempo a m) = Tempo a (cut (d*a) m) cut d (Trans a m) = Trans a (cut d m) cut d (Instr a m) = Instr a (cut d m) cut d (m1 :+: m2) = let m1' = cut d m1 m2' = cut (d - dur m1') m2 in m1' :+: m2'

Comments Music is a high level abstract representation of music. Its analyzable so we can do many things with it First, we can play it But we can also compute its duration (without playing it) reverse it scale it’s Tempo truncate it to a specific duration transpose it into another key

Percussion data PercussionSound = AcousticBassDrum -- MIDI Key 35 | SideStick -- ... | AcousticSnare | HandClap | ElectricSnare | LowFloorTom | ClosedHiHat | HighFloorTom | PedalHiHat | LowTom | OpenHiHat | LowMidTom | HiMidTom | CrashCymbal1 | HighTom | RideCymbal1 | ChineseCymbal | RideBell | Tambourine | SplashCymbal | Cowbell | CrashCymbal2 | Vibraslap | RideCymbal2 | HiBongo | LowBongo | MuteHiConga | OpenHiConga | LowConga | HighTimbale | LowTimbale | HighAgogo | LowAgogo | Cabasa | Maracas | ShortWhistle | LongWhistle | ShortGuiro | LongGuiro | Claves | HiWoodBlock | LowWoodBlock | MuteCuica | OpenCuica | MuteTriangle | OpenTriangle -- MIDI Key 82 deriving (Show,Eq,Ord,Ix,Enum)

Let’s beat the drums perc :: PercussionSound -> Dur -> Music perc ps = Note (pitch (fromEnum ps + 35)) funkGroove = let p1 = perc LowTom qn p2 = perc AcousticSnare en in Tempo 3 (Instr Percussion (cut 8 (repeatM ( (p1 :+: qnr :+: p2 :+: qnr :+: p2 :+: p1 :+: p1 :+: qnr :+: p2 :+: enr) :=: roll en (perc ClosedHiHat 2) ) )))

Music Presentation Music is a highlevel, abstract representation We call the playing of Music its Presentation Presentation requires “flattening” the Music representation into a list of low level events. Events contain information about pitch start-time end-time loudness duration instrument etc. The MIDI standard is a file format to represent this low level information. Presentation is the subject of the next lecture.

MIDI Event List Hours, Minutes, Seconds, Frames Pitch, Volume, Duration Measure, Beats, Ticks channel track Time in 2 formats