PROGRAM matrices1 ! ! Author: Br. David Carlson ! ! Date: March 29, 2010 ! ! This program prompts the user for the values to use in 3 by 3 matrix A ! and hard codes the values for a second 3 by 3 matrix C. It then prints ! A + C, computed in two different ways. Of course the two answers ! should be the same. IMPLICIT NONE INTEGER, PARAMETER::n = 3 REAL, DIMENSION(n, n)::A, Answer REAL, DIMENSION(n, n):: C = RESHAPE( (/1.0, 2.0, 3.0, -1.0, 0.0, 0.5, 1.5, -2.5, 4.0/), (/3, 3/) ) CALL ReadMatrix(n, A) WRITE (*, *) 'Matrix A contains:' CALL WriteMatrix(n, A) WRITE (*, *) 'Matrix C contains:' CALL WriteMatrix(n, C) CALL AddMatrices(n, A, C, Answer) WRITE (*, *) 'Sum of A and C, computed with AddMatrices, is:' CALL WriteMatrix(n, Answer) Answer = A + C ! Shorthand way to add two matrices WRITE (*, *) 'Sum of A and C, computed as A + C, is:' CALL WriteMatrix(n, Answer) END PROGRAM matrices1 ! Given: n Number of rows (and columns) in matrix M. ! Task: To prompt the user to input the values to place in matrix M. ! Return: M The matrix M holding these values just entered. SUBROUTINE ReadMatrix(n, M) IMPLICIT NONE INTEGER, INTENT(IN)::n REAL, DIMENSION(n, n), INTENT(OUT)::M INTEGER::row, col DO row = 1, n DO col = 1, n WRITE (*, *) 'Enter the value for your matrix at row ', row, ' column ', col READ (*, *) M(row, col) ! Always put row index first, then column index. END DO END DO END SUBROUTINE ReadMatrix ! Given: n Number of rows (and columns) in matrix M. ! M n by n matrix of reals ! Task: To print the values of M in typical grid fashion. ! Return: Nothing SUBROUTINE WriteMatrix(n, M) IMPLICIT NONE INTEGER, INTENT(IN)::n REAL, DIMENSION(n, n), INTENT(IN)::M INTEGER::row, col DO row = 1, n WRITE (*, *) (M(row, col), col = 1, n) ! Implied DO loop prints items on the same line. ! Whereas each new WRITE prints on a new line. END DO END SUBROUTINE WriteMatrix ! Given: n Number of rows (and columns) in matrices M and P. ! M n by n matrix of reals ! P Another n by n matrix of reals ! Task: To add the matrices M and P. ! Return: Result, a matrix holding the sum of M and P. SUBROUTINE AddMatrices(n, M, P, Result) IMPLICIT NONE INTEGER, INTENT(IN)::n REAL, DIMENSION(n, n), INTENT(IN)::M, P REAL, DIMENSION(n, n), INTENT(OUT)::Result INTEGER::row, col DO row = 1, n DO col = 1, n Result(row, col) = M(row, col) + P(row, col) END DO END DO END SUBROUTINE AddMatrices