blues Program

Uses

  • program~~blues~~UsesGraph program~blues blues iso_fortran_env iso_fortran_env program~blues->iso_fortran_env module~gm_instruments GM_instruments program~blues->module~gm_instruments module~midi_control_changes MIDI_control_changes program~blues->module~midi_control_changes module~midi_file_class MIDI_file_class program~blues->module~midi_file_class module~music music program~blues->module~music module~midi_file_class->iso_fortran_env module~utilities utilities module~midi_file_class->module~utilities module~music->iso_fortran_env module~music_common music_common module~music->module~music_common module~music->module~utilities module~utilities->iso_fortran_env

A stochastic blues


Calls

program~~blues~~CallsGraph program~blues blues proc~control_change MIDI_file%Control_Change program~blues->proc~control_change proc~delta_time MIDI_file%delta_time program~blues->proc~delta_time proc~end_of_track MIDI_file%end_of_track program~blues->proc~end_of_track proc~get_name MIDI_file%get_name program~blues->proc~get_name proc~midi_note MIDI_Note program~blues->proc~midi_note proc~new MIDI_file%new program~blues->proc~new proc~note_off MIDI_file%Note_OFF program~blues->proc~note_off proc~note_on MIDI_file%Note_ON program~blues->proc~note_on proc~play_chord MIDI_file%play_chord program~blues->proc~play_chord proc~program_change MIDI_file%Program_Change program~blues->proc~program_change proc~track_header MIDI_file%track_header program~blues->proc~track_header proc~control_change->proc~delta_time proc~checked_int8 checked_int8 proc~control_change->proc~checked_int8 proc~checked_int32 checked_int32 proc~delta_time->proc~checked_int32 proc~write_variable_length_quantity MIDI_file%write_variable_length_quantity proc~delta_time->proc~write_variable_length_quantity proc~end_of_track->proc~delta_time proc~write_track_size MIDI_file%write_track_size proc~end_of_track->proc~write_track_size proc~new->proc~end_of_track proc~new->proc~track_header proc~checked_int16 checked_int16 proc~new->proc~checked_int16 proc~new->proc~checked_int32 proc~new->proc~checked_int8 proc~copyright_notice MIDI_file%copyright_notice proc~new->proc~copyright_notice proc~init_formidi MIDI_file%init_formidi proc~new->proc~init_formidi proc~set_tempo MIDI_file%set_tempo proc~new->proc~set_tempo proc~set_time_signature MIDI_file%set_time_signature proc~new->proc~set_time_signature proc~text_event MIDI_file%text_event proc~new->proc~text_event proc~note_off->proc~checked_int8 proc~note_on->proc~checked_int8 proc~play_chord->proc~delta_time proc~play_chord->proc~note_off proc~play_chord->proc~note_on proc~play_chord->proc~checked_int32 proc~program_change->proc~delta_time proc~program_change->proc~checked_int8 proc~sequence_track_name MIDI_file%sequence_track_name proc~track_header->proc~sequence_track_name proc~track_header->proc~text_event proc~write_string MIDI_file%write_string proc~copyright_notice->proc~write_string proc~sequence_track_name->proc~write_string proc~set_tempo->proc~delta_time proc~set_tempo->proc~checked_int32 proc~set_time_signature->proc~delta_time proc~set_time_signature->proc~checked_int8 proc~text_event->proc~write_string proc~variable_length_quantity variable_length_quantity proc~write_variable_length_quantity->proc~variable_length_quantity proc~write_string->proc~delta_time proc~write_string->proc~checked_int8 proc~write_string->proc~write_variable_length_quantity

Variables

Type Attributes Name Initial
logical :: again
integer :: b_scale(0:127)
real(kind=dp) :: delta
integer :: i
integer :: j
integer :: jmax
integer, parameter :: length = 200
type(MIDI_file) :: midi
integer, parameter :: nb_notes = 6
integer :: note
integer :: octave
real(kind=dp) :: p
integer :: tonic
integer :: value

Source Code

