Skip to content

Instantly share code, notes, and snippets.

@nilforooshan
Last active March 30, 2019 10:07
Show Gist options
  • Save nilforooshan/953b5742b1acbda05abf634903ecc039 to your computer and use it in GitHub Desktop.
Save nilforooshan/953b5742b1acbda05abf634903ecc039 to your computer and use it in GitHub Desktop.
f90: Convert correlation and covariance matrices to each other. *.exe and *.out are the Windows and Linux executables.
PROGRAM corr_cov
IMPLICIT NONE
! Declarations
CHARACTER(20):: infile_var, infile_corr, infile_cov, outfile_cov, outfile_corr, exiit
INTEGER:: i, j, n, question, err10, err11, err13
REAL,DIMENSION(:),ALLOCATABLE:: var
REAL,DIMENSION(:,:),ALLOCATABLE:: corr, cov
! Opening prints
PRINT*,
PRINT*,
PRINT*, 'This program is written by Mohammad A. Nilforooshan.'
PRINT*, 'All rights reserved.'
PRINT*, 'http://sites.google.com/site/mannprofile/'
! Ask for the operation to do
PRINT*,
PRINT*,
PRINT*, 'Press 1 if you want to convert correlations to covariances.'
PRINT*, 'Press 2 if you want to convert covariances to correlations.'
PRINT*, 'Press another number to exit.'
READ*, question
IF (question/=1 .AND. question/=2) THEN
STOP
ELSE IF (question==1) THEN
! Converting correlations to covariances
! Ask for the input files, open and check them
PRINT*,
PRINT*,
PRINT*, 'Type the name of the input file for the correlation matrix.'
READ*, infile_corr
OPEN(UNIT=10, FILE=infile_corr, STATUS='OLD', IOSTAT=err10)
IF (err10/=0) THEN
PRINT*,
PRINT*,
PRINT*, 'Error reading file ',infile_corr
STOP
END IF
PRINT*,
PRINT*,
PRINT*, 'Type the name of the input file for the variance vector.'
READ*, infile_var
OPEN(UNIT=11, FILE=infile_var, STATUS='OLD', IOSTAT=err11)
IF (err11/=0) THEN
PRINT*,
PRINT*,
PRINT*, 'Error reading file ',infile_var
STOP
END IF
! Ask for the name of the output file
PRINT*,
PRINT*,
PRINT*, 'Type the name of the output file for the covariance matrix.'
READ*, outfile_cov
OPEN(UNIT=12, FILE=outfile_cov, STATUS='UNKNOWN')
! Ask the size of the correlation matrix
PRINT*,
PRINT*,
PRINT*, 'Number of columns in the correlation matrix?'
READ*, n
IF (n>40) THEN
PRINT*,
PRINT*,
PRINT*, 'Sorry, up to 40 columns is supprted!'
PRINT*, 'Contact programmer to get space for more columns.'
STOP
END IF
ALLOCATE(corr(n,n))
READ(10,*) ((corr(i,j),j=1,n),i=1,n)
! Read the variance array
ALLOCATE(var(n))
READ(11,*) (var(i),i=1,n)
var(j)=var(i)
! Calculate the covariance matrix
ALLOCATE(cov(n,n))
DO i=1,n
DO j=1,n
cov(i,j)=corr(i,j)*SQRT(var(i)*var(j))
END DO
END DO
! Write in the output file
DO i=1,n
WRITE(12,'(40F12.4)') (cov(i,j), j=1,n)
END DO
ELSE
! Converting covariances to correlations
! Ask for the input file, open and check it
PRINT*,
PRINT*,
PRINT*, 'Type the name of the input file for the covariance matrix.'
READ*, infile_cov
OPEN(UNIT=13, FILE=infile_cov, STATUS='OLD', IOSTAT=err13)
IF (err13/=0) THEN
PRINT*,
PRINT*,
PRINT*, 'Error reading file ',infile_cov
STOP
END IF
! Ask for the name of the output file
PRINT*,
PRINT*,
PRINT*, 'Type the name of the output file for the correlation matrix.'
READ*, outfile_corr
OPEN(UNIT=14, FILE=outfile_corr, STATUS='UNKNOWN')
! Ask the size of the covariance matrix
PRINT*,
PRINT*,
PRINT*, 'Number of columns in the covariance matrix?'
READ*, n
IF (n>40) THEN
PRINT*,
PRINT*,
PRINT*, 'Sorry, up to 40 columns is supprted!'
PRINT*, 'Contact programmer to get space for more columns.'
STOP
END IF
ALLOCATE(cov(n,n))
READ(13,*) ((cov(i,j),j=1,n),i=1,n)
! Calculate the correlation matrix
ALLOCATE(corr(n,n))
DO i=1,n
DO j=1,n
corr(i,j)=cov(i,j)/SQRT(cov(i,i)*cov(j,j))
END DO
END DO
! Write in the output file
DO i=1,n
WRITE(14,'(40F9.4)') (corr(i,j), j=1,n)
END DO
END IF
! Finished
PRINT*,
PRINT*,
PRINT*, 'Press any key to exit.'
READ*, exiit
IF (exiit=='a') THEN
GO TO 182
END IF
182 END PROGRAM corr_cov
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment