circle_of_fifths Program

Uses

  • program~~circle_of_fifths~~UsesGraph program~circle_of_fifths circle_of_fifths iso_fortran_env iso_fortran_env program~circle_of_fifths->iso_fortran_env module~gm_instruments GM_instruments program~circle_of_fifths->module~gm_instruments module~midi_control_changes MIDI_control_changes program~circle_of_fifths->module~midi_control_changes module~midi_file_class MIDI_file_class program~circle_of_fifths->module~midi_file_class module~music music program~circle_of_fifths->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 random walk on the circle of fifths


Calls

program~~circle_of_fifths~~CallsGraph program~circle_of_fifths circle_of_fifths proc~control_change MIDI_file%Control_Change program~circle_of_fifths->proc~control_change proc~end_of_track MIDI_file%end_of_track program~circle_of_fifths->proc~end_of_track proc~get_name MIDI_file%get_name program~circle_of_fifths->proc~get_name proc~midi_note MIDI_Note program~circle_of_fifths->proc~midi_note proc~new MIDI_file%new program~circle_of_fifths->proc~new proc~play_chord MIDI_file%play_chord program~circle_of_fifths->proc~play_chord proc~program_change MIDI_file%Program_Change program~circle_of_fifths->proc~program_change proc~track_header MIDI_file%track_header program~circle_of_fifths->proc~track_header proc~checked_int8 checked_int8 proc~control_change->proc~checked_int8 proc~delta_time MIDI_file%delta_time proc~control_change->proc~delta_time 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~checked_int32 checked_int32 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~play_chord->proc~checked_int32 proc~play_chord->proc~delta_time proc~note_off MIDI_file%Note_OFF proc~play_chord->proc~note_off proc~note_on MIDI_file%Note_ON proc~play_chord->proc~note_on proc~program_change->proc~checked_int8 proc~program_change->proc~delta_time 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~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~note_off->proc~checked_int8 proc~note_on->proc~checked_int8 proc~sequence_track_name->proc~write_string proc~set_tempo->proc~checked_int32 proc~set_tempo->proc~delta_time proc~set_time_signature->proc~checked_int8 proc~set_time_signature->proc~delta_time proc~text_event->proc~write_string proc~write_string->proc~checked_int8 proc~write_string->proc~delta_time proc~write_string->proc~write_variable_length_quantity proc~variable_length_quantity variable_length_quantity proc~write_variable_length_quantity->proc~variable_length_quantity

Variables

Type Attributes Name Initial
integer :: channel
integer :: i
integer :: instrument
integer, parameter :: length = 200
logical :: major
type(MIDI_file) :: midi
character(len=3) :: name
integer :: note
real(kind=dp) :: p
integer :: velocity

Source Code

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

    implicit none
    type(MIDI_file) :: midi
    integer :: channel, instrument, velocity, note
    character(3) :: name
    logical  :: major
    integer, parameter :: length = 200
    integer  :: i
    real(dp) :: p

    ! Create a file with 2 tracks (including the metadata track):
    ! The first track is always a metadata track. We define the 
    ! tempo: a quarter note will last 500000 µs = 0.5 s => tempo = 120 bpm
    call midi%new("circle_of_fifths.mid", format=1, tracks=2, divisions=quarter_note, tempo=500000)

    ! (1) The single music track:
    call midi%track_header()

    ! Sounds also good with instruments String_Ensemble_2 and Pad_8_sweep:
    instrument = Choir_Aahs
    ! We will use altenatively MIDI channels 0 and 1 to avoid cutting
    ! the tail of each chord:
    call midi%Program_Change(channel=0, instrument=instrument)
    call midi%Program_Change(channel=1, instrument=instrument)
    ! Heavy (127) reverb effect:
    call midi%Control_Change(channel=0, type=Effects_1_Depth, ctl_value=127)  ! Reverb
    call midi%Control_Change(channel=1, type=Effects_1_Depth, ctl_value=127)  ! Reverb

    ! We start with C Major (note at the top of the Major circle):
    note = 1
    major = .true.
    name = trim(CIRCLE_OF_FIFTHS_MAJOR(note)) // "4"
    call midi%play_chord(channel=0, note=MIDI_Note(name), chord=MAJOR_CHORD, velocity=f_level+10, value=whole_note)

    ! A random walk with three events: we can go one note clockwise,
    ! one note counterclockwise or switch Major<->minor.
    do i = 1, length
        ! A random number 0 <= p < 3
        call random_number(p)
        p = 3 * p
        ! The three possible events:
        if (p >= 2.0_dp) then
            note = note + 1
            if (note > 12) note = 1
        else if (p >= 1.0_dp) then
            note = note - 1
            if (note < 1) note = 12
        else
            major = .not. major
        end if

        ! Alternate between channels 0 and 1:
        channel = mod(i, 2)

        ! The volume will evolve, to obtain some dynamics:
        velocity = f_level + 10 + int(20*sin(real(i)))

        ! Write a major or minor chord on the track:
        if (major) then
            name = trim(CIRCLE_OF_FIFTHS_MAJOR(note)) // "4"
            call midi%play_chord(channel, MIDI_Note(name), MAJOR_CHORD, velocity, whole_note)
        else
            name = trim(CIRCLE_OF_FIFTHS_MINOR(note)) // "4"
            call midi%play_chord(channel, MIDI_Note(name), MINOR_CHORD, velocity, whole_note)
        end if
    end do

    call midi%end_of_track()

    call midi%close()

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