Four Fortran 95 programmes.

Discussion of anything and everything relating to chess playing software and machines.

Moderator: Ras

User avatar
Evert
Posts: 2929
Joined: Sat Jan 22, 2011 12:42 am
Location: NL

Re: New update of Probabilities_in_a_trinomial_distribution.

Post by Evert »

Ok, I've taken a bit of time to look at the code a bit more closely. The following should be much faster than the original version and produce the same output (it does as far as I can tell, but as I said, I can't compile it):

Code: Select all

! Programme that calculates the probabilities of reach certain scores when given some input data.
program Trinomial_distribution_probabilities
   implicit none
   integer, parameter :: dbl = selected_real_kind(15,307)

   character(len=*), parameter :: F0 = '(A,I4,A)'
   character(len=*), parameter :: F1 = '(A,F7.4,A)'
   character(len=*), parameter :: F2 = '(A,F6.1,A,I4)'
   character(len=*), parameter :: F3 = '(A,I4,A,I4,A,I4)'
   character(len=*), parameter :: F4 = '(A,F6.1,A)'
   character(len=*), parameter :: F5 = '(I4,A,F7.4,A)'
   character(len=*), parameter :: F6 = '(F8.4,A)'
   character(len=*), parameter :: F7 = '(F6.1,A,F7.4)'
   integer :: games, i, j, k, i_max
   integer :: n = 1000  ! Maximum number of games supported.
   integer, allocatable :: wins(:,:), draws(:,:), loses(:,:), relative_frequency(:)
   real(dbl), allocatable :: points(:), P(:,:), sum_P(:)
   real(dbl), allocatable :: fact(:)
   real(dbl) :: f_winsij, f_drawsij, f_losesij
   real(dbl) :: delta, x, D, D_max, W_minus_L, W, L, overall_1, overall_2
   real(dbl) :: f_games  ! f_* = factorials.
   real(dbl) :: max_frequency, prob_player_1_wins_the_match, prob_of_a_tied_match, prob_player_2_wins_the_match
   real(dbl) :: half_time, time_of_calculations, elapsed_time
   real :: time0, time

   write(*,*)
   write(*,'(A)') 'Probabilities_in_a_trinomial_distribution, ? 2013.'
   write(*,*)
   write(*,'(A)') '--------------------------------------------------------------------'
   write(*,'(A)') 'Probabilities of all possible scores in a match between two engines.'
   write(*,'(A)') '--------------------------------------------------------------------'
   write(*,*)
   write(*,F0) 'Write down the number of games of the match (minimum 2):'
   write(*,*)
   read(*,*) games
   write(*,*)
   if (games < 2) then
     write(*,'(A)') 'The number of games must be greater than 1.'
     write(*,*)
     write(*,'(A)') 'Please close and try again. Press Enter to exit.'
     read(*,'()')
     stop
   end if
   n = games
   allocate(wins(0:2*n,0:2*n))
   allocate(draws(0:2*n,0:2*n))
   allocate(loses(0:2*n,0:2*n))
   allocate(relative_frequency(0:2*n))
   allocate(points(0:2*n))
   allocate(P(0:2*n,0:n))
   allocate(sum_P(0:2*n))
   allocate(fact(0:n))

   fact(0) = 1.
   fact(1) = 1.
   do k=2, n
      fact(k) = k*fact(k-1)
   end do

   write(*,'(A)') 'Write down the engines rating difference (between -800 Elo and 800 Elo).'
   write(*,'(A)') 'Elo(first player) - Elo(second player):'
   write(*,*)
   read(*,*) delta
   write(*,*)
   if (abs(delta) > 8d2) then
     write(*,'(A)') 'The engines rating difference must be between -800 Elo and 800 Elo.'
     write(*,*)
     write(*,'(A)') 'Please close and try again. Press Enter to exit.'
     read(*,'()')
     stop
   end if

   x = 1d1**(2.5d-3*delta)  ! x = 10^(delta/400)
   W_minus_L = (x - 1d0)/(x + 1d0)  ! delta = 400*log{[1 + (W - L)]/[1 - (W - L)]}
   D_max = 1d0 - abs(W_minus_L) - 1d-6  ! Supposing (W = W_max, L = 0) or (W = 0, L = L_max.); -1d-6 avoids D = 1 when x = 1.

   write(*,F1) 'Write down the probability of a draw (%) between 0.0001 % and ', 1d-4*int(1d6*D_max), ' %'
   ! Using int() avoid cases where, for example:
   ! D_max = 84.21776...%, cmd prints 84.2178% (if nint() is used), the user writes 84.2178% and of course 84.2178 > 84.21776...
   write(*,*)
   read(*,*) D
   write(*,*)
   if ((D < 1d-4) .or. (D > 1d-4*int(1d6*D_max))) then
     write(*,'(A)') 'Incorrect probability of a draw.'
     write(*,*)
     write(*,'(A)') 'Please close and try again. Press Enter to exit.'
     read(*,'()')
     stop
   end if
   D = 1d-2*D  ! D = probability of a draw.

   write(*,'(A)') 'Calculating, please wait.'
   write(*,*)

   call cpu_time(time0)

   ! W + D + L = 1 by definition; 1 - D = W + L.
   W = 5d-1*(1d0 - D + W_minus_L)  ! W = probability of a win.
   L = 5d-1*(1d0 - D - W_minus_L)  ! L = probability of a lose.

   i_max = games + games  ! i_max = 2*(games - 0)

   wins(0,0) = games
   draws(0,0) = 0
   loses(0,0) = 0
   points(0) = games
   P(0,draws(0,0)) = W**wins(0,0)  ! i = 0; (i,j) = (0,0).
   sum_P(0) = P(0,draws(0,0))

   if (wins(0,0) >= 2) f_games = fact(wins(0, 0))

   do i = 1, i_max/2
     points(i) = games - 5d-1*i  ! Continue at points = games - 0.5, then decrease by 0.5 points each time.
     sum_P(i) = 0d0              ! Initialization of the value.
     do j = 0, int(i/2)
       wins(i,j) = games - (i - j)  ! It goes from the minimum number of wins (games - i) up to the maximum number of wins.
       draws(i,j) = i - j - j  ! draws(i,j) = games - [wins(i,j) + loses(i,j)] = games - {[(games - (i - j)] + j} = i - 2*j. 
       loses(i,j) = j  ! It goes from the minimum number of loses (0) up to the maximum number of loses.
       ! wins(i,j) - loses(i,j) = games - i = constant for each i (it does not depend on j).
       ! Start of the calculation of factorials:

       f_winsij  = fact(wins(i,j))
       f_drawsij = fact(draws(i,j))
       f_losesij = fact(loses(i,j))
       ! Finish of the calculation of factorials.
       P(i,draws(i,j)) = (f_games/(f_winsij*f_drawsij*f_losesij))*(W**wins(i,j))*(D**draws(i,j))*(L**loses(i,j))
       ! P(i,draws(i,j)): probability of points = points(i) with draws = draws(i,j).
       sum_P(i) = sum_P(i) + P(i,draws(i,j))
     end do
   end do

   call cpu_time(time)
   half_time = time - time0
   write(*,'(A,F6.2,A)') '50% of the calculations are done; approximated elapsed time: ', 1d-2*nint(1d2*half_time), ' seconds.'  ! Rounded up to 0.01 seconds.
   write(*,*)

   do i = i_max/2+1, i_max-1
     points(i) = games - 5d-1*i
     sum_P(i) = 0d0  ! Initialization of the value.
     do j = i-1, i-(1+int(0.5*(i_max-i))), -1
       ! Taking advantage of simmetry:
       wins(i,j) = loses(i_max-i,i-j-1)
       draws(i,j) = draws(i_max-i,i-j-1)
       loses(i,j) = wins(i_max-i,i-j-1)

       ! Start of the calculation of factorials:
       f_winsij  = fact(wins(i, j))
       f_drawsij = fact(draws(i, j))
       f_losesij = fact(loses(i, j))

       ! Finish of the calculation of factorials.
       P(i,draws(i,j)) = (f_games/(f_winsij*f_drawsij*f_losesij))*(W**wins(i,j))*(D**draws(i,j))*(L**loses(i,j))
       sum_P(i) = sum_P(i) + P(i,draws(i,j))
     end do
   end do

   wins (i_max,i_max) = 0
   draws(i_max,i_max) = 0
   loses(i_max,i_max) = games  ! Finish at points = 0.
   points(i_max) = 0d0
   P(i_max,draws(i_max,i_max)) = L**loses(i_max,i_max)
   sum_P(i_max) = P(i_max,draws(i_max,i_max))

   prob_player_1_wins_the_match = sum(sum_P(1:i_max/2 - 1))
   prob_of_a_tied_match = sum_P(i_max/2)
   prob_player_2_wins_the_match = sum(sum_P(i_max/2 + 1:i_max))

   overall_1 = prob_player_1_wins_the_match + 5d-1*prob_of_a_tied_match
   overall_2 = 1d0 - overall_1

   max_frequency = maxval(sum_P)  ! The mode of the trinomial distribution.
   do i = 0, i_max
     relative_frequency(i) = nint(8d1*sum_P(i)/max_frequency)
     ! It pretends an approximated graphical representation: the mode is rescaled to 80 hyphens and the whole distribution is resized according to that.
   end do

   call cpu_time(time)
   time_of_calculations = time - time0
   write(*,'(A)') 'End of the calculations.'
   write(*,'(A,F6.2,A)') 'Approximated time spent in calculations: ', 1d-2*nint(1d2*time_of_calculations), ' seconds.'  ! Rounded up to 0.01 seconds.
   write(*,*)
   write(*,'(A)') 'The results will be saved into two different Notepads, at the same path of this programme.'
   write(*,*)

   open(unit=11,file='Probabilities.txt', status='unknown', action='write')
   write(11,F0) 'Probabilities for a match of ', games, ' games (rounded up to 0.0001 %):'
   write(11,'(A)')
   write(11,'(A,F7.2,A)') 'Rating difference (rounded up to 0.01 Elo): ', 1d-2*nint(1d2*delta), ' Elo.'
   write(11,'(A)')
   write(11,F1) 'Probability of a win  = W ~ ', 1d-4*nint(1d6*W), ' %'
   write(11,F1) 'Probability of a draw = D ~ ', 1d-4*nint(1d6*D), ' %'
   write(11,F1) 'Probability of a lose = L ~ ', 1d-4*nint(1d6*L), ' %'
   write(11,'(A)')
   write(11,'(A)') '======================================================='
   write(11,'(A)')

   write(11,F2) 'Points: ', points(0), '/', games
   write(11,'(A)')
   write(11,F3) '+', wins(0,0), ' =', draws(0,0), ' -', loses(0,0)
   write(11,F1) 'P ~ ', 1d-4*nint(1d6*P(0,draws(0,0))),' %'
   write(11,'(A)')
   write(11,F4,advance='no') 'Probability of win ', points(0), ' points out of '
   write(11,F5) games, ': ', 1d-4*nint(1d6*sum_P(0)), ' %'
   write(11,'(A)')
   write(11,'(A)') '-------------------------------------------------------'
   write(11,'(A)')

   do i = 1, i_max/2
     write(11,F2) 'Points: ', points(i), '/', games
     write(11,'(A)')
     do j = 0, int(i/2)
       write(11,F3) '+', wins(i,j), ' =', draws(i,j), ' -', loses(i,j)
       write(11,F1) 'P ~ ', 1d-4*nint(1d6*P(i,draws(i,j))),' %'
       write(11,'(A)')
     end do
     write(11,F4,advance='no') 'Probability of win ', points(i), ' points out of '
     write(11,F5) games, ': ', 1d-4*nint(1d6*sum_P(i)), ' %'
     write(11,'(A)')
     write(11,'(A)') '-------------------------------------------------------'
     write(11,'(A)')
   end do

   do i = i_max/2+1, i_max-1
     write(11,F2) 'Points: ', points(i), '/', games
     write(11,'(A)')
     do j = i-1, i-(1+int(0.5*(i_max-i))), -1
       write(11,F3) '+', wins(i,j), ' =', draws(i,j), ' -', loses(i,j)
       write(11,F1) 'P ~ ', 1d-4*nint(1d6*P(i,draws(i,j))),' %'
       write(11,'(A)')
     end do
     write(11,F4,advance='no') 'Probability of win ', points(i), ' points out of '
     write(11,F5) games, ': ', 1d-4*nint(1d6*sum_P(i)), ' %'
     write(11,'(A)')
     write(11,'(A)') '-------------------------------------------------------'
     write(11,'(A)')
   end do

   write(11,F2) 'Points: ', points(i_max), '/', games
   write(11,'(A)')
   write(11,F3) '+', wins(i_max,i_max), ' =', draws(i_max,i_max), ' -', loses(i_max,i_max)
   write(11,F1) 'P ~ ', 1d-4*nint(1d6*P(i_max,draws(i_max,i_max))),' %'
   write(11,'(A)')
   write(11,F4,advance='no') 'Probability of win ', points(i_max), ' points out of '
   write(11,F5) games, ': ', 1d-4*nint(1d6*sum_P(i_max)), ' %'
   write(11,'(A)')

   write(11,'(A)') '=============================================================='
   write(11,'(A)')
   write(11,'(A)') '                           SUMMARY:'
   write(11,'(A)')
   write(11,'(A)',advance='no') ' Probability that the first player wins the match ~ '
   write(11,F6) 1d-4*nint(1d6*prob_player_1_wins_the_match), ' %'
   write(11,'(A)',advance='no') '                      Probability of a tied match ~ '
   write(11,F6) 1d-4*nint(1d6*prob_of_a_tied_match), ' %'
   write(11,'(A)',advance='no') 'Probability that the second player wins the match ~ '
   write(11,F6) 1d-4*nint(1d6*prob_player_2_wins_the_match), ' %'
   write(11,'(A)')
   write(11,'(A)') '--------------------------------------------------------------'
   write(11,'(A)')
   write(11,'(A,F8.4,A)') ' Prob.(first player wins) + 0.5*Prob.(tied match) ~ ', 1d-4*nint(1d6*overall_1), ' %'
   write(11,'(A,F8.4,A)',advance='no') 'Prob.(second player wins) + 0.5*Prob.(tied match) ~ ', 1d-4*nint(1d6*overall_2), ' %'
     
   close(11)

   open(unit=10,file='Summary_of_probabilities.txt', status='unknown', action='write')
   write(10,F0) 'Probabilities for a match of ', games, ' games (rounded up to 0.0001 %):'
   write(10,'(A)')
   write(10,'(A,F7.2,A)') 'Rating difference (rounded up to 0.01 Elo): ', 1d-2*nint(1d2*delta), ' Elo.'
   write(10,'(A)')
   write(10,F1) 'Probability of a win  = W ~ ', 1d-4*nint(1d6*W), ' %'
   write(10,F1) 'Probability of a draw = D ~ ', 1d-4*nint(1d6*D), ' %'
   write(10,F1) 'Probability of a lose = L ~ ', 1d-4*nint(1d6*L), ' %'
   write(10,'(A)')
   write(10,'(A)') '=============================================================================================='
   write(10,'(A)')
   write(10,'(A)') 'Points:    Probabilities (%):                           Approximated graphical representation:'
   write(10,'(A)')
   do i = i_max, 0, -1
     write(10,F7,advance='no') points(i), '           ', 1d-4*nint(1d6*sum_P(i))
     if (relative_frequency(i) == 0) then
       write(10,'(A)')
     else if (relative_frequency(i) == 1) then
       write(10,'(A)') '            -'
     else if (relative_frequency(i) == 2) then
       write(10,'(A)') '            --'
     else if (relative_frequency(i) == 3) then
       write(10,'(A)') '            ---'
     else if (relative_frequency(i) == 4) then
       write(10,'(A)') '            ----'
     else if (relative_frequency(i) == 5) then
       write(10,'(A)') '            -----'
     else if (relative_frequency(i) == 6) then
       write(10,'(A)') '            ------'
     else if (relative_frequency(i) == 7) then
       write(10,'(A)') '            -------'
     else if (relative_frequency(i) == 8) then
       write(10,'(A)') '            --------'
     else if (relative_frequency(i) == 9) then
       write(10,'(A)') '            ---------'
     else if (relative_frequency(i) == 10) then
       write(10,'(A)') '            ----------'
     else if (relative_frequency(i) == 11) then
       write(10,'(A)') '            -----------'
     else if (relative_frequency(i) == 12) then
       write(10,'(A)') '            ------------'
     else if (relative_frequency(i) == 13) then
       write(10,'(A)') '            -------------'
     else if (relative_frequency(i) == 14) then
       write(10,'(A)') '            --------------'
     else if (relative_frequency(i) == 15) then
       write(10,'(A)') '            ---------------'
     else if (relative_frequency(i) == 16) then
       write(10,'(A)') '            ----------------'
     else if (relative_frequency(i) == 17) then
       write(10,'(A)') '            -----------------'
     else if (relative_frequency(i) == 18) then
       write(10,'(A)') '            ------------------'
     else if (relative_frequency(i) == 19) then
       write(10,'(A)') '            -------------------'
     else if (relative_frequency(i) == 20) then
       write(10,'(A)') '            --------------------'
     else if (relative_frequency(i) == 21) then
       write(10,'(A)') '            ---------------------'
     else if (relative_frequency(i) == 22) then
       write(10,'(A)') '            ----------------------'
     else if (relative_frequency(i) == 23) then
       write(10,'(A)') '            -----------------------'
     else if (relative_frequency(i) == 24) then
       write(10,'(A)') '            ------------------------'
     else if (relative_frequency(i) == 25) then
       write(10,'(A)') '            -------------------------'
     else if (relative_frequency(i) == 26) then
       write(10,'(A)') '            --------------------------'
     else if (relative_frequency(i) == 27) then
       write(10,'(A)') '            ---------------------------'
     else if (relative_frequency(i) == 28) then
       write(10,'(A)') '            ----------------------------'
     else if (relative_frequency(i) == 29) then
       write(10,'(A)') '            -----------------------------'
     else if (relative_frequency(i) == 30) then
       write(10,'(A)') '            ------------------------------'
     else if (relative_frequency(i) == 31) then
       write(10,'(A)') '            -------------------------------'
     else if (relative_frequency(i) == 32) then
       write(10,'(A)') '            --------------------------------'
     else if (relative_frequency(i) == 33) then
       write(10,'(A)') '            ---------------------------------'
     else if (relative_frequency(i) == 34) then
       write(10,'(A)') '            ----------------------------------'
     else if (relative_frequency(i) == 35) then
       write(10,'(A)') '            -----------------------------------'
     else if (relative_frequency(i) == 36) then
       write(10,'(A)') '            ------------------------------------'
     else if (relative_frequency(i) == 37) then
       write(10,'(A)') '            -------------------------------------'
     else if (relative_frequency(i) == 38) then
       write(10,'(A)') '            --------------------------------------'
     else if (relative_frequency(i) == 39) then
       write(10,'(A)') '            ---------------------------------------'
     else if (relative_frequency(i) == 40) then
       write(10,'(A)') '            ----------------------------------------'
     else if (relative_frequency(i) == 41) then
       write(10,'(A)') '            -----------------------------------------'
     else if (relative_frequency(i) == 42) then
       write(10,'(A)') '            ------------------------------------------'
     else if (relative_frequency(i) == 43) then
       write(10,'(A)') '            -------------------------------------------'
     else if (relative_frequency(i) == 44) then
       write(10,'(A)') '            --------------------------------------------'
     else if (relative_frequency(i) == 45) then
       write(10,'(A)') '            ---------------------------------------------'
     else if (relative_frequency(i) == 46) then
       write(10,'(A)') '            ----------------------------------------------'
     else if (relative_frequency(i) == 47) then
       write(10,'(A)') '            -----------------------------------------------'
     else if (relative_frequency(i) == 48) then
       write(10,'(A)') '            ------------------------------------------------'
     else if (relative_frequency(i) == 49) then
       write(10,'(A)') '            -------------------------------------------------'
     else if (relative_frequency(i) == 50) then
       write(10,'(A)') '            --------------------------------------------------'
     else if (relative_frequency(i) == 51) then
       write(10,'(A)') '            ---------------------------------------------------'
     else if (relative_frequency(i) == 52) then
       write(10,'(A)') '            ----------------------------------------------------'
     else if (relative_frequency(i) == 53) then
       write(10,'(A)') '            -----------------------------------------------------'
     else if (relative_frequency(i) == 54) then
       write(10,'(A)') '            ------------------------------------------------------'
     else if (relative_frequency(i) == 55) then
       write(10,'(A)') '            -------------------------------------------------------'
     else if (relative_frequency(i) == 56) then
       write(10,'(A)') '            --------------------------------------------------------'
     else if (relative_frequency(i) == 57) then
       write(10,'(A)') '            ---------------------------------------------------------'
     else if (relative_frequency(i) == 58) then
       write(10,'(A)') '            ----------------------------------------------------------'
     else if (relative_frequency(i) == 59) then
       write(10,'(A)') '            -----------------------------------------------------------'
     else if (relative_frequency(i) == 60) then
       write(10,'(A)') '            ------------------------------------------------------------'
     else if (relative_frequency(i) == 61) then
       write(10,'(A)') '            -------------------------------------------------------------'
     else if (relative_frequency(i) == 62) then
       write(10,'(A)') '            --------------------------------------------------------------'
     else if (relative_frequency(i) == 63) then
       write(10,'(A)') '            ---------------------------------------------------------------'
     else if (relative_frequency(i) == 64) then
       write(10,'(A)') '            ----------------------------------------------------------------'
     else if (relative_frequency(i) == 65) then
       write(10,'(A)') '            -----------------------------------------------------------------'
     else if (relative_frequency(i) == 66) then
       write(10,'(A)') '            ------------------------------------------------------------------'
     else if (relative_frequency(i) == 67) then
       write(10,'(A)') '            -------------------------------------------------------------------'
     else if (relative_frequency(i) == 68) then
       write(10,'(A)') '            --------------------------------------------------------------------'
     else if (relative_frequency(i) == 69) then
       write(10,'(A)') '            ---------------------------------------------------------------------'
     else if (relative_frequency(i) == 70) then
       write(10,'(A)') '            ----------------------------------------------------------------------'
     else if (relative_frequency(i) == 71) then
       write(10,'(A)') '            -----------------------------------------------------------------------'
     else if (relative_frequency(i) == 72) then
       write(10,'(A)') '            ------------------------------------------------------------------------'
     else if (relative_frequency(i) == 73) then
       write(10,'(A)') '            -------------------------------------------------------------------------'
     else if (relative_frequency(i) == 74) then
       write(10,'(A)') '            --------------------------------------------------------------------------'
     else if (relative_frequency(i) == 75) then
       write(10,'(A)') '            ---------------------------------------------------------------------------'
     else if (relative_frequency(i) == 76) then
       write(10,'(A)') '            ----------------------------------------------------------------------------'
     else if (relative_frequency(i) == 77) then
       write(10,'(A)') '            -----------------------------------------------------------------------------'
     else if (relative_frequency(i) == 78) then
       write(10,'(A)') '            ------------------------------------------------------------------------------'
     else if (relative_frequency(i) == 79) then
       write(10,'(A)') '            -------------------------------------------------------------------------------'
     else if (relative_frequency(i) == 80) then
       write(10,'(A)') '            --------------------------------------------------------------------------------'
     end if
   end do
   write(10,'(A)')
   write(10,'(A)') '=============================================================='
   write(10,'(A)')
   write(10,'(A)') '                           SUMMARY:'
   write(10,'(A)')
   write(10,'(A)',advance='no') ' Probability that the first player wins the match ~ '
   write(10,F6) 1d-4*nint(1d6*prob_player_1_wins_the_match), ' %'
   write(10,'(A)',advance='no') '                      Probability of a tied match ~ '
   write(10,F6) 1d-4*nint(1d6*prob_of_a_tied_match), ' %'
   write(10,'(A)',advance='no') 'Probability that the second player wins the match ~ '
   write(10,F6) 1d-4*nint(1d6*prob_player_2_wins_the_match), ' %'
   write(10,'(A)')
   write(10,'(A)') '--------------------------------------------------------------'
   write(10,'(A)')
   write(10,'(A,F8.4,A)') ' Prob.(first player wins) + 0.5*Prob.(tied match) ~ ', 1d-4*nint(1d6*overall_1), ' %'
   write(10,'(A,F8.4,A)',advance='no') 'Prob.(second player wins) + 0.5*Prob.(tied match) ~ ', 1d-4*nint(1d6*overall_2), ' %'

   close(10)

   call cpu_time(time)
   elapsed_time = time - time0

   write(*,'(A)') 'The results have been successfully saved into two files:'
   write(*,*)
   write(*,'(A)') '     Probabilities.txt'
   write(*,'(A)') '     Summary_of_probabilities.txt'
   write(*,*)
   write(*,'(A,F6.2,A)') 'Approximated total elapsed time: ', 1d-2*nint(1d2*elapsed_time), ' seconds.'  ! Rounded up to 0.01 seconds.
   write(*,*)
   write(*,'(A)') 'Thanks for using Probabilities_in_a_trinomial_distribution. Press Enter to exit.'
   read(*,'()')

end program Trinomial_distribution_probabilities
I haven't really tried to re-write anything, just simplify the code. I suspect the memory requirements can come down with some effort, but I haven't tried. On my machine (core i7, 2.9 GHz) for 1000 games (compiled with the Intel compiler and -fast -O3 -march=corei7-avx) the calculation takes ~0.13s, but writing the output files takes several seconds. I haven't investigated why it's so slow, but I find it surprising.

The main simplification I did is to replace

Code: Select all

if (condition) then
   stuff
   goto number
end if
more stuff

number
with

Code: Select all

if (condition) then
    stuff
else
    more stuff
end if
which does the same thing and is (much) simpler. Actually, once I'd done that it turned out that the entire calculation could be condensed into

Code: Select all

more stuff
I also replaced the factorial calculation with a lookup table, which is where I think most of the speed improvement actually comes from.
User avatar
Ajedrecista
Posts: 2114
Joined: Wed Jul 13, 2011 9:04 pm
Location: Madrid, Spain.

Re: New update of Probabilities_in_a_trinomial_distribution.

Post by Ajedrecista »

Hello again!

I have uploaded Probabilities_in_a_trinomial_distribution again:

Six_Fortran_95_tools.rar (685.43 KB)

The maximum number of supported games is now 1500. I hope that I have finished definitely the development of this programme. The Readme file is also updated along with the source code.
Evert wrote:The thing is, "kind=integer" is not portable across different compilers since the standard doesn't specify what number corresponds to what type of integer. There are intrinsics for getting the real kind that has a range of such-and-so that I don't remember off the top of my head. Either way, if you don't need more than double precision, I'd suggest not using more than double precision. While double is as fast as single on modern CPUs (with one caveat: if you have a large array, it may fit in cache if it's single but not when it's double precision), that's not true for extended or quad precision.
Evert wrote:

Code: Select all

   integer, parameter :: dbl = selected_real_kind(15,307)
I really need extended precision: the maximum factorial that I can calculate with double precision is 170! instead of 1754! with extended precision IIRC. Please take a look to double precision and extended precision for more info. Your suggested code compiled flawlessly in Silverfrost Plato IDE but it failed to calculate the trinomial distribution for 200 games... it must be the kind of real variables. You can try the following:

Code: Select all

   integer, parameter :: ext = selected_real_kind(18,4931)
Which is real(KIND=3) or simply real(3) in Fortran 95. I do not know if your compiler will accept it.
Evert wrote:I haven't really tried to re-write anything, just simplify the code. I suspect the memory requirements can come down with some effort, but I haven't tried. On my machine (core i7, 2.9 GHz) for 1000 games (compiled with the Intel compiler and -fast -O3 -march=corei7-avx) the calculation takes ~0.13s, but writing the output files takes several seconds. I haven't investigated why it's so slow, but I find it surprising.
I finally did not try to allocate variables. The new code took about 0.22 seconds in my Intel Pentium D930 (3 GHz) of year 2006, which is of course much slower than your i7.

I also do not know what is wrong with the output: I tried the old code in an Intel i5-760 (2.8 GHz) and it did the calculations for 1000 games in 38 seconds (it took around 270 or 280 seconds on my PC)... but the write of the output was incredibly slow! I stopped it at two minutes of print or so and it had written less than 5% of the total output (in the i5)! Usual times for write the full results for 1000 games were 63 or 64 seconds in my Pentium D930. You can imagine how clueless I were, specially if you know that I am not a computer expert. :shock:

I finally opted for a Solomonic solution: write the full output (two Notepads) up to games = 100; otherwise I only write the summary (one Notepad). Now, the slowest total elapsed time is less than a second in my PC. I consider that printing all the possibilities could be an info excess with all the probabilities with a high number of games, so I arbitrarily choosed the limit of 100, which is enough IMHO.

Thanks to the idea of calculate each factorial only once at start (the logic thing), I got rid of several 'go to' statements (they were too many even for me!) although I still left one, which is inside an if statement and outside of a do loop, so it should be executed once at most.
Evert wrote:I also replaced the factorial calculation with a lookup table, which is where I think most of the speed improvement actually comes from.
It was definitely THE idea. It is indeed very simple and easy but I did not program it in that evident way (in fact, I already thought that I was not using previously calculated results). I start to calculate factorials after the timing is started because it is fair. Sorry for continue using cpu_clock@() instead of cpu_time().

You have a modest place in the last line of the Readme file. ;) Thank you very much again!

