Skip to content

Commit

Permalink
renames real*8 to double precision
Browse files Browse the repository at this point in the history
  • Loading branch information
danielpeter committed Jan 27, 2025
1 parent bc125b7 commit bafe8d4
Show file tree
Hide file tree
Showing 22 changed files with 99 additions and 100 deletions.
16 changes: 8 additions & 8 deletions src/inverse_problem_for_source/CMT3D/cmt3d/cmt3d_constants.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,15 @@ module cmt3d_constants
implicit none

! mathematical constantS
real*8, parameter :: PI = 3.141592653589793d0
double precision, parameter :: PI = 3.141592653589793d0

! scale of cmt pars (latitude,longitude,depth and moment
! centroid time and half duration)
real*8, parameter :: SCALE_DELTA = 0.001 ! degree
real*8, parameter :: SCALE_DEPTH = 1.0 ! km
real*8, parameter :: SCALE_MOMENT = 1.0e+22 ! dyns*cm
real*8, parameter :: SCALE_CTIME = 1.0 ! seconds
real*8, parameter :: SCALE_HDUR = 1.0 ! seconds
double precision, parameter :: SCALE_DELTA = 0.001 ! degree
double precision, parameter :: SCALE_DEPTH = 1.0 ! km
double precision, parameter :: SCALE_MOMENT = 1.0e+22 ! dyns*cm
double precision, parameter :: SCALE_CTIME = 1.0 ! seconds
double precision, parameter :: SCALE_HDUR = 1.0 ! seconds

! maximum number of parameters
integer, parameter :: NPARMAX = 11
Expand All @@ -36,8 +36,8 @@ module cmt3d_constants
integer, parameter :: NML = 9

! small numbers
real*8, parameter :: EPS2 = 1.0d-2
real*8, parameter :: EPS5 = 1.0d-5
double precision, parameter :: EPS2 = 1.0d-2
double precision, parameter :: EPS5 = 1.0d-5
real, parameter :: SMALL = -huge(1.0)

! io unit for parameter files
Expand Down
6 changes: 3 additions & 3 deletions src/inverse_problem_for_source/CMT3D/cmt3d/cmt3d_flexwin.f90
Original file line number Diff line number Diff line change
Expand Up @@ -9,11 +9,11 @@ program cmt3d_flexwin

character(len=150) :: par_file
integer :: ier, i
real*8, dimension(:,:), allocatable :: A
real*8, dimension(:), allocatable :: b,dm
double precision, dimension(:,:), allocatable :: A
double precision, dimension(:), allocatable :: b,dm

integer :: yr,mo,jda,ho,mi
real*8:: sec, t_cmt, hdur, elat, elon, depth, moment_tensor(NM)
double precision :: sec, t_cmt, hdur, elat, elon, depth, moment_tensor(NM)


! read and print parameters
Expand Down
18 changes: 9 additions & 9 deletions src/inverse_problem_for_source/CMT3D/cmt3d/cmt3d_sub.f90
Original file line number Diff line number Diff line change
Expand Up @@ -207,11 +207,11 @@ end subroutine setup_data_weights
subroutine setup_matrix(A,b,npar)

integer, intent(in) :: npar
real*8, intent(out) :: A(npar,npar), b(npar)
double precision, intent(out) :: A(npar,npar), b(npar)

integer :: ios,nf,nw,nwint,i,j
real :: tstart, tend
real*8 :: A1(npar,npar), b1(npar)
double precision :: A1(npar,npar), b1(npar)

open(IOWIN,file=trim(flexwin_out_file),iostat=ios)
if (ios /= 0) stop 'Flexwin output file can not be found'
Expand Down Expand Up @@ -254,15 +254,15 @@ end subroutine setup_matrix
subroutine invert_cmt(A,b,dm,npar)

integer, intent(in) :: npar
real*8 , intent(inout) :: A(npar,npar), b(npar)
real*8 , intent(out) :: dm(npar)
double precision, intent(inout) :: A(npar,npar), b(npar)
double precision, intent(out) :: dm(npar)

real*8 :: old_par(npar),new_par(npar)
real*8 :: trace, max_row
double precision :: old_par(npar),new_par(npar)
double precision :: trace, max_row
logical :: linear_inversion,singular
integer :: na, niter, i
real*8 :: xout(NPARMAX+2), AA(NPARMAX+2,NPARMAX+2), bb(NPARMAX+2)
real*8 :: m1(npar),lam(2), mstart(npar)
double precision :: xout(NPARMAX+2), AA(NPARMAX+2,NPARMAX+2), bb(NPARMAX+2)
double precision :: m1(npar),lam(2), mstart(npar)
integer, parameter :: NMAX_NL_ITER = 10

