Losing integer array values

I written the following code to find an array of values then to search those values for matches to a set of conditions. The code appears to run without errors but for some reason I am losing the values to several of the array parameters. There are 4 parameters in each array and most of them are working fine but others output random large values.

program solve_gear_ratios

    implicit none

        integer::  found_solutions, tsolutions
        integer, parameter:: final_solutions = 40

    !Teeth parameters
        integer:: Tsa, Tsa_min, Tsa_max, Tra, Tra_min, Tra_max
        integer:: Pcha, Pcha_min, Pcha_max
        integer:: Pch(final_solutions), Ts(final_solutions), Tr(final_solutions)
    !Total Ratio Values
        real:: Rt, Rt_calc
        real:: PRa, PRa_min, PRa_max, PR1, PR2, PR3
        real:: PR(final_solutions)
    !Teeth Check values
        real:: Pta, Pta_calc, Pta_dif
    !Sun Pitch Diameters
        real:: Pdsa_calc
    !Planet Pd & OD
        real:: Pdpa, OdPa, OdPa_check
    !Ring Pitch Diameters
        real:: Pdra_calc, Pdra_max, Pdra_min
    !Planetary Ratios
        real:: Pclear
        real:: pi

!File Writer
        integer::unit_number, iostat, i, j, k
        character(len=32)::filename
        !character(len=200) :: row1, row2, row3, blank_row

        tsolutions = 0
        found_solutions = 0

        filename = 'azimuth-Planetary-data-101.csv'
        unit_number = 10

!Open File for writing
    open(unit = unit_number, file = filename, status = 'replace', action = 'write', iostat = iostat)
        if (iostat /= 0) then
            print*, 'Error opening file: ', filename
            stop
        end if

! Write header row
    write(unit_number, '(A)', iostat = iostat) 'Ratio, Pitch, Sun Teeth, Ring Teeth'

    if (iostat /= 0) then
        print*, 'Error opening file: ', filename
    end if

!Set System parameters
!Total Ratio
    Rt = 892.5
!Planet to Planet Clearance
    Pclear = 3e-2
    pi = 3.141592654
!Planetary 1 range parameters
    Pcha_min = 4
    Pcha_max = 128
    Tsa_min = 12
    Tsa_max = 48
    Tra_min = 40
    Tra_max = 640
    Pdra_min = 3.0
    Pdra_max = 4.9
    PRa_min = 9
    PRa_max = 16

i=0; j=0; k=0

    do Pcha = Pcha_min,Pcha_max
        do Tsa = Tsa_min, Tsa_max
                do Tra = Tra_min, Tra_max
!print*, P0, Ts0, Tr0
                    PRa =(1 + (real(Tra)/Tsa))
                    Pta = (Tra - Tsa) / 2
                    Pta_calc = (real(Tra)-real(Tsa))/2
                    Pta_dif = Pta_calc - Pta
                    Pdra_calc = real(Tra)/Pcha
                    Pdsa_calc = real(Tsa)/Pcha
                    OdPa = (Pta_calc +2 )/Pcha
                    OdPa_check = ((Pdsa_calc + Pdra_calc)*sin(pi/3.0)) - Pclear
                    Pdpa =real(Pta)/Pcha

!print*, 'PR0 =', PR0, 'Pdr0_calc =', Pdr0_calc, 'Pt0 =', Pt0, 'OdP0_check =', OdP0_check
                    if ((PRa < PRa_max) .and. (PRa > PRa_min)) then
                        if ((Pdra_calc <= Pdra_max) .and. (Pdra_calc >= Pdra_min)) then
                            if ((Pta_dif ==0) .and. (OdPa_check > OdPa)) then
!print*, 'PR0 =', PR0, 'Pdr0_calc =', Pdr0_calc, 'Pt0 =', Pt0, 'OdP0_check =', OdP0_check
!read(*,*)
                                    tsolutions = tsolutions +1

                                    PR(tsolutions) = PRa
                                    Ts(tsolutions) = Tsa
                                    Tr(tsolutions) = Tra
                                    Pch(tsolutions) = Pcha

!print*, tsolutions
!print*, P(tsolutions), Ts(tsolutions), Tr(tsolutions), P(tsolutions)
!read(*,*)
                            endif
                        endif
                    endif
                enddo
            enddo
            !print*, tsolutions
            !if (tsolutions >= tsolutions_max) exit
        enddo