The programme is decent now in terms of efficiency. Enjoy!

Regards from Spain.

Ajedrecista.
User avatar
Evert
Posts: 2929
Joined: Sat Jan 22, 2011 12:42 am
Location: NL

Re: New update of Probabilities_in_a_trinomial_distribution.

Post by Evert »

Ajedrecista wrote:I really need extended precision: the maximum factorial that I can calculate with double precision is 170! instead of 1754! with extended precision IIRC. Please take a look to double precision and extended precision for more info. Your suggested code compiled flawlessly in Silverfrost Plato IDE but it failed to calculate the trinomial distribution for 200 games... it must be the kind of real variables. You can try the following:

Code: Select all

   integer, parameter :: ext = selected_real_kind(18,4931)
Which is real(KIND=3) or simply real(3) in Fortran 95. I do not know if your compiler will accept it.
Correction: it's real(3) for your particular compiler, but that isn't portable to other compilers. real(KIND=selected_real_kind(18, 4931)) works properly here, but the corresponding kind is 16 for the Intel compiler (why? Don't know, but that's what it says if I print the value). As I said, hard-coding the kind variables as integers is not portable.

So I recommend doing it similar to how I did it above for maximum portability.
I finally did not try to allocate variables.
Keep it in mind for the future. It really helps a lot if you don't allocate more memory than you need (and arbitrary limits are annoying in general ;)).
Usual times for write the full results for 1000 games were 63 or 64 seconds in my Pentium D930. You can imagine how clueless I were, specially if you know that I am not a computer expert. :shock:
I have no idea why the output is so slow (I haven't looked into it much). It really shouldn't be.
It was definitely THE idea. It is indeed very simple and easy but I did not program it in that evident way (in fact, I already thought that I was not using previously calculated results). I start to calculate factorials after the timing is started because it is fair.
Calculating it once is fast anyway. :)
There may be a cleverer way to do the calculations for a large number of games (rather than brute-force), but I haven't thought about it at all.
Sorry for continue using cpu_clock@() instead of cpu_time().
It's not portable though, so I'd change it if you can (it also simplifies things because you don't need to ask for the speed of the CPU).
You have a modest place in the last line of the Readme file. ;) Thank you very much again!
Don't mention is!
User avatar
Ajedrecista
Posts: 2114
Joined: Wed Jul 13, 2011 9:04 pm
Location: Madrid, Spain.

