Skip to content

Commit

Permalink
Merge pull request #78 from DusanJovic-NOAA/no_warn
Browse files Browse the repository at this point in the history
Clean up compiler warnings
  • Loading branch information
pjpegion authored Apr 17, 2024
2 parents 7dc4d9b + 36d87e5 commit 31e4e3e
Show file tree
Hide file tree
Showing 7 changed files with 18 additions and 12 deletions.
2 changes: 1 addition & 1 deletion cellular_automata_global.F90
Original file line number Diff line number Diff line change
Expand Up @@ -167,7 +167,7 @@ subroutine cellular_automata_global(kstep,restart,first_time_step,ca1_cpl,ca2_cp
else
! don't rely on compiler to truncate integer(8) to integer(4) on
! overflow, do wrap around explicitly.
count4 = mod(((iseed_ca+7)*mytile)*(i1+nx_full*(j1-1))+ 2147483648, 4294967296) - 2147483648
count4 = mod(((iseed_ca+7)*mytile)*(i1+nx_full*(j1-1))+ 2147483648_8, 4294967296_8) - 2147483648_8
endif
ct=1
do nf=1,nca
Expand Down
2 changes: 1 addition & 1 deletion cellular_automata_sgs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -296,7 +296,7 @@ subroutine cellular_automata_sgs(kstep,dtf,restart,first_time_step,sst,lsmsk,lak
else
! don't rely on compiler to truncate integer(8) to integer(4) on
! overflow, do wrap around explicitly.
count4 = mod((iseed_ca+mytile)*(i1+nx_full*(j1-1))+ 2147483648, 4294967296) - 2147483648
count4 = mod((iseed_ca+mytile)*(i1+nx_full*(j1-1))+ 2147483648_8, 4294967296_8) - 2147483648_8
endif
ct=1
do nf=1,nca
Expand Down
5 changes: 5 additions & 0 deletions plumes.F90
Original file line number Diff line number Diff line change
@@ -1,3 +1,6 @@
module plumes_mod

contains
subroutine plumes(V,L,AG,a,row,col,kend)
implicit none

Expand Down Expand Up @@ -165,3 +168,5 @@ subroutine plumes(V,L,AG,a,row,col,kend)


end subroutine plumes

end module plumes_mod
7 changes: 4 additions & 3 deletions spectral_transforms.F90
Original file line number Diff line number Diff line change
Expand Up @@ -723,11 +723,13 @@ SUBROUTINE RADB5_STOCHY (IDO,L1,CC,CH,WA1,WA2,WA3,WA4)
END

SUBROUTINE RADBG_STOCHY (IDO,IP,L1,IDL1,CC,C1,C2,CH,CH2,WA)
implicit real(kind=kind_dbl_prec) (A-H)
implicit real(kind=kind_dbl_prec) (O-Z)
implicit none
INTEGER :: IDO,IP,L1,IDL1
REAL(kind_dbl_prec) :: CH(IDO,L1,IP), CC(IDO,IP,L1), C1(IDO,L1,IP), C2(IDL1,IP), &
CH2(IDL1,IP) , WA(*)
REAL(kind_dbl_prec), parameter :: TPI=6.28318530717959
REAL(kind_dbl_prec) :: ARG, DCP, DSP, AI1, AI2, AR1, AR1H, DC2, DS2, AR2, AR2H
INTEGER :: I,J,K,IK, IDP2, IPP2, IPPH, JC, J2, IC, L, IS, IDIJ, NBD, LC
ARG = TPI/FLOAT(IP)
DCP = COS(ARG)
DSP = SIN(ARG)
Expand Down Expand Up @@ -1474,7 +1476,6 @@ subroutine stochy_la2ga(regin,imxin,jmxin,rinlon,rinlat,rlon,rlat, &
i2 = iindx2(i)
if(wrk(i) .eq. 0.0) then
write(6,*) ' la2ga: error'
call sleep(2)
stop
endif
enddo
Expand Down
4 changes: 1 addition & 3 deletions stochy_data_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -485,11 +485,9 @@ subroutine init_stochdata_ocn(nlevs,delt,iret)

integer :: nn,nm,stochlun,n,jcapin
integer :: l,jbasev,jbasod
integer :: indev,indod,indlsod,indlsev,varid1,varid2,varid3,varid4,ierr
integer :: indev,indod,varid1,varid2,varid3,varid4,ierr

real(kind_phys),allocatable :: noise_e(:,:),noise_o(:,:)
include 'function_indlsod'
include 'function_indlsev'
include 'netcdf.inc'
stochlun=99
levs=nlevs
Expand Down
4 changes: 2 additions & 2 deletions stochy_patterngenerator.F90
Original file line number Diff line number Diff line change
Expand Up @@ -158,8 +158,8 @@ subroutine patterngenerator_init(lscale, delt, tscale, stdev, iseed, rpattern,&
!count4 = iseed(np) + member_id
! don't rely on compiler to truncate integer(8) to integer(4) on
! overflow, do wrap around explicitly.
!count4 = mod(iseed(np) + member_id + 2147483648, 4294967296) - 2147483648
count4 = mod(iseed(np) + 2147483648, 4294967296) - 2147483648
!count4 = mod(iseed(np) + member_id + 2147483648_8, 4294967296_8) - 2147483648_8
count4 = mod(iseed(np) + 2147483648_8, 4294967296_8) - 2147483648_8
print *,'using seed',count4,iseed(np)!,member_id
endif
endif
Expand Down
6 changes: 4 additions & 2 deletions update_ca.F90
Original file line number Diff line number Diff line change
Expand Up @@ -289,6 +289,8 @@ subroutine update_cells_sgs(kstep,halo,dt,initialize_ca,iseed_ca,first_flag,rest
CA,ca_plumes,iini,ilives_in,uhigh,vhigh,dxhigh,nlives, &
nfracseed,nseed,nspinup,nf,nca_plumes,ncells,mytile)

use plumes_mod

implicit none

integer, intent(in) :: kstep,nxc,nyc,nlon,nlat,nxch,nych,nca,isc,iec,jsc,jec,npx,npy
Expand Down Expand Up @@ -395,7 +397,7 @@ subroutine update_cells_sgs(kstep,halo,dt,initialize_ca,iseed_ca,first_flag,rest
count_trunc = iscale*(count/iscale)
count4 = count - count_trunc + mytile *( i1+nx_full*(j1-1)) ! no need to multply by 7 since time will be different in sgs
else
count4 = mod((iseed_ca*nf+mytile)*(i1+nx_full*(j1-1))+ 2147483648, 4294967296) - 2147483648
count4 = mod((iseed_ca*nf+mytile)*(i1+nx_full*(j1-1))+ 2147483648_8, 4294967296_8) - 2147483648_8
endif
noise_b(i,j)=real(random_01_CB(kstep,count4),kind=8)
enddo
Expand Down Expand Up @@ -706,7 +708,7 @@ subroutine update_cells_global(kstep,halo,first_time_step,iseed_ca,restart,nca,n
count_trunc = iscale*(count/iscale)
count4 = count - count_trunc + mytile *( i1+nx_full*(j1-1)) ! no need to multply by 7 since time will be different in sgs
else
count4 = mod(iseed_ca*nf+(7*mytile)*(i1+nx_full*(j1-1))+ 2147483648, 4294967296) - 2147483648
count4 = mod(iseed_ca*nf+(7*mytile)*(i1+nx_full*(j1-1))+ 2147483648_8, 4294967296_8) - 2147483648_8
endif
noise_b(i,j)=real(random_01_CB(kstep,count4),kind=8)
enddo
Expand Down

0 comments on commit 31e4e3e

Please sign in to comment.