Weird behaviour using the product intrinsic function (Euler project number 11)

Hi all ,
I am at the Euler project number 11

Compiled with : ifort -O3 -arch COFFEELAKE -axCOFFEELAKE,SSE3 pr11.f90 -o pr11
This is my code :

PROGRAM pr11
  USE, INTRINSIC :: ISO_FORTRAN_ENV,ONLY: int16,int32
  IMPLICIT NONE

  INTEGER,PARAMETER :: m=20
  INTEGER(KIND=int16) :: input_matrix(m,m),element_product
  INTEGER(KIND=int32) :: greatest_product,top_left_product,top_right_product,&
       bottom_left_product, bottom_right_product, top_product, bottom_product,&
       left_product,right_product
  INTEGER(KIND=int16),ALLOCATABLE :: greatest_product_number_array(:),&
       test_array(:)
  INTEGER :: i,j,k,thickness,greatest_position_i,greatest_position_j

  WRITE(UNIT=*,FMT="(a)",ADVANCE='no') "Please enter the size of the range: "
  READ *, thickness

  IF (thickness .GT. m/2)&
       STOP "Range is greater than half the number of rows or columns"

  100 FORMAT(i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,&
           1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2)

  ALLOCATE(greatest_product_number_array(thickness))
  ALLOCATE(test_array(thickness))

  OPEN (UNIT=10,FILE='pr11_input.txt')
  READ (10,*) ((input_matrix(i,j),j=1,m),i=1,m)
  CLOSE(10)

  PRINT 100, ((input_matrix(i,j),j=1,m),i=1,m)

  greatest_product = 0
  DO i=thickness,m - ( thickness - 1 )
     DO j=thickness,m - ( thickness - 1 )

        top_left_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i-(k-1),j-(k-1))
           top_left_product = top_left_product * test_array(k)
        END DO

!        top_left_product = PRODUCT(test_array)
        IF (top_left_product .GT. greatest_product) THEN
           greatest_product = top_left_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        top_right_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i-(k-1),j+(k-1))
           top_right_product = top_right_product * test_array(k)
        END DO

!        top_right_product = PRODUCT(test_array)
        IF (top_right_product .GT. greatest_product) THEN
           greatest_product = top_right_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        bottom_left_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i+(k-1),j-(k-1))
           bottom_left_product = bottom_left_product * test_array(k)
        END DO

!        bottom_left_product = PRODUCT(test_array)
        IF (bottom_left_product .GT. greatest_product) THEN
           greatest_product = bottom_left_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        bottom_right_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i+(k-1),j+(k-1))
           bottom_right_product = bottom_right_product * test_array(k)
        END DO

!        bottom_right_product = PRODUCT(test_array)
        IF (bottom_right_product .GT. greatest_product) THEN
           greatest_product = bottom_right_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        top_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i-(k-1),j)
           top_product = top_product * test_array(k)
        END DO
!       top_product = PRODUCT(test_array)

        IF (top_product .GT. greatest_product) THEN
           greatest_product = top_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        bottom_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i+(k-1),j)
           bottom_product = bottom_product * test_array(k)
        END DO
!       bottom_product = PRODUCT(test_array)

        IF (bottom_product .GT. greatest_product) THEN
           greatest_product = bottom_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        left_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i,j-(k-1))
           left_product = left_product * test_array(k)
        END DO
!       left_product = PRODUCT(test_array)

        IF (left_product .GT. greatest_product) THEN
           greatest_product = left_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        right_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i,j+(k-1))
           right_product = right_product * test_array(k)
        END DO
!       right_product = PRODUCT(test_array)

        IF (right_product .GT. greatest_product) THEN
           greatest_product = right_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

     END DO
  END DO

  PRINT *, " "
  PRINT '(a,i0,a,i0)', "Found at ",greatest_position_i," ",greatest_position_j
  PRINT '(a,i0)', "The greatest product is ", greatest_product
  PRINT '(i0)', greatest_product_number_array

END PROGRAM pr11

This is the input file :