program blues
    use, intrinsic :: iso_fortran_env, only: dp=>real64
    use MIDI_file_class
    use music
    use MIDI_control_changes, only: Effects_1_Depth, Modulation_Wheel_or_Lever, Pan
    ! Contains the list of General MIDI 128 instruments and 47 percussions:
    use GM_instruments

    implicit none
    type(MIDI_file) :: midi
    real(dp) :: p, delta
    integer :: i, j, jmax
    integer, parameter :: nb_notes = 6
    integer, parameter :: length = 200
    integer :: b_scale(0:127)     ! Blues scale
    integer :: octave, note, value
    logical :: again
    ! The tonic is the C note:
    integer :: tonic

    tonic = MIDI_Note("C1")

    ! Create a file with 3 tracks (including the metadata track):
    ! A quarter note will last 1000000 µs = 1 s => tempo = 60 bpm
    call midi%new("blues.mid", format=1, tracks=3, divisions=quarter_note, tempo=1000000)

    ! (1) A first music track with guitar:
    call midi%track_header()
    ! Reverb:
    call midi%Control_Change(channel=0, type=Effects_1_Depth, ctl_value=64)
    ! Modulation:
    call midi%Control_Change(channel=0, type=Modulation_Wheel_or_Lever, ctl_value=40)
    ! Panning, slightly on the left (center is 64):
    call midi%Control_Change(channel=0, type=Pan, ctl_value=44)
    ! Instrument:
    call midi%Program_Change(channel=0, instrument=Distortion_Guitar)

    ! A blues scale C, Eb, F, Gb, G, Bb, repeated at each octave.
    ! The MIDI note 0 is a C-1, but can not be heard (f=8.18 Hz).
    ! https://en.wikipedia.org/wiki/Hexatonic_scale#Blues_scale
    ! We copy the blues scale at the beginning of the array:
    do j = 0, 5
        b_scale(j) = MIDI_Note(trim(HEXATONIC_BLUES_SCALE(j+1))//"0") - 12
    end do

    ! And we copy it as many times as possible:
    jmax = nb_notes - 1
    octave = 1
    again = .true.
    do
        do j = 0, nb_notes-1
            if (b_scale(j) + octave*12 <= 127) then
                jmax = octave*nb_notes + j
                b_scale(jmax) = b_scale(j) + octave*12
            else
                again = .false.
            end if
        end do
        octave = octave + 1
        if (.not. again) exit
    end do

    ! Let's make a random walk on that scale:
    value = quarter_note
    note = tonic
    do i = 1, length
        call midi%play_chord(channel=0, note=b_scale(note), chord=POWER_CHORD, velocity=p_level-2, value=value)

        ! Random walk:
        call random_number(p)
        ! We need a kind of restoring force to avoid going too far:
        delta = ((b_scale(note) - b_scale(tonic)) / 12.0_dp) * 0.45_dp
        if (p >= 0.55_dp + delta) then
            if (note < jmax) note = note + 1
        else if (p >= 0.1_dp) then
            if (note > 0) note = note - 1
        end if

        ! Duration:
        call random_number(p)
        if (p >= 0.75_dp) then
            value = quarter_note
        else
            value = sixteenth_note
        end if
    end do

    call midi%end_of_track()

    ! (2) Drums track (channel 9 by default):
    call midi%track_header()
    ! Reverb:
    call midi%Control_Change(channel=drums, type=Effects_1_Depth, ctl_value=64)
    ! Panning, slightly on the right (center is 64):
    call midi%Control_Change(channel=drums, type=Pan, ctl_value=84)

    do i = 1, length*2
        call midi%delta_time(0)
        ! On the drum channel, each note corresponds to a percussion:
        call midi%Note_ON(channel=drums, note=Closed_Hi_Hat, velocity=80)

        ! We use modulo to create a rhythm:
        if (mod(i, 6) == 4) then
            call midi%delta_time(0)
            call midi%Note_ON(channel=drums, note=Acoustic_Snare, velocity=92)
        else if ((mod(i, 6) == 1) .or. (mod(i, 12) == 6)) then
            call midi%delta_time(0)
            call midi%Note_ON(channel=drums, note=Acoustic_Bass_Drum, velocity=127)
        end if

        call midi%delta_time(quarter_note / 3)
        call midi%Note_OFF(channel=drums, note=Closed_Hi_Hat, velocity=64)

        if (mod(i, 6) == 4) then
            call midi%delta_time(0)
            call midi%Note_OFF(channel=drums, note=Acoustic_Snare, velocity=92)
        else if ((mod(i, 6) == 1) .or. (mod(i, 12) == 6)) then
            call midi%delta_time(0)
            call midi%Note_OFF(channel=drums, note=Acoustic_Bass_Drum, velocity=127)
        end if
    end do

    call midi%end_of_track()

    call midi%close()

    print *,"You can now play the file ", midi%get_name()
end program blues