Re: New update of Probabilities_in_a_trinomial_distribution.

Post by Ajedrecista »

Hello:

I have updated Probabilities_in_a_trinomial_distribution once again:

Six_Fortran_95_tools.rar (686.33 KB)

A good way to outsmart bounds of huge numbers is the use of logarithms: extended precision was limited up to factorial (1754)! Now I use logarithms if games > 1754. Things seem to work really well, so the new limit for my programme is established in 5000 games instead of the former limit of 1500 games! Now my tool uses around 770 MB in Windows XP (checked with the Task Manager), so I hope that most users will not have problems although I want to warn about it. The most extreme case of 5000 games only takes around nine or ten seconds in my computer of year 2006.

Happy May 1st!

Regards from Spain.

Ajedrecista.
User avatar
Ajedrecista
Posts: 2114
Joined: Wed Jul 13, 2011 9:04 pm
Location: Madrid, Spain.

New update of Probabilities_in_a_trinomial_distribution.

Post by Ajedrecista »

Hello:

I have updated Probabilities_in_a_trinomial_distribution once again. Sorry for the inconvenience of such frequent updates.

Six_Fortran_95_tools.rar (687.13 KB)

I hope that this is the last time that this programme is updated. Finally I consider that it is complete. Crossing fingers for being right this time.