08 02 22 97 38 15 00 40 00 75 04 05 07 78 52 12 50 77 91 08
49 49 99 40 17 81 18 57 60 87 17 40 98 43 69 48 04 56 62 00
81 49 31 73 55 79 14 29 93 71 40 67 53 88 30 03 49 13 36 65
52 70 95 23 04 60 11 42 69 24 68 56 01 32 56 71 37 02 36 91
22 31 16 71 51 67 63 89 41 92 36 54 22 40 40 28 66 33 13 80
24 47 32 60 99 03 45 02 44 75 33 53 78 36 84 20 35 17 12 50
32 98 81 28 64 23 67 10 26 38 40 67 59 54 70 66 18 38 64 70
67 26 20 68 02 62 12 20 95 63 94 39 63 08 40 91 66 49 94 21
24 55 58 05 66 73 99 26 97 17 78 78 96 83 14 88 34 89 63 72
21 36 23 09 75 00 76 44 20 45 35 14 00 61 33 97 34 31 33 95
78 17 53 28 22 75 31 67 15 94 03 80 04 62 16 14 09 53 56 92
16 39 05 42 96 35 31 47 55 58 88 24 00 17 54 24 36 29 85 57
86 56 00 48 35 71 89 07 05 44 44 37 44 60 21 58 51 54 17 58
19 80 81 68 05 94 47 69 28 73 92 13 86 52 17 77 04 89 55 40
04 52 08 83 97 35 99 16 07 97 57 32 16 26 26 79 33 27 98 66
88 36 68 87 57 62 20 72 03 46 33 67 46 55 12 32 63 93 53 69
04 42 16 73 38 25 39 11 24 94 72 18 08 46 29 32 40 62 76 36
20 69 36 41 72 30 23 88 34 62 99 69 82 67 59 85 74 04 36 16
20 73 35 29 78 31 90 01 74 31 49 71 48 86 81 16 23 57 05 54
01 70 54 71 83 51 54 69 16 92 33 48 61 43 52 01 89 19 67 48
  1. People can improve the code if they want
  2. I have a problem when using the product intrinsic function, for some reason it gives a negative result which forced me to use a do loop to calculate the product. Can anyone tell me what I did wrong here ?

Did not actually check yet, but sounds like you overflowed the values allowed for an integer,
and this is causing the negative results. Using real arrays or possibly a larger integer kind may
resolve it.

changing the second and third integer declarations to int64 did the trick. Thanks

The edited code :

PROGRAM pr11
  USE, INTRINSIC :: ISO_FORTRAN_ENV,ONLY: int8,int16,int32,int64
  IMPLICIT NONE

  INTEGER,PARAMETER :: m=20
  INTEGER(KIND=int16) :: input_matrix(m,m)
  INTEGER(KIND=int64) :: greatest_product,top_left_product,top_right_product,&
       bottom_left_product, bottom_right_product, top_product, bottom_product,&
       left_product,right_product
  INTEGER(KIND=int64),ALLOCATABLE :: greatest_product_number_array(:),&
       test_array(:)
  INTEGER :: i,j,k,thickness,greatest_position_i,greatest_position_j

  WRITE(UNIT=*,FMT="(a)",ADVANCE='no') "Please enter the size of the range: "
  READ *, thickness

  IF (thickness .GT. m/2)&
       STOP "Range is greater than half the number of rows or columns"

  100 FORMAT(i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,&
           1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2,1X,i2)

  ALLOCATE(greatest_product_number_array(thickness))
  ALLOCATE(test_array(thickness))

  OPEN (UNIT=10,FILE='pr11_input.txt')
  READ (10,*) ((input_matrix(i,j),j=1,m),i=1,m)
  CLOSE(10)

  PRINT 100, ((input_matrix(i,j),j=1,m),i=1,m)

  greatest_product = 0
  DO i=thickness,m - ( thickness - 1 )
     DO j=thickness,m - ( thickness - 1 )

        top_left_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i-(k-1),j-(k-1))
        END DO
        top_left_product = PRODUCT(test_array)
        IF (top_left_product .GT. greatest_product) THEN
           greatest_product = top_left_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        top_right_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i-(k-1),j+(k-1))
        END DO
        top_right_product = PRODUCT(test_array)
        IF (top_right_product .GT. greatest_product) THEN
           greatest_product = top_right_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        bottom_left_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i+(k-1),j-(k-1))
        END DO
        bottom_left_product = PRODUCT(test_array)
        IF (bottom_left_product .GT. greatest_product) THEN
           greatest_product = bottom_left_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        bottom_right_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i+(k-1),j+(k-1))
        END DO
        bottom_right_product = PRODUCT(test_array)
        IF (bottom_right_product .GT. greatest_product) THEN
           greatest_product = bottom_right_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        top_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i-(k-1),j)
        END DO
        top_product = PRODUCT(test_array)
        IF (top_product .GT. greatest_product) THEN
           greatest_product = top_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        bottom_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i+(k-1),j)
        END DO
        bottom_product = PRODUCT(test_array)
        IF (bottom_product .GT. greatest_product) THEN
           greatest_product = bottom_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        left_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i,j-(k-1))
        END DO
        left_product = PRODUCT(test_array)
        IF (left_product .GT. greatest_product) THEN
           greatest_product = left_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

        right_product = 1
        DO k=1,thickness
           test_array(k) = input_matrix(i,j+(k-1))
        END DO
        right_product = PRODUCT(test_array)
        IF (right_product .GT. greatest_product) THEN
           greatest_product = right_product
           greatest_product_number_array = test_array
           greatest_position_i = i
           greatest_position_j = j
        END IF

     END DO
  END DO

  PRINT *, " "
  PRINT '(a,i0,a,i0)', "Found at ",greatest_position_i," ",greatest_position_j
  PRINT '(a,i0)', "The greatest product is ", greatest_product
  PRINT '(i0)', greatest_product_number_array