! do we really need the extra scaling??
Expand Down Expand Up @@ -364,7 +364,7 @@ end subroutine invert_cmt
subroutine variance_reduction(dm,npar)

integer,intent(in) :: npar
real*8,intent(in) :: dm(npar)
double precision,intent(in) :: dm(npar)

integer :: ios, nf, nwint, nw, is, ie, i, j, npts, ishift, ishift_new
real :: b, dt, tstart, tend
Expand Down
16 changes: 8 additions & 8 deletions src/inverse_problem_for_source/CMT3D/cmt3d/cmt3d_sub2.f90
Original file line number Diff line number Diff line change
Expand Up @@ -148,8 +148,8 @@ subroutine compute_A_b(syn_file,data_file,data_weight,tstart,tend,A1,b1,npar)

character(len=*),intent(in) :: syn_file, data_file
real,intent(in) :: data_weight, tstart, tend
real*8, intent(out),dimension(:,:) :: A1
real*8, intent(out),dimension(:) :: b1
double precision, intent(out),dimension(:,:) :: A1
double precision, intent(out),dimension(:) :: b1
integer, intent(in) :: npar

real :: t0, dt, t0_1, dt1
Expand Down Expand Up @@ -245,13 +245,13 @@ end subroutine compute_A_b
subroutine get_f_df(npar,A,b,m,lam,mstart,fij,f0)

integer,intent(in) :: npar
real*8,intent(in) :: A(:,:),b(:)
real*8,intent(in) :: m(:),mstart(:)
real*8,intent(in) :: lam(:)
double precision,intent(in) :: A(:,:),b(:)
double precision,intent(in) :: m(:),mstart(:)
double precision,intent(in) :: lam(:)

real*8,intent(out) :: fij(:,:),f0(:)
double precision,intent(out) :: fij(:,:),f0(:)

real*8 :: dc1_dm(NM),dc2_dm(NM),dc2_dmi_dmj(NM,NM)
double precision :: dc1_dm(NM),dc2_dm(NM),dc2_dmi_dmj(NM,NM)
integer :: i,j

! U_j's
Expand Down Expand Up @@ -303,7 +303,7 @@ subroutine compute_new_syn(data_file,syn_file,npts,b,dt,dm)
character(len=*),intent(in):: data_file, syn_file
integer,intent(out) :: npts
real, intent(out) :: b, dt
real*8, intent(in) :: dm(:)
double precision, intent(in) :: dm(:)

real,dimension(NDATAMAX,NPARMAX) :: dsyn_sngl
real, dimension(NDATAMAX) :: time
Expand Down
15 changes: 7 additions & 8 deletions src/inverse_problem_for_source/CMT3D/cmt3d/cmt3d_sub3.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,13 +12,13 @@ module cmt3d_sub3
subroutine write_new_cmtsolution(cmt_file,new_cmt_file,new_par_all)

character(len=*),intent(in) :: cmt_file,new_cmt_file
real*8,intent(inout) :: new_par_all(NPARMAX)
double precision,intent(inout) :: new_par_all(NPARMAX)

integer, parameter :: NSIG_DIGIT = 6
character(len=150) :: pde_time,event_name,out_cmt
real*8 :: exponent
double precision :: exponent
integer :: i, nn, exp_largest, iflag
real*8 :: epsilon, s1, d1, r1, s2, d2, r2, mw, m0, m00
double precision :: epsilon, s1, d1, r1, s2, d2, r2, mw, m0, m00

open(21,file = cmt_file, status = 'old')
read(21,'(a)') pde_time
Expand Down Expand Up @@ -94,14 +94,13 @@ subroutine Gaussian_elimination(A,n,b,x,singular)
implicit none

integer,intent(in) :: n
real*8,intent(inout) :: A(:,:),b(:)
real*8,intent(out) :: x(:)
double precision,intent(inout) :: A(:,:),b(:)
double precision,intent(out) :: x(:)
logical,intent(out) :: singular

integer :: i,j,k,pivot_row
real*8 :: pivot,temp(n),temp1,l(n)
real*8 ,parameter :: EPS = 1.0e-12

double precision :: pivot,temp(n),temp1,l(n)
double precision ,parameter :: EPS = 1.0d-12

! perform Gaussian ellimination

Expand Down
16 changes: 8 additions & 8 deletions src/inverse_problem_for_source/CMT3D/cmt3d/cmt3d_sub4.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,12 +12,12 @@ subroutine rotate_cmt(cmt_par,npar,elat0,elon0,DIRECTION)
! DIRECTION = 1/-1: entering/leaving with cmt par read from /write to cmtsolution file
! in terms of Mij, dep, lon and lat