I decided to not store values that I will not print later... it brought a doubling of speed more less. The used RAM is not a problem anymore (less than 10 MB now, verified with the Task Manager). As a bonus, I raised the limit up to 16000 games (I have problems with more games and I also think that computing a trinomial distribution for 16000 games is enough; just for curiosity, some tests of SF distributed testing framework can be checked now). This single core, 32-bit programme takes around 37.5 seconds of calculations in the case of 16000 games in my PC and around 40 seconds including the print of results in a Notepad. My computer is an Intel Pentium D930 (3 GHz) of year 2006, so nothing outstanding.

Gone are the times when 150 games were an incredible limit... :)

Enjoy!

Regards from Spain.

Ajedrecista.
User avatar
Ajedrecista
Posts: 2114
Joined: Wed Jul 13, 2011 9:04 pm
Location: Madrid, Spain.

New update of Probabilities_in_a_trinomial_distribution.

Post by Ajedrecista »

Hello:

I hope that this is my final update of Probabilities_in_a_trinomial_distribution and hopefully in all these six tools:

Six_Fortran_95_tools.rar (686.24 KB)

I added the cumulative distribution function, which I consider important (only numbers, not graphics). It was a fast addition.

The other change is the raise to the limit up to 50000 games. I changed the kind of the integers and everything works flawlessly for such a high number of games. A higher number of games can be computed just recompiling the source changing the correct parameter.

The issue of different output speeds puzzles me. I tried the most extreme case of 50000 games in two very different computers: an Intel i5-760 (2.8 GHz) and an Intel Pentium D930 (3 GHz). Here is some data that I remember, so numbers are approximated:

Code: Select all

                         i5-760     Pentium D930:
 Time of calculations:   2 min.        5.5 min.
Time of print results:   4 min.        10 sec.
I ran a single sample for each PC... I know that the correct method is averaging more samples.

The difference of time of calculations is logic (I expected around 3x for the Pentium D, so I was not much wrong)... but i5 was more than 20 times slower when printing results! Any thoughts will be welcome.

Have a nice day!

Regards from Spain.

Ajedrecista.