END PROGRAM pr11

I admit to not having read the problem, but assuming the input file is limited to values up to 99
if the input file “worst case” is that all the values are 99, and the maximum size to consider is
20/2, you want to harden it theoretically to handle answers up to 99*10, which would be a
problem using 64-bit signed integers, because

 99**10  =         90438207500880449001  
 huge(0_int64) = 9223372036854775807

If the file or the values can be bigger you need to make sure the worst case does not cause overflow, as very few intrinsics are required to catch overflow such as PRODUCT() or even
INT(), so you need to consider it, and turn on any related compiler flags you can.

So given my hypothetical limits what happens now with an input file that is all 99s?

1 Like

Ahh. I read the original problem. the original problem was limited to 99**4. Being an Overachiever got you in a little trouble, although you could have gone for the longest diagonal :>

1 Like

ohh so int32 is limited to 99**4 ? Did not know that since most documentation for the iso_fortran_env does not state this. Unless it does and I’ve missed it somewhere.

Now I wanna check this out. I will check what happens if all the numbers are 99 later in the day.

Also why the longest diagonal ?
This is the right answer as far as I have checked :

Please enter the size of the range: 4                      
 8  2 22 97 38 15  0 40  0 75  4  5  7 78 52 12 50 77 91  8
49 49 99 40 17 81 18 57 60 87 17 40 98 43 69 48  4 56 62  0
81 49 31 73 55 79 14 29 93 71 40 67 53 88 30  3 49 13 36 65
52 70 95 23  4 60 11 42 69 24 68 56  1 32 56 71 37  2 36 91
22 31 16 71 51 67 63 89 41 92 36 54 22 40 40 28 66 33 13 80
24 47 32 60 99  3 45  2 44 75 33 53 78 36 84 20 35 17 12 50
32 98 81 28 64 23 67 10 26 38 40 67 59 54 70 66 18 38 64 70
67 26 20 68  2 62 12 20 95 63 94 39 63  8 40 91 66 49 94 21
24 55 58  5 66 73 99 26 97 17 78 78 96 83 14 88 34 89 63 72
21 36 23  9 75  0 76 44 20 45 35 14  0 61 33 97 34 31 33 95
78 17 53 28 22 75 31 67 15 94  3 80  4 62 16 14  9 53 56 92
16 39  5 42 96 35 31 47 55 58 88 24  0 17 54 24 36 29 85 57
86 56  0 48 35 71 89  7  5 44 44 37 44 60 21 58 51 54 17 58
19 80 81 68  5 94 47 69 28 73 92 13 86 52 17 77  4 89 55 40
 4 52  8 83 97 35 99 16  7 97 57 32 16 26 26 79 33 27 98 66
88 36 68 87 57 62 20 72  3 46 33 67 46 55 12 32 63 93 53 69
 4 42 16 73 38 25 39 11 24 94 72 18  8 46 29 32 40 62 76 36
20 69 36 41 72 30 23 88 34 62 99 69 82 67 59 85 74  4 36 16
20 73 35 29 78 31 90  1 74 31 49 71 48 86 81 16 23 57  5 54
 1 70 54 71 83 51 54 69 16 92 33 48 61 43 52  1 89 19 67 48
                                                           
Found at 13 7                                              
The greatest product is 70600674                           
89                                                         
94                                                         
97                                                         
87                                                         

Just meant that 99**4 would not overflow a 32-bit int. The HUGE() intrinsic will tell you the maximum value supported by a type …

program biggest
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
! https://github.com/urbanjost/M_intrinsics/blob/master/md/HUGE.md
implicit none
character(len=*),parameter :: g='(*(g0,1x))'
write(*,g)8,huge(0_int8)
write(*,g)16,huge(0_int16)
write(*,g)32,huge(0_int32)
write(*,g)'99**4',99**4
write(*,g)64,huge(0_int64)
end program biggest

See HUGE for how to query the biggest value for a type.

I was just noting the original only asked for 4 values but you extended it to allow up to 10, but the most general question would be to look at all vectors that were rows, columns, or diagonals; and the largest vector from that set would be from corner to corner. Just kidding that since you had already gone far beyond the original question there was still more room to go :slight_smile:

1 Like

:smiley:

Also thank you once again for telling me about huge . Much appreciated .