real*8, intent(inout) :: cmt_par(NPARMAX)
real*8, intent(in) :: elat0, elon0
double precision, intent(inout) :: cmt_par(NPARMAX)
double precision, intent(in) :: elat0, elon0
integer,intent(in) :: npar,DIRECTION

real*8 :: th, phi, loc(3), gl(3), moment(3,3), elon,elat,edep
real*8 :: rmat(3,3)
double precision :: th, phi, loc(3), gl(3), moment(3,3), elon,elat,edep
double precision :: rmat(3,3)

! check input arguments
if (DIRECTION /= 1 .and. DIRECTION /= -1) stop 'Error DIRECTION (1 or -1)'
Expand Down Expand Up @@ -83,11 +83,11 @@ end subroutine rotate_cmt

subroutine calc_rot_matrix(elon,elat,rmat)

real*8,intent(in) :: elon, elat
real*8,intent(out) :: rmat(3,3)
real*8 :: th,phi
double precision,intent(in) :: elon, elat
double precision,intent(out) :: rmat(3,3)
double precision :: th,phi

th=(90-elat)*PI/180
th = (90-elat)*PI/180
phi = elon*PI/180

rmat(1,1)=dsin(th)*dcos(phi)
Expand Down
16 changes: 8 additions & 8 deletions src/inverse_problem_for_source/CMT3D/cmt3d/cmt3d_utils.f
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@
c double couple, and their moment.

subroutine mij(m,epsilon,s1,d1,r1,s2,d2,r2,m0,m00,iflag)
implicit REAL*8(A-H,O-Z)
implicit double precision(A-H,O-Z)

dimension a(3,3),d(3),v(3,3),ae(3),an(3)
dimension ae1(3),an1(3),an2(3),ae2(3)
real*8 m(6), m0, m00
double precision m(6), m0, m00
common/mpa/ft,fd,fl,ft1,fd1,fl1,azt,aiht,azp,aihp,az0,aih0,
*d,clvd

Expand Down Expand Up @@ -173,7 +173,7 @@ subroutine mij(m,epsilon,s1,d1,r1,s2,d2,r2,m0,m00,iflag)
end

subroutine jacobi(a,n,np,d,v,nrot)
implicit REAL*8(A-H,O-Z)
implicit double precision(A-H,O-Z)
parameter (nmax=100)
dimension a(np,np),d(np),v(np,np),b(nmax),z(nmax)
do 12 ip=1,n
Expand Down Expand Up @@ -264,7 +264,7 @@ subroutine jacobi(a,n,np,d,v,nrot)
end

subroutine tdl(an,bn,ft,fd,fl)
implicit REAL*8(A-H,O-Z)
implicit double precision(A-H,O-Z)
dimension an(3),bn(3)
xn=an(1)
yn=an(2)
Expand Down Expand Up @@ -343,7 +343,7 @@ subroutine tdl(an,bn,ft,fd,fl)
end

subroutine azih(aa,az,aih)
implicit REAL*8(A-H,O-Z)
implicit double precision(A-H,O-Z)
dimension aa(3)
con=57.2957795
gx=aa(1)
Expand Down Expand Up @@ -379,9 +379,9 @@ subroutine sdr2moment(sphif,sdlt,slmda,moment,mrr,mtt,mpp,mrt,mrp,mtp)
c this subroutine converts eqk fault parameters to moment tensors
c for definitions see hiroo''s class notes
c
real*8 sphif,sdlt,slmda,moment
real*8 mrr,mtt,mpp,mrt,mrp,mtp
real*8 pi,phif,dlt,lmda
double precision sphif,sdlt,slmda,moment
double precision mrr,mtt,mpp,mrt,mrp,mtp
double precision pi,phif,dlt,lmda
c
pi=3.1415926
phif=sphif*pi/180
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -23,14 +23,14 @@ module cmt3d_variables
! inversion schemes
logical :: station_correction
logical :: zero_trace_inversion, double_couple_inversion
real*8 :: lambda
double precision :: lambda
! misc
logical :: write_new_syn


! other parameters used globally
! collect all pars in an array
real*8,dimension(NPARMAX) :: cmt_par,dcmt_par,new_cmt_par
double precision,dimension(NPARMAX) :: cmt_par,dcmt_par,new_cmt_par

! number of files and windows
integer :: nfiles,nwins(NRECMAX),nwin_total
Expand All @@ -41,7 +41,7 @@ module cmt3d_variables
character(len=150) :: data_file, syn_file

! scales of cmt pars
real*8 :: SCALE_PAR(NPARMAX)
double precision :: SCALE_PAR(NPARMAX)

end module cmt3d_variables

