Welcome to AE Resources
Converted document Converted document

FORTRAN 90+: SUBROUTINE DEMONSTRATION

The use of the subroutines is demonstrated in the Theory and Examples sections using snippets of code. The Numerical Methods section has a number of codes that also demonstrate the use of these in full codes.
PROGRAM h5
​
IMPLICIT NONE
INTEGER :: i, j, tick, ios, n
INTEGER, PARAMETER :: r4 = selected_real_kind(4,32)
INTEGER, PARAMETER :: r8 = selected_real_kind(8,32)
REAL(KIND=r4), DIMENSION(:,:), ALLOCATABLE :: mA, cA, f
REAL(KIND=r4), DIMENSION(:), ALLOCATABLE :: mB, cB, sol
REAL(KIND=r8), DIMENSION(:), ALLOCATABLE :: dsol
​
!NOTE :: FILE FORMAT
!The file should be placed into the program as an input, e.g.
!     ./h5.e < fort1.20
!Meaning this is coming from a file named "fort1.20"
!
!The format of the data within the input file should be as follows:
!    N (Number of variables/equations)
!    Row 1 Coefficients of Input Matrix and Element 1 of Output Vector
!    Row 1 Coefficients of Input Matrix and Element 1 of Output Vector
!    ....
!    Row N Coefficients of Input Matrix and Element 1 of Output Vector
!    
!    e.g.
!    2
!    2, 100000, 100000
!    1, 1, 2
!    
!The above is for the equations:
!    2x + 100,000y = 100,000
!    x + y = 2
​
!Read in file
READ(5,*) n
!First line displays size of matrix
!Allocate A and B sizes
ALLOCATE(mA(n,n), cA(n,n), mB(n), cB(n), f(n,n), sol(n), dsol(n))
f(1:n,1:n) = 0
sol(1:n) = 0
dsol(1:n) = 0
!Read in the rest of the file
DO i = 1,n
	READ (5, *, IOSTAT=ios) (mA(i,j), j=1,n), mB(i)
ENDDO
​
!Original Equations
WRITE(*,*) ’Original Equations:  ’
DO i=1,n
	WRITE(*,*) mA(i,1:n), ’ == ’, mB(i)
ENDDO
cA = mA
cB = mB
WRITE(*,*)
​
!Make a copy of Matrices A and B for use
​
DO tick = 1,3,1
	SELECT CASE (tick)
	CASE(1)
		WRITE(*,*) ’Naive Strategy Solutions:’
		CALL gauss(n, cA, cB, sol, dsol)
		CALL myerr(n, mA, mB, sol, dsol)
		WRITE(*,*)
		WRITE(*,*)
	
	CASE(2)
		WRITE(*,*) ’Pivoting Strategy Solutions:’
		CALL pivot(n, mA, mB, cA, cB)
		CALL gauss(n, cA, cB, sol, dsol)
		CALL myerr(n, mA, mB, sol, dsol)
		WRITE(*,*)
		WRITE(*,*)
	
	CASE(3)
		WRITE(*,*) ’Scaling Strategy Solutions:’
		CALL scale(n, mA, mB, cA, cB)
		!Also involves a possible need for a pivot
		CALL pivot(n, cA, cB, cA, cB)
		CALL gauss(n, cA, cB, sol, dsol)
		CALL myerr(n, mA, mB, sol, dsol)
		WRITE(*,*)
		WRITE(*,*)
	END SELECT
ENDDO
​
​
CONTAINS
!!! code is continued on next page
Next Page →
Next Page →