!print*, 'Hello'
    do i = 1, tsolutions
        do j = 1, tsolutions
            if (j /= i .and. Pch(i) > Pch(j)) then
                do k = 1, tsolutions
                    if (k /= i .and. k /=j .and. Pch(j) > Pch(k)) then
                        PR1 = PR(i)
                        PR2 = PR(j)
                        PR3 = Rt / (PR1 * PR2)
                        Rt_calc = PR(i) * PR(j) * PR(k)

!print*, found_solutions

                        if (abs(Rt_calc - Rt) < 1e-1) then
                            found_solutions = found_solutions +1

                            print*, Rt_calc, Pch(i), PR(i), Ts(i), Tr(i)
                            print*, Rt_calc, Pch(j), PR(j), Ts(j), Tr(j)
                            print*, Rt_calc, Pch(k), PR(k), Ts(k), Tr(k)
                            print*, ''

    write(unit_number, '(F10.4, A)') Rt_calc
    write(unit_number, '(F10.4, A, I5, A, I5, A, I5)') PR(i), ',', Pch(i), ',', Ts(i), ',', Tr(i)
    write(unit_number, '(F10.4, A, I5, A, I5, A, I5)') PR(j), ',', Pch(j), ',', Ts(j), ',', Tr(j)
    write(unit_number, '(F10.4, A, I5, A, I5, A, I5)') PR(k), ',', Pch(k), ',', Ts(k), ',', TR(k)
    write(unit_number, '(A)') ''

    !write(unit_number, '(A)') TRIM(row1)
    !write(unit_number, '(A)') TRIM(row2)
    !write(unit_number, '(A)') TRIM(row3)
    !write(unit_number, '(A)') blank_row

    !print*, 'tsolutions =', tsolutions
                                if (found_solutions >= final_solutions) then
                                    print*, 'The maximum solutions have been found'
                                    print*, 'If additional solutions are required, increase tsolutions_max'
                                    stop
                                end if
                            endif
                        endif
                    enddo
                endif
            enddo
        enddo

    ! Close the file
        close(unit_number, iostat = iostat)

Print*, 'The data has been successfully saved to ', filename

end program

Here is a sample of the screen output the csv returns ******** for the missing values

 892.564026      1091809595   9.23076916              13         107
   892.564026              25   9.83333302              12         106
   892.564026              24   9.83333302              12         106

You should use debugging options when writing a code.

Compiling your code with gfortran -Wall -Wextra -fbounds-check and running gave

Fortran runtime error: Index '41' of dimension 1 of array 'pr' above upper bound of 40

pertaining to the line

PR(tsolutions) = PRa

Inserting the line


print*,"tsolutions, lbound(PR), ubound(PR) =", tsolutions, lbound(PR), ubound(PR)

before that line gave

tsolutions, lbound(PR), ubound(PR) = 41 1 40

before the program terminated, consistent with the error message.

1 Like

Adding to your answer,

I would also recommend using -fcheck=all flag to find other critical errors during runtime.

Documentation for OP: Code Gen Options (The GNU Fortran Compiler)

Thank you for the review, are there places in codeblocks where I can set these options without resorting to cmd prompt? Haven’t programmed in over 35 years so abit new in how to make these tools sing. Thanks again

never mind found them in compiler settings

I set those flags as you mentioned, I expect I would see the errors in the build log? but nothing, ran the same way with same issue. I don’t expect that I am hitting an array limit, running 64 bit compiler on a system with i7-12700 and 64 G RAM.

Ok, starting to get it! Thanks for the flag help. My problem seems to be with my code and my misunderstanding of arrays in fortran? The program finds all possible PR’s within the conditions set. Then I look to check that array ‘tsolutions’ for sets of 3 arrays within tsolutions that meet my second set of conditions. For that I am iterating between i,j.k = 1, tsolutions. Which makes sense to me since tsolutions is the size of the first array. As the program finds these combinations of 3 groups, ‘found_solutions’ they are written to a file, I limit those solutions to final_solutions = 100, the error is that somehow It is comparing the size of final solutions to tsolutions, which is as far a my understanding goes…makes no sense to me where tsolutions is an array being searched and final_soltuions is merely a variable set to limit found solutions. Perhaps its the way I am trying to stop the program?

if (found_solutions >= final_solutions) then
    print*, 'The maximum solutions have been found'
    print*, 'If additional solutions are required, increase final_solutions'
    stop
end if