Expand Down
8 changes: 4 additions & 4 deletions src/inverse_problem_for_source/CMT3D/cmt3d/get_cmt.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@ subroutine get_cmt(cmt_file,yr,mo,jda,ho,mi,sec, &

implicit none

character(len=*) :: cmt_file
character(len=*), intent(in) :: cmt_file
integer :: yr,jda,ho,mi
real*8 :: sec,t_cmt,hdur,elat,elon,depth
real*8 :: moment_tensor(6)
double precision :: sec,t_cmt,hdur,elat,elon,depth
double precision :: moment_tensor(6)

integer :: i,ios,lstr,mo,da
real*8 :: mb,ms
double precision :: mb,ms
character(len=24) :: reg
character(len=5) :: datasource
character(len=150) :: string
Expand Down
8 changes: 4 additions & 4 deletions src/inverse_problem_for_source/CMT3D/grid3d/get_cmt.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@ subroutine get_cmt(cmt_file,yr,mo,jda,ho,mi,sec, &

implicit none

character(len=*) :: cmt_file
character(len=*), intent(in) :: cmt_file
integer :: yr,jda,ho,mi
real*8 :: sec,t_cmt,hdur,elat,elon,depth
real*8 :: moment_tensor(6)
double precision :: sec,t_cmt,hdur,elat,elon,depth
double precision :: moment_tensor(6)

integer :: i,ios,lstr,mo,da
real*8 :: mb,ms
double precision :: mb,ms
character(len=24) :: reg
character(len=5) :: datasource
character(len=150) :: string
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
module grid3d_constants

implicit none

! mathematical constant pi
real, parameter :: PI = 3.14159265

Expand Down
4 changes: 2 additions & 2 deletions src/inverse_problem_for_source/CMT3D/grid3d/grid3d_sub.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ subroutine set_parameters(par_file)
character(len=*),intent(in) :: par_file
! cmt_file
integer :: yr,mo,jda,ho,mi
real*8 :: sec,t_cmt,hdur,elat,elon,depth
real*8 :: moment_tensor(NM)
double precision :: sec,t_cmt,hdur,elat,elon,depth
double precision :: moment_tensor(NM)
real :: mw

integer :: ios
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -658,7 +658,7 @@ end subroutine clogc
subroutine ftinv(npow,s,zzign,dt,r)
!------------------------------------------------------------------

!implicit real*8(a-h,o-z)
!implicit double precision(a-h,o-z)
!dimension r(4096*4)
!complex s(4096*4)

Expand All @@ -682,7 +682,7 @@ end subroutine ftinv
subroutine rspec(s,np2)
!------------------------------------------------------------------

!implicit real*8(a-h,o-z)
!implicit double precision(a-h,o-z)
!complex s(4096*4)

complex*16 :: s(NDIM)
Expand All @@ -705,7 +705,7 @@ end subroutine rspec
subroutine remo(ny,nm,nd)
!------------------------------------------------------------------

!implicit real*8(a-h,o-z)
!implicit double precision(a-h,o-z)
!dimension m(12)
!data m/0,31,59,90,120,151,181,212,243,273,304,334/

Expand Down Expand Up @@ -748,7 +748,7 @@ subroutine staper(nt, fw, nev, v, ndim, a, w)
! tsturm for the tapers and use them in Slepians eq 18 to get the
! bandwidth retention factors (i.e. the eigenvalues) Thomson's
! normalisation is used with no attention to sign.
!implicit real*8(a-h,o-z)
!implicit double precision(a-h,o-z)
!dimension a(*),w(*),v(ndim,*)
!parameter (pi=3.14159265358979d0,r2=1.414213562373095d0)

Expand Down Expand Up @@ -852,7 +852,7 @@ subroutine tsturm(nt,n,a,b,w,nev,r,ndim,ev,ipar)
! subroutine root then direct recursion is used to get the eigenvector
! as this is always stable. Note ipar=0 for even tapers =1 for odd
! tapers
!implicit real*8(a-h,o-z)
!implicit double precision(a-h,o-z)
!parameter (epsi=1.d-15,epsi1=5.d-15)
!dimension a(*),b(*),ev(*),w(*),r(ndim,*)

Expand Down Expand Up @@ -921,7 +921,7 @@ end subroutine tsturm
subroutine root(u,el,elam,a,bb,w,n,ik)
!------------------------------------------------------------------

!implicit real*8(a-h,o-z)
!implicit double precision(a-h,o-z)
!parameter (epsi = 1.d-15, epsi1 = 5.d-15)
!dimension a(*),bb(*),w(*)

Expand Down
Loading

0 comments on commit bafe8d4

Please sign in to comment.