78 logical fexist, opened
79 integer fsize, ncid, error, id_dim, nx, ny
80 character(len=256) :: outgrid =
"none"
81 character(len=256) :: inputorog =
"none"
82 logical :: do_oa = .true.
83 logical :: grid_from_file = .true.
84 integer :: mtnres,im,jm,nm,nr,nf0,nf1,efac,blat,nw
86 READ(5,*) mtnres,im,jm,nm,nr,nf0,nf1,efac,blat
100 print*,
"INPUTOROG=", trim(inputorog)
101 print*,
"IM,JM=", im, jm
109 print*, mtnres,im,jm,nm,nr,nf0,nf1,efac,blat
110 nw=(nm+1)*((nr+1)*nm+2)
113 print *,
' Starting terr12 mtnlm7_slm30.f IMN,JMN:',imn,jmn
116 if( trim(outgrid) .NE.
"none" )
then
117 inquire(file=trim(outgrid), exist=fexist)
118 if(.not. fexist)
then
119 print*,
"file "//trim(outgrid)//
" does not exist"
123 inquire( ncid,opened=opened )
124 if( .NOT.opened )
exit
127 print*,
"outgrid=", trim(outgrid)
128 error=nf__open(trim(outgrid),nf_nowrite,fsize,ncid)
129 call
netcdf_err(error,
'Open file '//trim(outgrid) )
130 error=nf_inq_dimid(ncid,
'nx', id_dim)
131 call
netcdf_err(error,
'inquire dimension nx from file '//
133 error=nf_inq_dimlen(ncid,id_dim,nx)
134 call
netcdf_err(error,
'inquire dimension nx length '//
135 &
'from file '//trim(outgrid) )
137 error=nf_inq_dimid(ncid,
'ny', id_dim)
138 call
netcdf_err(error,
'inquire dimension ny from file '//
140 error=nf_inq_dimlen(ncid,id_dim,ny)
141 call
netcdf_err(error,
'inquire dimension ny length '//
142 &
'from file '//trim(outgrid) )
144 if(im .ne. nx/2)
then
145 print*,
"IM=",im,
" /= grid file nx/2=",nx/2
146 print*,
"Set IM = ", nx/2
149 if(jm .ne. ny/2)
then
150 print*,
"JM=",jm,
" /= grid file ny/2=",ny/2
151 print*,
"Set JM = ", ny/2
155 call
netcdf_err(error,
'close file '//trim(outgrid) )
160 CALL
tersub(imn,jmn,im,jm,nm,nr,nf0,nf1,nw,efac,blat,
185 SUBROUTINE tersub(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,BLAT,
191 integer :: imn,jmn,im,jm,nw
192 character(len=*),
intent(in) :: outgrid
193 character(len=*),
intent(in) :: inputorog
194 integer :: nr,nf0,nf1
195 real,
parameter :: missing_value=-9999.
196 real,
PARAMETER :: pi=3.1415926535897931
197 integer :: efac, blat
198 integer,
PARAMETER :: nmt=14
199 INTEGER zslmx(2700,1350)
202 INTEGER,
allocatable:: zavg(:,:),zslm(:,:)
203 REAL(4),
allocatable:: gice(:,:),oclsm(:,:)
205 integer*1,
allocatable:: umd(:,:)
207 integer*2 glob(imn,jmn), i2save
208 logical grid_from_file
209 INTEGER kpds(200),kgds(200), zsave1,zsave2,itopo,kount
210 INTEGER kount2,islmx,jslmx,oldslm,msksrc,mskocn,notocn
211 REAL cosclt(jm),wgtclt(jm),rclt(jm),xlat(jm),diffx(jm/2)
213 LOGICAL is_south_pole(im,jm), is_north_pole(im,jm)
214 REAL geolon(im,jm),geolat(im,jm)
215 REAL,
allocatable :: tmpvar(:,:)
216 REAL geolon_c(im+1,jm+1),geolat_c(im+1,jm+1)
217 REAL dx(im,jm),dy(im,jm)
218 REAL slm(im,jm),oro(im,jm),var(im,jm),ors(nw),orf(im,jm)
219 REAL land_frac(im,jm)
220 REAL theta(im,jm),gamma(im,jm),sigma(im,jm),elvmax(im,jm)
221 REAL wz4(im,jm),var4(im,jm),oa(im,jm,4),ol(im,jm,4),slmi(im,jm)
222 integer ist(im,jm),ien(im,jm),jst(jm),jen(jm)
223 integer iwork(im,jm,4)
224 real work1(im,jm),work2(im,jm),work3(im,jm),work4(im,jm)
225 real work5(im,jm),work6(im,jm),glat(jmn)
226 LOGICAL spectr, revlat, filter
228 real hprime(im,jm,14)
229 real oaa(4),ola(4),sumdif,avedif,alon,alat
230 real,
allocatable :: oa_in(:,:,:), ol_in(:,:,:)
231 real,
allocatable :: slm_in(:,:), lon_in(:,:), lat_in(:,:)
232 integer numi(jm),ios,iosg,latg2,istat
233 integer maxc3,maxc4,maxc5,maxc6,maxc7,maxc8
234 integer lonsperlat(jm/2),itest,jtest
235 integer i, j, nx, ny, ncid, js, jn, iw, ie, k
236 integer it,jt,i1,error,id_dim,id_var,nx_in,ny_in
237 integer i_south_pole,j_south_pole,i_north_pole,j_north_pole
241 integer fsize,wgta,in,inw,ine,is,isw,ise,m,n,imt,iret
243 real dlat,phi,delxn,rs,rn,slma,oroa,vara,var4a,xn,xs,fff
245 real ::
timef,tbeg,tend,tbeg1
246 logical :: output_binary
247 output_binary = .false.
252 allocate (zavg(imn,jmn))
253 allocate (zslm(imn,jmn))
254 allocate (gice(imn+1,3601))
255 allocate (umd(imn,jmn))
256 allocate (oclsm(im,jm))
274 print *,
' In TERSUB, ITOPO=',itopo
275 if (mskocn .eq. 1)
then
276 print *,
' Ocean Model LSM Present and '
277 print *,
' Overrides OCEAN POINTS in LSM: mskocn=',mskocn
278 if (notocn .eq. 1)
then
279 print *,
' Ocean LSM Reversed: NOTOCN=',notocn
297 IF (msksrc .eq. 0 )
then
298 READ(14,12,iostat=ios) zslmx
302 print *,
' navy10 lake mask rd fail -- ios,MSKSRC:',ios,msksrc
305 print *,
' Attempt to open/read UMD 30" slmsk MSKSRC=',msksrc
311 open(10,file=
"landcover30.fixed",
312 & recl=43200*21600, access=
'direct',iostat=istat)
316 print *,
' UMD lake mask open failed -- ios,MSKSRC:',istat,msksrc
319 read(10, rec=1,iostat=istat) umd
320 print *,
' UMD lake mask opened OK -- ios,MSKSRC:',istat,msksrc
326 print *,
' UMD lake mask rd err -- trying navy 10',istat
328 print *,
' ***** MSKSRC set to 0 MSKSRC=',msksrc
329 if (msksrc .eq. 0 )
then
330 READ(14,12,iostat=ios) zslmx
333 print *,
' navy10 lake mask rd fail - ios,MSKSRC:',ios,msksrc
337 print *,
' UMD lake, UMD(50,50)=',umd(50,50),msksrc
345 print *,
' About to call read_g, ITOPO=',itopo
346 if ( itopo .ne. 0 ) call
read_g(glob,itopo)
365 print *,
' After read_g, glob(500,500)=',glob(500,500)
369 print*,
' IM, JM, NM, NR, NF0, NF1, EFAC, BLAT'
370 print*, im,jm,nm,nr,nf0,nf1,efac,blat
371 print *,
' imn,jmn,glob(imn,jmn)=',imn,jmn,glob(imn,jmn)
372 print *,
' UBOUND ZAVG=',ubound(zavg)
373 print *,
' UBOUND glob=',ubound(glob)
374 print *,
' UBOUND ZSLM=',ubound(zslm)
375 print *,
' UBOUND GICE=',ubound(gice)
376 print *,
' UBOUND OCLSM=',ubound(oclsm)
413 if ( umd(i,j) .eq. 0 ) zslm(i,j) = 0
414 zavg(i,j) = glob(i,j)
422 print *,
' NAVY 10 (8) slmsk for lakes, MSKSRC=',msksrc
430 zavg(i,j) = glob(i,j)
431 if ( glob(i,j) .eq. -9999 )
then
437 if ( zslmx(islmx,jslmx) .eq. 0 )
then
438 if ( j .gt. 8 .and. j .lt. jmn-8 )
then
439 if (i1 .gt. imn ) i1 = i1 - imn
441 if(zslm(i,j).eq.1 .and. oldslm .eq. 1 .and. zslm(i1,j).eq.1)
then
442 if (i .ne. 1) oldslm = zslm(i,j)
453 print *,
' ***** set ZAVG and slm from 30" glob, MSKSRC=',msksrc
460 zavg(i,j) = glob(i,j)
461 if ( glob(i,j) .eq. -9999 )
then
482 read(20,*,iostat=ios) latg2,lonsperlat
483 if(ios.ne.0.or.2*latg2.ne.jm)
then
487 print *,ios,latg2,
'COMPUTE TERRAIN ON A FULL GAUSSIAN GRID'
490 numi(j)=lonsperlat(j)
493 numi(j)=lonsperlat(jm+1-j)
495 print *,ios,latg2,
'COMPUTE TERRAIN ON A REDUCED GAUSSIAN GRID',
504 print *,
' SPECTR=',spectr,
' REVLAT=',revlat,
' ** with GICE-07 **'
506 CALL splat(4,jm,cosclt,wgtclt)
508 rclt(j) = acos(cosclt(j))
511 phi = rclt(j) * degrad
513 xlat(jm-j+1) = phi - 90.
516 CALL splat(0,jm,cosclt,wgtclt)
518 rclt(j) = acos(cosclt(j))
519 xlat(j) = 90.0 - rclt(j) * degrad
527 diffx(j) = xlat(j) - xlat(j-1)
528 sumdif = sumdif + diffx(j)
530 avedif=sumdif/(float(jm/2))
534 write (6,106) (xlat(j),j=jm,1,-1)
535 106
format( 10(f7.3,1x))
536 107
format( 10(f9.5,1x))
541 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
544 &
' Before GICE ZAVG(1,2)=',zavg(1,2),zslm(1,2)
546 &
' Before GICE ZAVG(1,12)=',zavg(1,12),zslm(1,12)
548 &
' Before GICE ZAVG(1,52)=',zavg(1,52),zslm(1,52)
550 &
' Before GICE ZAVG(1,112)=',zavg(1,jmn-112),zslm(1,112)
554 READ(15,iostat=iosg) gice
555 if(iosg .ne. 0 )
then
556 print *,
' *** Err on reading GICE record, iosg=',iosg
557 print *,
' exec continues but NO GICE correction done '
560 print *,
' GICE 30" Antarctica RAMP orog 43200x3616 read OK'
561 print *,
' Processing! '
562 print *,
' Processing! '
563 print *,
' Processing! '
568 if( gice(i,j) .ne. -99. .and. gice(i,j) .ne. -1.0 )
then
569 if ( gice(i,j) .gt. 0.)
then
570 zavg(i,j) = int( gice(i,j) + 0.5 )
590 152
format(1x,
' ZAVG(i=',i4,
' j=',i4,
')=',i5,i3,
591 &
' orig:',i5,i4,
' Lat=',f7.3,f8.2,
'E',
' GICE=',f8.1)
609 if (mskocn .eq. 1)
then
613 open(25,form=
'formatted',iostat=istat)
616 print *,
' Ocean lsm file Open failure: mskocn,istat=',mskocn,istat
619 print *,
' Ocean lsm file Opened OK: mskocn,istat=',mskocn,istat
625 read(25,*,iostat=ios)oclsm
630 print *,
' Rd fail: Ocean lsm - continue, mskocn,ios=',mskocn,ios
633 print *,
' Rd OK: ocean lsm: mskocn,ios=',mskocn,ios
637 if ( mskocn .eq. 1 )
then
640 if ( notocn .eq. 0 )
then
641 slmi(i,j) = float(nint(oclsm(i,j)))
643 if ( nint(oclsm(i,j)) .eq. 0)
then
651 print *,
' OCLSM',oclsm(1,1),oclsm(50,50),oclsm(75,75),oclsm(im,jm)
652 print *,
' SLMI:',slmi(1,1),slmi(50,50),slmi(75,75),slmi(im,jm)
660 print *,
' Not using Ocean model land sea mask'
663 if (mskocn .eq. 1)
then
664 print *,
' LSM:',oclsm(1,1),oclsm(50,50),oclsm(75,75),oclsm(im,jm)
668 grid_from_file = .false.
669 is_south_pole = .false.
670 is_north_pole = .false.
675 if( trim(outgrid) .NE.
"none" )
then
676 grid_from_file = .true.
677 inquire(file=trim(outgrid), exist=fexist)
678 if(.not. fexist)
then
679 print*,
"file "//trim(outgrid)//
" does not exist"
683 inquire( ncid,opened=opened )
684 if( .NOT.opened )
exit
687 print*,
"outgrid=", trim(outgrid)
688 error=nf__open(trim(outgrid),nf_nowrite,fsize,ncid)
689 call
netcdf_err(error,
'Open file '//trim(outgrid) )
690 error=nf_inq_dimid(ncid,
'nx', id_dim)
691 call
netcdf_err(error,
'inquire dimension nx from file '//
714 print*,
"Read the grid from file "//trim(outgrid)
716 allocate(tmpvar(nx+1,ny+1))
718 error=nf_inq_varid(ncid,
'x', id_var)
719 call
netcdf_err(error,
'inquire varid of x from file '
721 error=nf_get_var_double(ncid, id_var, tmpvar)
722 call
netcdf_err(error,
'inquire data of x from file '
725 do j = 1,ny+1;
do i = 1,nx+1
726 if(tmpvar(i,j) .NE. missing_value)
then
727 if(tmpvar(i,j) .GT. 360) tmpvar(i,j) = tmpvar(i,j) - 360
728 if(tmpvar(i,j) .LT. 0) tmpvar(i,j) = tmpvar(i,j) + 360
732 geolon(1:im,1:jm) = tmpvar(2:nx:2,2:ny:2)
733 geolon_c(1:im+1,1:jm+1) = tmpvar(1:nx+1:2,1:ny+1:2)
735 error=nf_inq_varid(ncid,
'y', id_var)
736 call
netcdf_err(error,
'inquire varid of y from file '
738 error=nf_get_var_double(ncid, id_var, tmpvar)
739 call
netcdf_err(error,
'inquire data of y from file '
741 geolat(1:im,1:jm) = tmpvar(2:nx:2,2:ny:2)
742 geolat_c(1:im+1,1:jm+1) = tmpvar(1:nx+1:2,1:ny+1:2)
751 do j = 1, ny+1;
do i = 1, nx+1
752 if( tmpvar(i,j) > maxlat )
then
757 if( tmpvar(i,j) < minlat )
then
764 if(maxlat < 89.9 )
then
768 if(minlat > -89.9 )
then
772 print*,
"minlat=", minlat,
"maxlat=", maxlat
773 print*,
"north pole supergrid index is ",
774 & i_north_pole, j_north_pole
775 print*,
"south pole supergrid index is ",
776 & i_south_pole, j_south_pole
779 if(i_south_pole >0 .and. j_south_pole > 0)
then
780 if(mod(i_south_pole,2)==0)
then
781 do j = 1, jm;
do i = 1, im
782 if(i==i_south_pole/2 .and. (j==j_south_pole/2
783 & .or. j==j_south_pole/2+1) )
then
784 is_south_pole(i,j) = .true.
785 print*,
"south pole at i,j=", i, j
789 do j = 1, jm;
do i = 1, im
790 if((i==i_south_pole/2 .or. i==i_south_pole/2+1)
791 & .and. (j==j_south_pole/2 .or.
792 & j==j_south_pole/2+1) )
then
793 is_south_pole(i,j) = .true.
794 print*,
"south pole at i,j=", i, j
799 if(i_north_pole >0 .and. j_north_pole > 0)
then
800 if(mod(i_north_pole,2)==0)
then
801 do j = 1, jm;
do i = 1, im
802 if(i==i_north_pole/2 .and. (j==j_north_pole/2 .or.
803 & j==j_north_pole/2+1) )
then
804 is_north_pole(i,j) = .true.
805 print*,
"north pole at i,j=", i, j
809 do j = 1, jm;
do i = 1, im
810 if((i==i_north_pole/2 .or. i==i_north_pole/2+1)
811 & .and. (j==j_north_pole/2 .or.
812 & j==j_north_pole/2+1) )
then
813 is_north_pole(i,j) = .true.
814 print*,
"north pole at i,j=", i, j
821 allocate(tmpvar(nx,ny))
822 error=nf_inq_varid(ncid,
'area', id_var)
823 call
netcdf_err(error,
'inquire varid of area from file '
825 error=nf_get_var_double(ncid, id_var, tmpvar)
826 call
netcdf_err(error,
'inquire data of area from file '
831 dx(i,j) = sqrt(tmpvar(2*i-1,2*j-1)+tmpvar(2*i,2*j-1)
832 & +tmpvar(2*i-1,2*j )+tmpvar(2*i,2*j ))
858 write(6,*)
' Timer 1 time= ',tend-tbeg
860 if(grid_from_file)
then
862 CALL
makemt2(zavg,zslm,oro,slm,land_frac,var,var4,glat,
863 & im,jm,imn,jmn,geolon_c,geolat_c)
865 write(6,*)
' MAKEMT2 time= ',tend-tbeg
867 CALL
makemt(zavg,zslm,oro,slm,var,var4,glat,
868 & ist,ien,jst,jen,im,jm,imn,jmn,xlat,numi)
871 call
minmxj(im,jm,oro,
' ORO')
872 call
minmxj(im,jm,slm,
' SLM')
873 call
minmxj(im,jm,var,
' VAR')
874 call
minmxj(im,jm,var4,
' VAR4')
895 if(grid_from_file)
then
897 CALL
makepc2(zavg,zslm,theta,gamma,sigma,glat,
898 1 im,jm,imn,jmn,geolon_c,geolat_c)
900 write(6,*)
' MAKEPC2 time= ',tend-tbeg
902 CALL
makepc(zavg,zslm,theta,gamma,sigma,glat,
903 1 ist,ien,jst,jen,im,jm,imn,jmn,xlat,numi)
906 call
minmxj(im,jm,theta,
' THETA')
907 call
minmxj(im,jm,gamma,
' GAMMA')
908 call
minmxj(im,jm,sigma,
' SIGMA')
917 call
minmxj(im,jm,oro,
' ORO')
918 print*,
"inputorog=", trim(inputorog)
919 if(grid_from_file)
then
920 if(trim(inputorog) ==
"none")
then
921 print*,
"calling MAKEOA2 to compute OA, OL"
923 CALL
makeoa2(zavg,zslm,var,glat,oa,ol,iwork,elvmax,oro,
924 1 work1,work2,work3,work4,work5,work6,
925 2 im,jm,imn,jmn,geolon_c,geolat_c,
926 3 geolon,geolat,dx,dy,is_south_pole,is_north_pole)
928 write(6,*)
' MAKEOA2 time= ',tend-tbeg
931 error=nf__open(trim(inputorog),nf_nowrite,fsize,ncid)
932 call
netcdf_err(error,
'Open file '//trim(inputorog) )
933 error=nf_inq_dimid(ncid,
'lon', id_dim)
934 call
netcdf_err(error,
'inquire dimension lon from file '//
936 error=nf_inq_dimlen(ncid,id_dim,nx_in)
937 call
netcdf_err(error,
'inquire dimension lon length '//
938 &
'from file '//trim(inputorog) )
939 error=nf_inq_dimid(ncid,
'lat', id_dim)
940 call
netcdf_err(error,
'inquire dimension lat from file '//
942 error=nf_inq_dimlen(ncid,id_dim,ny_in)
943 call
netcdf_err(error,
'inquire dimension lat length '//
944 &
'from file '//trim(inputorog) )
946 print*,
"extrapolate OA, OL from Gaussian grid with nx=",
947 & nx_in,
", ny=", ny_in
948 allocate(oa_in(nx_in,ny_in,4), ol_in(nx_in,ny_in,4))
949 allocate(slm_in(nx_in,ny_in) )
950 allocate(lon_in(nx_in,ny_in), lat_in(nx_in,ny_in) )
952 error=nf_inq_varid(ncid,
'oa1', id_var)
953 call
netcdf_err(error,
'inquire varid of oa1 from file '
954 & //trim(inputorog) )
955 error=nf_get_var_double(ncid, id_var, oa_in(:,:,1))
956 call
netcdf_err(error,
'inquire data of oa1 from file '
957 & //trim(inputorog) )
958 error=nf_inq_varid(ncid,
'oa2', id_var)
959 call
netcdf_err(error,
'inquire varid of oa2 from file '
960 & //trim(inputorog) )
961 error=nf_get_var_double(ncid, id_var, oa_in(:,:,2))
962 call
netcdf_err(error,
'inquire data of oa2 from file '
963 & //trim(inputorog) )
964 error=nf_inq_varid(ncid,
'oa3', id_var)
965 call
netcdf_err(error,
'inquire varid of oa3 from file '
966 & //trim(inputorog) )
967 error=nf_get_var_double(ncid, id_var, oa_in(:,:,3))
968 call
netcdf_err(error,
'inquire data of oa3 from file '
969 & //trim(inputorog) )
970 error=nf_inq_varid(ncid,
'oa4', id_var)
971 call
netcdf_err(error,
'inquire varid of oa4 from file '
972 & //trim(inputorog) )
973 error=nf_get_var_double(ncid, id_var, oa_in(:,:,4))
974 call
netcdf_err(error,
'inquire data of oa4 from file '
975 & //trim(inputorog) )
977 error=nf_inq_varid(ncid,
'ol1', id_var)
978 call
netcdf_err(error,
'inquire varid of ol1 from file '
979 & //trim(inputorog) )
980 error=nf_get_var_double(ncid, id_var, ol_in(:,:,1))
981 call
netcdf_err(error,
'inquire data of ol1 from file '
982 & //trim(inputorog) )
983 error=nf_inq_varid(ncid,
'ol2', id_var)
984 call
netcdf_err(error,
'inquire varid of ol2 from file '
985 & //trim(inputorog) )
986 error=nf_get_var_double(ncid, id_var, ol_in(:,:,2))
987 call
netcdf_err(error,
'inquire data of ol2 from file '
988 & //trim(inputorog) )
989 error=nf_inq_varid(ncid,
'ol3', id_var)
990 call
netcdf_err(error,
'inquire varid of ol3 from file '
991 & //trim(inputorog) )
992 error=nf_get_var_double(ncid, id_var, ol_in(:,:,3))
993 call
netcdf_err(error,
'inquire data of ol3 from file '
994 & //trim(inputorog) )
995 error=nf_inq_varid(ncid,
'ol4', id_var)
996 call
netcdf_err(error,
'inquire varid of ol4 from file '
997 & //trim(inputorog) )
998 error=nf_get_var_double(ncid, id_var, ol_in(:,:,4))
999 call
netcdf_err(error,
'inquire data of ol4 from file '
1000 & //trim(inputorog) )
1002 error=nf_inq_varid(ncid,
'slmsk', id_var)
1003 call
netcdf_err(error,
'inquire varid of slmsk from file '
1004 & //trim(inputorog) )
1005 error=nf_get_var_double(ncid, id_var, slm_in)
1006 call
netcdf_err(error,
'inquire data of slmsk from file '
1007 & //trim(inputorog) )
1009 error=nf_inq_varid(ncid,
'geolon', id_var)
1010 call
netcdf_err(error,
'inquire varid of geolon from file '
1011 & //trim(inputorog) )
1012 error=nf_get_var_double(ncid, id_var, lon_in)
1013 call
netcdf_err(error,
'inquire data of geolon from file '
1014 & //trim(inputorog) )
1016 error=nf_inq_varid(ncid,
'geolat', id_var)
1017 call
netcdf_err(error,
'inquire varid of geolat from file '
1018 & //trim(inputorog) )
1019 error=nf_get_var_double(ncid, id_var, lat_in)
1020 call
netcdf_err(error,
'inquire data of geolat from file '
1021 & //trim(inputorog) )
1024 do j=1,ny_in;
do i=1,nx_in
1025 if(slm_in(i,j) == 2) slm_in(i,j) = 0
1028 error=nf_close(ncid)
1030 & //trim(inputorog) )
1032 print*,
"calling MAKEOA3 to compute OA, OL"
1033 CALL
makeoa3(zavg,zslm,var,glat,oa,ol,iwork,elvmax,oro,slm,
1034 1 work1,work2,work3,work4,work5,work6,
1035 2 im,jm,imn,jmn,geolon_c,geolat_c,
1036 3 geolon,geolat,is_south_pole,is_north_pole,nx_in,ny_in,
1037 4 oa_in,ol_in,slm_in,lon_in,lat_in)
1040 CALL
makeoa(zavg,var,glat,oa,ol,iwork,elvmax,oro,
1041 1 work1,work2,work3,work4,
1043 3 ist,ien,jst,jen,im,jm,imn,jmn,xlat,numi)
1046 call
minmxj(im,jm,oa,
' OA')
1047 call
minmxj(im,jm,ol,
' OL')
1048 call
minmxj(im,jm,elvmax,
' ELVMAX')
1049 call
minmxj(im,jm,oro,
' ORO')
1069 if (elvmax(i,j) .gt. 3000.) maxc3 = maxc3 +1
1070 if (elvmax(i,j) .gt. 4000.) maxc4 = maxc4 +1
1071 if (elvmax(i,j) .gt. 5000.) maxc5 = maxc5 +1
1072 if (elvmax(i,j) .gt. 6000.) maxc6 = maxc6 +1
1073 if (elvmax(i,j) .gt. 7000.) maxc7 = maxc7 +1
1074 if (elvmax(i,j) .gt. 8000.) maxc8 = maxc8 +1
1077 print *,
' MAXC3:',maxc3,maxc4,maxc5,maxc6,maxc7,maxc8
1082 print *,
' ===> Replacing ELVMAX with ELVMAX-ORO <=== '
1083 print *,
' ===> if ELVMAX<=ORO replace with proxy <=== '
1084 print *,
' ===> the sum of mean orog (ORO) and std dev <=== '
1087 if (elvmax(i,j) .lt. oro(i,j) )
then
1089 elvmax(i,j) = max( 3. * var(i,j),0.)
1091 elvmax(i,j) = max( elvmax(i,j) - oro(i,j),0.)
1103 if (elvmax(i,j) .gt. 3000.) maxc3 = maxc3 +1
1104 if (elvmax(i,j) .gt. 4000.) maxc4 = maxc4 +1
1105 if (elvmax(i,j) .gt. 5000.) maxc5 = maxc5 +1
1106 if (elvmax(i,j) .gt. 6000.) maxc6 = maxc6 +1
1107 if (elvmax(i,j) .gt. 7000.) maxc7 = maxc7 +1
1108 if (elvmax(i,j) .gt. 8000.) maxc8 = maxc8 +1
1111 print *,
' after MAXC 3-6 km:',maxc3,maxc4,maxc5,maxc6
1113 call
mnmxja(im,jm,elvmax,itest,jtest,
' ELVMAX')
1118 print *,
' Testing at point (itest,jtest)=',itest,jtest
1119 print *,
' SLM(itest,jtest)=',slm(itest,jtest),itest,jtest
1120 print *,
' ORO(itest,jtest)=',oro(itest,jtest),itest,jtest
1123 IF(slm(i,j).EQ.0.)
THEN
1152 if ( mskocn .eq. 1 )
then
1156 if (abs(oro(i,j)) .lt. 1. )
then
1157 slm(i,j) = slmi(i,j)
1159 if ( slmi(i,j) .eq. 1. .and. slm(i,j) .eq. 1) slm(i,j) = 1
1160 if ( slmi(i,j) .eq. 0. .and. slm(i,j) .eq. 0) slm(i,j) = 0
1161 if ( slmi(i,j) .eq. 0. .and. slm(i,j) .eq. 1) slm(i,j) = 0
1162 if ( slmi(i,j) .eq. 0. .and. slm(i,j) .eq. 0) slm(i,j) = 0
1167 print *,
' SLM(itest,jtest)=',slm(itest,jtest),itest,jtest
1168 print *,
' ORO(itest,jtest)=',oro(itest,jtest),itest,jtest
1174 rn=
REAL(numi(jn))/
REAL(numi(j))
1175 rs=
REAL(numi(js))/
REAL(numi(j))
1179 slma=slm(iw,j)+slm(ie,j)
1180 oroa=oro(iw,j)+oro(ie,j)
1181 vara=var(iw,j)+var(ie,j)
1182 var4a=var4(iw,j)+var4(ie,j)
1184 oaa(k)=oa(iw,j,k)+oa(ie,j,k)
1186 ola(k)=ol(iw,j,k)+ol(ie,j,k)
1190 IF(abs(xn-nint(xn)).LT.1.e-2)
THEN
1191 in=mod(nint(xn)-1,numi(jn))+1
1192 inw=mod(in+numi(jn)-2,numi(jn))+1
1193 ine=mod(in,numi(jn))+1
1194 slma=slma+slm(inw,jn)+slm(in,jn)+slm(ine,jn)
1195 oroa=oroa+oro(inw,jn)+oro(in,jn)+oro(ine,jn)
1196 vara=vara+var(inw,jn)+var(in,jn)+var(ine,jn)
1197 var4a=var4a+var4(inw,jn)+var4(in,jn)+var4(ine,jn)
1199 oaa(k)=oaa(k)+oa(inw,jn,k)+oa(in,jn,k)+oa(ine,jn,k)
1200 ola(k)=ola(k)+ol(inw,jn,k)+ol(in,jn,k)+ol(ine,jn,k)
1205 ine=mod(inw,numi(jn))+1
1206 slma=slma+slm(inw,jn)+slm(ine,jn)
1207 oroa=oroa+oro(inw,jn)+oro(ine,jn)
1208 vara=vara+var(inw,jn)+var(ine,jn)
1209 var4a=var4a+var4(inw,jn)+var4(ine,jn)
1211 oaa(k)=oaa(k)+oa(inw,jn,k)+oa(ine,jn,k)
1212 ola(k)=ola(k)+ol(inw,jn,k)+ol(ine,jn,k)
1217 IF(abs(xs-nint(xs)).LT.1.e-2)
THEN
1218 is=mod(nint(xs)-1,numi(js))+1
1219 isw=mod(is+numi(js)-2,numi(js))+1
1220 ise=mod(is,numi(js))+1
1221 slma=slma+slm(isw,js)+slm(is,js)+slm(ise,js)
1222 oroa=oroa+oro(isw,js)+oro(is,js)+oro(ise,js)
1223 vara=vara+var(isw,js)+var(is,js)+var(ise,js)
1224 var4a=var4a+var4(isw,js)+var4(is,js)+var4(ise,js)
1226 oaa(k)=oaa(k)+oa(isw,js,k)+oa(is,js,k)+oa(ise,js,k)
1227 ola(k)=ola(k)+ol(isw,js,k)+ol(is,js,k)+ol(ise,js,k)
1232 ise=mod(isw,numi(js))+1
1233 slma=slma+slm(isw,js)+slm(ise,js)
1234 oroa=oroa+oro(isw,js)+oro(ise,js)
1235 vara=vara+var(isw,js)+var(ise,js)
1236 var4a=var4a+var4(isw,js)+var4(ise,js)
1238 oaa(k)=oaa(k)+oa(isw,js,k)+oa(ise,js,k)
1239 ola(k)=ola(k)+ol(isw,js,k)+ol(ise,js,k)
1250 IF(slm(i,j).EQ.0..AND.slma.EQ.wgta)
THEN
1251 print
'("SEA ",2F8.0," MODIFIED TO LAND",2F8.0," AT ",2I8)',
1252 & oro(i,j),var(i,j),oroa,vara,i,j
1261 ELSEIF(slm(i,j).EQ.1..AND.slma.EQ.0.)
THEN
1262 print
'("LAND",2F8.0," MODIFIED TO SEA ",2F8.0," AT ",2I8)',
1263 & oro(i,j),var(i,j),oroa,vara,i,j
1276 print *,
' after isolated points removed'
1277 call
minmxj(im,jm,oro,
' ORO')
1279 print *,
' ORO(itest,jtest)=',oro(itest,jtest)
1280 print *,
' VAR(itest,jtest)=',var(itest,jtest)
1281 print *,
' VAR4(itest,jtest)=',var4(itest,jtest)
1282 print *,
' OA(itest,jtest,1)=',oa(itest,jtest,1)
1283 print *,
' OA(itest,jtest,2)=',oa(itest,jtest,2)
1284 print *,
' OA(itest,jtest,3)=',oa(itest,jtest,3)
1285 print *,
' OA(itest,jtest,4)=',oa(itest,jtest,4)
1286 print *,
' OL(itest,jtest,1)=',ol(itest,jtest,1)
1287 print *,
' OL(itest,jtest,2)=',ol(itest,jtest,2)
1288 print *,
' OL(itest,jtest,3)=',ol(itest,jtest,3)
1289 print *,
' OL(itest,jtest,4)=',ol(itest,jtest,4)
1290 print *,
' Testing at point (itest,jtest)=',itest,jtest
1291 print *,
' THETA(itest,jtest)=',theta(itest,jtest)
1292 print *,
' GAMMA(itest,jtest)=',gamma(itest,jtest)
1293 print *,
' SIGMA(itest,jtest)=',sigma(itest,jtest)
1294 print *,
' ELVMAX(itest,jtest)=',elvmax(itest,jtest)
1295 print *,
' EFAC=',efac
1299 oro(i,j) = oro(i,j) + efac*var(i,j)
1300 hprime(i,j,1) = var(i,j)
1301 hprime(i,j,2) = var4(i,j)
1302 hprime(i,j,3) = oa(i,j,1)
1303 hprime(i,j,4) = oa(i,j,2)
1304 hprime(i,j,5) = oa(i,j,3)
1305 hprime(i,j,6) = oa(i,j,4)
1306 hprime(i,j,7) = ol(i,j,1)
1307 hprime(i,j,8) = ol(i,j,2)
1308 hprime(i,j,9) = ol(i,j,3)
1309 hprime(i,j,10)= ol(i,j,4)
1310 hprime(i,j,11)= theta(i,j)
1311 hprime(i,j,12)= gamma(i,j)
1312 hprime(i,j,13)= sigma(i,j)
1313 hprime(i,j,14)= elvmax(i,j)
1317 call
mnmxja(im,jm,elvmax,itest,jtest,
' ELVMAX')
1325 IF ( nf1 - nf0 .eq. 0 ) filter=.false.
1326 print *,
' NF1, NF0, FILTER=',nf1,nf0,filter
1330 if(numi(j).lt.im)
then
1332 call
spfft1(numi(j),im/2+1,numi(j),1,ffj,oro(1,j),-1)
1333 call
spfft1(im,im/2+1,im,1,ffj,oro(1,j),+1)
1336 CALL sptez(nr,nm,4,im,jm,ors,oro,-1)
1338 print *,
' about to apply spectral filter '
1344 www=max(1.-fff*(n-nf0)**2,0.)
1345 ors(i+1)=ors(i+1)*www
1346 ors(i+2)=ors(i+2)*www
1352 CALL sptez(nr,nm,4,im,jm,ors,orf,+1)
1354 if(numi(j).lt.im)
then
1355 call
spfft1(im,im/2+1,im,1,ffj,orf(1,j),-1)
1356 call
spfft1(numi(j),im/2+1,numi(j),1,ffj,orf(1,j),+1)
1362 CALL
revers(im, jm, numi, slm, work1)
1363 CALL
revers(im, jm, numi, oro, work1)
1365 CALL
revers(im, jm, numi, hprime(1,1,imt), work1)
1371 call
mnmxja(im,jm,elvmax,itest,jtest,
' ELVMAX')
1372 print *,
' ELVMAX(',itest,jtest,
')=',elvmax(itest,jtest)
1373 print *,
' after spectral filter is applied'
1374 call
minmxj(im,jm,oro,
' ORO')
1375 call
minmxj(im,jm,orf,
' ORF')
1378 call
rg2gg(im,jm,numi,slm)
1379 call
rg2gg(im,jm,numi,oro)
1380 call
rg2gg(im,jm,numi,orf)
1383 call
rg2gg(im,jm,numi,hprime(1,1,imt))
1386 print *,
' after nearest neighbor interpolation applied '
1387 call
minmxj(im,jm,oro,
' ORO')
1388 call
minmxj(im,jm,orf,
' ORF')
1389 call
mnmxja(im,jm,elvmax,itest,jtest,
' ELVMAX')
1390 print *,
' ORO,ORF(itest,jtest),itest,jtest:',
1391 & oro(itest,jtest),orf(itest,jtest),itest,jtest
1392 print *,
' ELVMAX(',itest,jtest,
')=',elvmax(itest,jtest)
1398 if ( i .le. 21 .and. i .ge. 1 )
then
1399 if (j .eq. jm )
write(6,153)i,j,oro(i,j),elvmax(i,j),slm(i,j)
1400 153
format(1x,
' ORO,ELVMAX(i=',i4,
' j=',i4,
')=',2e14.5,f5.1)
1405 write(6,*)
' Timer 5 time= ',tend-tbeg
1406 if (output_binary)
then
1409 print *,
' OUTPUT BINARY FIELDS'
1410 WRITE(51)
REAL(slm,4)
1411 WRITE(52)
REAL(orf,4)
1412 WRITE(53)
REAL(hprime,4)
1413 WRITE(54)
REAL(ors,4)
1414 WRITE(55)
REAL(oro,4)
1415 WRITE(66)
REAL(theta,4)
1416 WRITE(67)
REAL(gamma,4)
1417 WRITE(68)
REAL(sigma,4)
1419 if ( mskocn .eq. 1 )
then
1421 WRITE(27,iostat=ios) oclsm
1422 print *,
' write OCLSM input:',ios
1426 call
minmxj(im,jm,oro,
' ORO')
1427 print *,
' IM=',im,
' JM=',jm,
' SPECTR=',spectr
1429 WRITE(71)
REAL(slm,4)
1431 WRITE(71)
REAL(HPRIME(:,:,IMT),4)
1432 print *,
' HPRIME(',itest,jtest,imt,
')=',hprime(itest,jtest,imt)
1434 WRITE(71)
REAL(oro,4)
1436 WRITE(71)
REAL(ORF,4)
1461 kgds(4)=90000-180000/pi*rclt(1)
1463 kgds(7)=180000/pi*rclt(1)-90000
1464 kgds(8)=-nint(360000./im)
1465 kgds(9)=nint(360000./im)
1469 CALL baopen(56,
'fort.56',iret)
1470 if (iret .ne. 0) print *,
' BAOPEN ERROR UNIT 56: IRET=',iret
1471 CALL putgb(56,im*jm,kpds,kgds,lb,slm,iret)
1472 print *,
' SLM: putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1473 if (iret .ne. 0) print *,
' SLM PUTGB ERROR: UNIT 56: IRET=',iret
1474 print *,
' SLM: putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1486 CALL baopen(57,
'fort.57',iret)
1487 CALL putgb(57,im*jm,kpds,kgds,lb,orf,iret)
1488 print *,
' ORF (ORO): putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1495 CALL baopen(58,
'fort.58',iret)
1496 CALL putgb(58,im*jm,kpds,kgds,lb,theta,iret)
1497 print *,
' THETA: putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1504 CALL baopen(60,
'fort.60',iret)
1505 CALL putgb(60,im*jm,kpds,kgds,lb,sigma,iret)
1506 print *,
' SIGMA: putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1513 CALL baopen(59,
'fort.59',iret)
1514 CALL putgb(59,im*jm,kpds,kgds,lb,gamma,iret)
1515 print *,
' GAMMA: putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1519 CALL baopen(61,
'fort.61',iret)
1520 CALL putgb(61,im*jm,kpds,kgds,lb,hprime,iret)
1521 print *,
' HPRIME: putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1526 CALL baopen(62,
'fort.62',iret)
1527 CALL putgb(62,im*jm,kpds,kgds,lb,elvmax,iret)
1528 print *,
' ELVMAX: putgb-KPDS(22,5),iret:',kpds(22),kpds(5),iret
1533 xlon(i) = delxn*(i-1)
1535 IF(trim(outgrid) ==
"none")
THEN
1538 geolon(i,j) = xlon(i)
1539 geolat(i,j) = xlat(j)
1544 xlat(j) = geolat(1,j)
1547 xlon(i) = geolon(i,1)
1551 write(6,*)
' Binary output time= ',tend-tbeg
1553 CALL
write_netcdf(im,jm,slm,land_frac,oro,orf,hprime,1,1,
1554 1 geolon(1:im,1:jm),geolat(1:im,1:jm), xlon,xlat)
1556 write(6,*)
' WRITE_NETCDF time= ',tend-tbeg
1557 print *,
' wrote netcdf file out.oro.tile?.nc'
1559 print *,
' ===== Deallocate Arrays and ENDING MTN VAR OROG program'
1565 write(6,*)
' Total runtime time= ',tend-tbeg1
1598 SUBROUTINE makemt(ZAVG,ZSLM,ORO,SLM,VAR,VAR4,
1599 1 glat,ist,ien,jst,jen,im,jm,imn,jmn,xlat,numi)
1600 dimension glat(jmn),xlat(jm)
1602 INTEGER zavg(imn,jmn),zslm(imn,jmn)
1603 dimension oro(im,jm),slm(im,jm),var(im,jm),var4(im,jm)
1604 dimension ist(im,jm),ien(im,jm),jst(jm),jen(jm),numi(jm)
1605 INTEGER mskocn,isave
1613 print *,
' _____ SUBROUTINE MAKEMT '
1620 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
1630 faclon = delx / delxn
1631 ist(i,j) = faclon * float(i-1) - faclon * 0.5 + 1
1632 ien(i,j) = faclon * float(i) - faclon * 0.5 + 1
1636 IF (ist(i,j) .LE. 0) ist(i,j) = ist(i,j) + imn
1637 IF (ien(i,j) .LT. ist(i,j)) ien(i,j) = ien(i,j) + imn
1646 print *,
' DELX=',delx,
' DELXN=',delxn
1650 xxlat = (xlat(j)+xlat(j+1))/2.
1651 IF(flag.AND.glat(j1).GT.xxlat)
THEN
1659 jst(jm) = max(jst(jm-1) - (jen(jm-1)-jst(jm-1)),1)
1660 jen(1) = min(jen(2) + (jen(2)-jst(2)),jmn)
1678 DO ii1 = 1, ien(i,j) - ist(i,j) + 1
1679 i1 = ist(i,j) + ii1 - 1
1680 IF(i1.LE.0.) i1 = i1 + imn
1681 IF(i1.GT.imn) i1 = i1 - imn
1688 xland = xland + float(zslm(i1,j1))
1689 xwatr = xwatr + float(1-zslm(i1,j1))
1691 height = float(zavg(i1,j1))
1693 IF(height.LT.-990.) height = 0.0
1694 xl1 = xl1 + height * float(zslm(i1,j1))
1695 xs1 = xs1 + height * float(1-zslm(i1,j1))
1697 xw2 = xw2 + height ** 2
1708 IF(xnsum.GT.1.)
THEN
1713 slm(i,j) = float(nint(xland/xnsum))
1714 IF(slm(i,j).NE.0.)
THEN
1715 oro(i,j)= xl1 / xland
1717 oro(i,j)= xs1 / xwatr
1719 var(i,j)=sqrt(max(xw2/xnsum-(xw1/xnsum)**2,0.))
1720 DO ii1 = 1, ien(i,j) - ist(i,j) + 1
1721 i1 = ist(i,j) + ii1 - 1
1722 IF(i1.LE.0.) i1 = i1 + imn
1723 IF(i1.GT.imn) i1 = i1 - imn
1725 height = float(zavg(i1,j1))
1726 IF(height.LT.-990.) height = 0.0
1727 xw4 = xw4 + (height-oro(i,j)) ** 4
1730 IF(var(i,j).GT.1.)
THEN
1734 var4(i,j) = min(xw4/xnsum/var(i,j) **4,10.)
1739 WRITE(6,*)
"! MAKEMT ORO SLM VAR VAR4 DONE"
1765 & jst,jen,ilist,numx)
1767 integer,
intent(in) :: imn,jmn
1769 real,
intent(in) :: lono(npts), lato(npts)
1770 real,
intent(in) :: delxn
1771 integer,
intent(out) :: jst,jen
1772 integer,
intent(out) :: ilist(imn)
1773 integer,
intent(out) :: numx
1774 real minlat,maxlat,minlon,maxlon
1775 integer i2, ii, ist, ien
1777 minlat = minval(lato)
1778 maxlat = maxval(lato)
1779 minlon = minval(lono)
1780 maxlon = maxval(lono)
1781 ist = minlon/delxn+1
1782 ien = maxlon/delxn+1
1783 jst = (minlat+90)/delxn+1
1784 jen = (maxlat+90)/delxn
1789 if(jen>jmn) jen = jmn
1792 if((jst == 1 .OR. jen == jmn) .and.
1793 & (ien-ist+1 > imn/2) )
then
1798 else if( ien-ist+1 > imn/2 )
then
1804 ii = lono(i2)/delxn+1
1805 if(ii <0 .or. ii>imn) print*,
"ii=",ii,imn,lono(i2),delxn
1806 if( ii < imn/2 )
then
1808 else if( ii > imn/2 )
then
1812 if(ist<1 .OR. ist>imn)
then
1813 print*, .or.
"ist<1 ist>IMN"
1816 if(ien<1 .OR. ien>imn)
then
1817 print*, .or.
"iend<1 iend>IMN"
1821 numx = imn - ien + 1
1823 ilist(i2) = ien + (i2-1)
1832 ilist(i2) = ist + (i2-1)
1858 SUBROUTINE makemt2(ZAVG,ZSLM,ORO,SLM,land_frac,VAR,VAR4,
1859 1 glat,im,jm,imn,jmn,lon_c,lat_c)
1861 real,
parameter :: d2r = 3.14159265358979/180.
1862 integer,
parameter :: maxsum=20000000
1863 real,
dimension(:),
allocatable :: hgt_1d
1864 integer im, jm, imn, jmn
1865 real glat(jmn), glon(imn)
1866 INTEGER zavg(imn,jmn),zslm(imn,jmn)
1867 real land_frac(im,jm)
1868 real oro(im,jm),slm(im,jm),var(im,jm),var4(im,jm)
1869 integer ist,ien,jst, jen
1870 real lon_c(im+1,jm+1), lat_c(im+1,jm+1)
1871 INTEGER mskocn,isave
1873 real lono(4),lato(4),loni,lati
1875 integer jm1,i,j,nsum,ii,jj,i1,numx,i2
1877 real delxn,xnsum,xland,xwatr,xl1,xs1,xw1,xw2,xw4
1879 real :: xnsum_j,xland_j,xwatr_j
1887 print *,
' _____ SUBROUTINE MAKEMT2 '
1888 allocate(hgt_1d(maxsum))
1895 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
1898 glon(i) = 0. + (i-1) * delxn + delxn * 0.5
1901 land_frac(:,:) = 0.0
1926 lono(1) = lon_c(i,j)
1927 lono(2) = lon_c(i+1,j)
1928 lono(3) = lon_c(i+1,j+1)
1929 lono(4) = lon_c(i,j+1)
1930 lato(1) = lat_c(i,j)
1931 lato(2) = lat_c(i+1,j)
1932 lato(3) = lat_c(i+1,j+1)
1933 lato(4) = lat_c(i,j+1)
1934 call
get_index(imn,jmn,4,lono,lato,delxn,jst,jen,ilist,numx)
1935 do jj = jst, jen;
do i2 = 1, numx
1938 lati = -90 + jj*delxn
1940 & lono*d2r,lato*d2r))
then
1942 xland = xland + float(zslm(ii,jj))
1943 xwatr = xwatr + float(1-zslm(ii,jj))
1945 height = float(zavg(ii,jj))
1947 if(nsum > maxsum)
then
1948 print*,
"nsum is greater than MAXSUM, increase MAXSUM"
1951 hgt_1d(nsum) = height
1952 IF(height.LT.-990.) height = 0.0
1953 xl1 = xl1 + height * float(zslm(ii,jj))
1954 xs1 = xs1 + height * float(1-zslm(ii,jj))
1956 xw2 = xw2 + height ** 2
1961 IF(xnsum.GT.1.)
THEN
1965 land_frac(i,j) = xland/xnsum
1966 slm(i,j) = float(nint(xland/xnsum))
1967 IF(slm(i,j).NE.0.)
THEN
1968 oro(i,j)= xl1 / xland
1970 oro(i,j)= xs1 / xwatr
1972 var(i,j)=sqrt(max(xw2/xnsum-(xw1/xnsum)**2,0.))
1974 xw4 = xw4 + (hgt_1d(i1) - oro(i,j)) ** 4
1977 IF(var(i,j).GT.1.)
THEN
1978 var4(i,j) = min(xw4/xnsum/var(i,j) **4,10.)
1984 WRITE(6,*)
"! MAKEMT2 ORO SLM VAR VAR4 DONE"
2018 SUBROUTINE makepc(ZAVG,ZSLM,THETA,GAMMA,SIGMA,
2019 1 glat,ist,ien,jst,jen,im,jm,imn,jmn,xlat,numi)
2023 parameter(rearth=6.3712e+6)
2024 dimension glat(jmn),xlat(jm),deltax(jmn)
2025 INTEGER zavg(imn,jmn),zslm(imn,jmn)
2026 dimension oro(im,jm),slm(im,jm),hl(im,jm),hk(im,jm)
2027 dimension hx2(im,jm),hy2(im,jm),hxy(im,jm),hlprim(im,jm)
2028 dimension theta(im,jm),gamma(im,jm),sigma2(im,jm),sigma(im,jm)
2029 dimension ist(im,jm),ien(im,jm),jst(jm),jen(jm),numi(jm)
2034 pi = 4.0 * atan(1.0)
2040 deltay = certh / float(jmn)
2041 print *,
'MAKEPC: DELTAY=',deltay
2044 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
2045 deltax(j) = deltay * cos(glat(j)*pi/180.0)
2054 faclon = delx / delxn
2055 ist(i,j) = faclon * float(i-1) - faclon * 0.5
2056 ist(i,j) = ist(i,j) + 1
2057 ien(i,j) = faclon * float(i) - faclon * 0.5
2064 IF (ist(i,j) .LE. 0) ist(i,j) = ist(i,j) + imn
2065 IF (ien(i,j) .LT. ist(i,j)) ien(i,j) = ien(i,j) + imn
2067 if ( i .lt. 10 .and. j .lt. 10 )
2068 1 print*,
' I j IST IEN ',i,j,ist(i,j),ien(i,j)
2070 IF (ien(i,j) .LT. ist(i,j))
2071 1 print *,
' MAKEPC: IEN < IST: I,J,IST(I,J),IEN(I,J)',
2072 2 i,j,ist(i,j),ien(i,j)
2078 xxlat = (xlat(j)+xlat(j+1))/2.
2079 IF(flag.AND.glat(j1).GT.xxlat)
THEN
2086 jst(jm) = max(jst(jm-1) - (jen(jm-1)-jst(jm-1)),1)
2087 jen(1) = min(jen(2) + (jen(2)-jst(2)),jmn)
2089 print*,
' IST,IEN(1,1-numi(1,JM))',ist(1,1),ien(1,1),
2090 1 ist(numi(jm),jm),ien(numi(jm),jm), numi(jm)
2091 print*,
' JST,JEN(1,JM) ',jst(1),jen(1),jst(jm),jen(jm)
2120 DO ii1 = 1, ien(i,j) - ist(i,j) + 1
2121 i1 = ist(i,j) + ii1 - 1
2122 IF(i1.LE.0.) i1 = i1 + imn
2123 IF(i1.GT.imn) i1 = i1 - imn
2128 if (i1 - 1 .le. 0 ) i0 = i0 + imn
2129 if (i1 - 1 .gt. imn) i0 = i0 - imn
2132 if (i1 + 1 .le. 0 ) ip1 = ip1 + imn
2133 if (i1 + 1 .gt. imn) ip1 = ip1 - imn
2137 if ( i1 .eq. ist(i,j) .and. j1 .eq. jst(j) )
2138 1 print*,
' J, J1,IST,JST,DELTAX,GLAT ',
2139 2 j,j1,ist(i,j),jst(j),deltax(j1),glat(j1)
2140 if ( i1 .eq. ien(i,j) .and. j1 .eq. jen(j) )
2141 1 print*,
' J, J1,IEN,JEN,DELTAX,GLAT ',
2142 2 j,j1,ien(i,j),jen(j),deltax(j1),glat(j1)
2144 xland = xland + float(zslm(i1,j1))
2145 xwatr = xwatr + float(1-zslm(i1,j1))
2148 height = float(zavg(i1,j1))
2149 hi0 = float(zavg(i0,j1))
2150 hip1 = float(zavg(ip1,j1))
2152 IF(height.LT.-990.) height = 0.0
2153 if(hi0 .lt. -990.) hi0 = 0.0
2154 if(hip1 .lt. -990.) hip1 = 0.0
2156 xfp = 0.5 * ( hip1 - hi0 ) / deltax(j1)
2157 xfp2 = xfp2 + 0.25 * ( ( hip1 - hi0 )/deltax(j1) )** 2
2161 if ( j1 .ne. jst(jm) .and. j1 .ne. jen(1) )
then
2162 hj0 = float(zavg(i1,j1-1))
2163 hjp1 = float(zavg(i1,j1+1))
2164 if(hj0 .lt. -990.) hj0 = 0.0
2165 if(hjp1 .lt. -990.) hjp1 = 0.0
2167 yfp = 0.5 * ( hjp1 - hj0 ) / deltay
2168 yfp2 = yfp2 + 0.25 * ( ( hjp1 - hj0 )/deltay )**2
2174 elseif ( j1 .eq. jst(jm) )
then
2176 if (ijax .le. 0 ) ijax = ijax + imn
2177 if (ijax .gt. imn) ijax = ijax - imn
2179 hijax = float(zavg(ijax,j1))
2180 hi1j1 = float(zavg(i1,j1))
2181 if(hijax .lt. -990.) hijax = 0.0
2182 if(hi1j1 .lt. -990.) hi1j1 = 0.0
2184 yfp = 0.5 * ( ( 0.5 * ( hijax - hi1j1 ) ) )/deltay
2185 yfp2 = yfp2 + 0.25 * ( ( 0.5 * ( hijax - hi1j1) )
2191 elseif ( j1 .eq. jen(1) )
then
2193 if (ijax .le. 0 ) ijax = ijax + imn
2194 if (ijax .gt. imn) ijax = ijax - imn
2195 hijax = float(zavg(ijax,j1))
2196 hi1j1 = float(zavg(i1,j1))
2197 if(hijax .lt. -990.) hijax = 0.0
2198 if(hi1j1 .lt. -990.) hi1j1 = 0.0
2199 if ( i1 .lt. 5 )print *,
' S.Pole i1,j1 :',i1,j1,hijax,hi1j1
2201 yfp = 0.5 * (0.5 * ( hijax - hi1j1) )/deltay
2202 yfp2 = yfp2 + 0.25 * ( (0.5 * (hijax - hi1j1) )
2209 xfpyfp = xfpyfp + xfp * yfp
2210 xl1 = xl1 + height * float(zslm(i1,j1))
2211 xs1 = xs1 + height * float(1-zslm(i1,j1))
2221 IF(xnsum.GT.1.)
THEN
2222 slm(i,j) = float(nint(xland/xnsum))
2223 IF(slm(i,j).NE.0.)
THEN
2224 oro(i,j)= xl1 / xland
2225 hx2(i,j) = xfp2 / xland
2226 hy2(i,j) = yfp2 / xland
2227 hxy(i,j) = xfpyfp / xland
2229 oro(i,j)= xs1 / xwatr
2233 print *,
" I,J,i1,j1,HEIGHT:", i,j,i1,j1,height,
2235 print *,
" xfpyfp,xfp2,yfp2:",xfpyfp,xfp2,yfp2
2236 print *,
" HX2,HY2,HXY:",hx2(i,j),hy2(i,j),hxy(i,j)
2242 hk(i,j) = 0.5 * ( hx2(i,j) + hy2(i,j) )
2243 hl(i,j) = 0.5 * ( hx2(i,j) - hy2(i,j) )
2244 hlprim(i,j) = sqrt(hl(i,j)*hl(i,j) + hxy(i,j)*hxy(i,j))
2245 IF( hl(i,j).NE. 0. .AND. slm(i,j) .NE. 0. )
THEN
2247 theta(i,j) = 0.5 * atan2(hxy(i,j),hl(i,j)) * 180.0 / pi
2251 sigma2(i,j) = ( hk(i,j) + hlprim(i,j) )
2252 if ( sigma2(i,j) .GE. 0. )
then
2253 sigma(i,j) = sqrt(sigma2(i,j) )
2254 if (sigma2(i,j) .ne. 0. .and.
2255 & hk(i,j) .GE. hlprim(i,j) )
2256 1 gamma(i,j) = sqrt( (hk(i,j) - hlprim(i,j)) / sigma2(i,j) )
2262 print *,
" I,J,THETA,SIGMA,GAMMA,",i,j,theta(i,j),
2263 1 sigma(i,j),gamma(i,j)
2264 print *,
" HK,HL,HLPRIM:",hk(i,j),hl(i,j),hlprim(i,j)
2268 WRITE(6,*)
"! MAKE Principal Coord DONE"
2293 1 glat,im,jm,imn,jmn,lon_c,lat_c)
2298 real,
parameter :: rearth=6.3712e+6
2299 real,
parameter :: d2r = 3.14159265358979/180.
2300 integer :: im,jm,imn,jmn
2301 real :: glat(jmn),deltax(jmn)
2302 INTEGER zavg(imn,jmn),zslm(imn,jmn)
2303 real lon_c(im+1,jm+1), lat_c(im+1,jm+1)
2304 real oro(im,jm),slm(im,jm),hl(im,jm),hk(im,jm)
2305 real hx2(im,jm),hy2(im,jm),hxy(im,jm),hlprim(im,jm)
2306 real theta(im,jm),gamma(im,jm),sigma2(im,jm),sigma(im,jm)
2307 real pi,certh,delxn,deltay,xnsum,xland,xwatr,xl1,xs1
2308 real xfp,yfp,xfpyfp,xfp2,yfp2,height
2309 real hi0,hip1,hj0,hjp1,hijax,hi1j1
2310 real lono(4),lato(4),loni,lati
2311 integer i,j,i1,j1,i2,jst,jen,numx,i0,ip1,ijax
2318 pi = 4.0 * atan(1.0)
2323 deltay = certh / float(jmn)
2324 print *,
'MAKEPC2: DELTAY=',deltay
2327 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
2328 deltax(j) = deltay * cos(glat(j)*d2r)
2366 lono(1) = lon_c(i,j)
2367 lono(2) = lon_c(i+1,j)
2368 lono(3) = lon_c(i+1,j+1)
2369 lono(4) = lon_c(i,j+1)
2370 lato(1) = lat_c(i,j)
2371 lato(2) = lat_c(i+1,j)
2372 lato(3) = lat_c(i+1,j+1)
2373 lato(4) = lat_c(i,j+1)
2374 call
get_index(imn,jmn,4,lono,lato,delxn,jst,jen,ilist,numx)
2376 do j1 = jst, jen;
do i2 = 1, numx
2379 lati = -90 + j1*delxn
2381 & lono*d2r,lato*d2r))
then
2386 if (i1 - 1 .le. 0 ) i0 = i0 + imn
2387 if (i1 - 1 .gt. imn) i0 = i0 - imn
2390 if (i1 + 1 .le. 0 ) ip1 = ip1 + imn
2391 if (i1 + 1 .gt. imn) ip1 = ip1 - imn
2393 xland = xland + float(zslm(i1,j1))
2394 xwatr = xwatr + float(1-zslm(i1,j1))
2397 height = float(zavg(i1,j1))
2398 hi0 = float(zavg(i0,j1))
2399 hip1 = float(zavg(ip1,j1))
2401 IF(height.LT.-990.) height = 0.0
2402 if(hi0 .lt. -990.) hi0 = 0.0
2403 if(hip1 .lt. -990.) hip1 = 0.0
2405 xfp = 0.5 * ( hip1 - hi0 ) / deltax(j1)
2406 xfp2 = xfp2 + 0.25 * ( ( hip1 - hi0 )/deltax(j1) )** 2
2410 if ( j1 .ne. 1 .and. j1 .ne. jmn )
then
2411 hj0 = float(zavg(i1,j1-1))
2412 hjp1 = float(zavg(i1,j1+1))
2413 if(hj0 .lt. -990.) hj0 = 0.0
2414 if(hjp1 .lt. -990.) hjp1 = 0.0
2416 yfp = 0.5 * ( hjp1 - hj0 ) / deltay
2417 yfp2 = yfp2 + 0.25 * ( ( hjp1 - hj0 )/deltay )**2
2423 elseif ( j1 .eq. 1 )
then
2425 if (ijax .le. 0 ) ijax = ijax + imn
2426 if (ijax .gt. imn) ijax = ijax - imn
2428 hijax = float(zavg(ijax,j1))
2429 hi1j1 = float(zavg(i1,j1))
2430 if(hijax .lt. -990.) hijax = 0.0
2431 if(hi1j1 .lt. -990.) hi1j1 = 0.0
2433 yfp = 0.5 * ( ( 0.5 * ( hijax - hi1j1 ) ) )/deltay
2434 yfp2 = yfp2 + 0.25 * ( ( 0.5 * ( hijax - hi1j1) )
2440 elseif ( j1 .eq. jmn )
then
2442 if (ijax .le. 0 ) ijax = ijax + imn
2443 if (ijax .gt. imn) ijax = ijax - imn
2444 hijax = float(zavg(ijax,j1))
2445 hi1j1 = float(zavg(i1,j1))
2446 if(hijax .lt. -990.) hijax = 0.0
2447 if(hi1j1 .lt. -990.) hi1j1 = 0.0
2448 if ( i1 .lt. 5 )print *,
' S.Pole i1,j1 :',i1,j1,
2451 yfp = 0.5 * (0.5 * ( hijax - hi1j1) )/deltay
2452 yfp2 = yfp2 + 0.25 * ( (0.5 * (hijax - hi1j1) )
2459 xfpyfp = xfpyfp + xfp * yfp
2460 xl1 = xl1 + height * float(zslm(i1,j1))
2461 xs1 = xs1 + height * float(1-zslm(i1,j1))
2472 IF(xnsum.GT.1.)
THEN
2473 slm(i,j) = float(nint(xland/xnsum))
2474 IF(slm(i,j).NE.0.)
THEN
2475 oro(i,j)= xl1 / xland
2476 hx2(i,j) = xfp2 / xland
2477 hy2(i,j) = yfp2 / xland
2478 hxy(i,j) = xfpyfp / xland
2480 oro(i,j)= xs1 / xwatr
2484 print *,
" I,J,i1,j1,HEIGHT:", i,j,i1,j1,height,
2486 print *,
" xfpyfp,xfp2,yfp2:",xfpyfp,xfp2,yfp2
2487 print *,
" HX2,HY2,HXY:",hx2(i,j),hy2(i,j),hxy(i,j)
2493 hk(i,j) = 0.5 * ( hx2(i,j) + hy2(i,j) )
2494 hl(i,j) = 0.5 * ( hx2(i,j) - hy2(i,j) )
2495 hlprim(i,j) = sqrt(hl(i,j)*hl(i,j) + hxy(i,j)*hxy(i,j))
2496 IF( hl(i,j).NE. 0. .AND. slm(i,j) .NE. 0. )
THEN
2498 theta(i,j) = 0.5 * atan2(hxy(i,j),hl(i,j)) / d2r
2502 sigma2(i,j) = ( hk(i,j) + hlprim(i,j) )
2503 if ( sigma2(i,j) .GE. 0. )
then
2504 sigma(i,j) = sqrt(sigma2(i,j) )
2505 if (sigma2(i,j) .ne. 0. .and.
2506 & hk(i,j) .GE. hlprim(i,j) )
2507 1 gamma(i,j) = sqrt( (hk(i,j) - hlprim(i,j)) / sigma2(i,j) )
2513 print *,
" I,J,THETA,SIGMA,GAMMA,",i,j,theta(i,j),
2514 1 sigma(i,j),gamma(i,j)
2515 print *,
" HK,HL,HLPRIM:",hk(i,j),hl(i,j),hlprim(i,j)
2520 WRITE(6,*)
"! MAKE Principal Coord DONE"
2566 SUBROUTINE makeoa(ZAVG,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
2567 1 oro,oro1,xnsum,xnsum1,xnsum2,xnsum3,xnsum4,
2568 2 ist,ien,jst,jen,im,jm,imn,jmn,xlat,numi)
2569 dimension glat(jmn),xlat(jm)
2570 INTEGER zavg(imn,jmn)
2571 dimension oro(im,jm),oro1(im,jm),elvmax(im,jm),zmax(im,jm)
2572 dimension oa4(im,jm,4),ioa4(im,jm,4)
2573 dimension ist(im,jm),ien(im,jm),jst(jm),jen(jm)
2574 dimension xnsum(im,jm),xnsum1(im,jm),xnsum2(im,jm)
2575 dimension xnsum3(im,jm),xnsum4(im,jm)
2576 dimension var(im,jm),ol(im,jm,4),numi(jm)
2586 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
2588 print *,
' IM=',im,
' JM=',jm,
' IMN=',imn,
' JMN=',jmn
2595 faclon = delx / delxn
2597 ist(i,j) = faclon * float(i-1) - faclon * 0.5
2598 ist(i,j) = ist(i,j) + 1
2599 ien(i,j) = faclon * float(i) - faclon * 0.5
2602 IF (ist(i,j) .LE. 0) ist(i,j) = ist(i,j) + imn
2603 IF (ien(i,j) .LT. ist(i,j)) ien(i,j) = ien(i,j) + imn
2605 if ( i .lt. 3 .and. j .lt. 3 )
2606 1print*,
' MAKEOA: I j IST IEN ',i,j,ist(i,j),ien(i,j)
2607 if ( i .lt. 3 .and. j .ge. jm-1 )
2608 1print*,
' MAKEOA: I j IST IEN ',i,j,ist(i,j),ien(i,j)
2611 print *,
'MAKEOA: DELXN,DELX,FACLON',delxn,delx,faclon
2612 print *,
' ***** ready to start JST JEN section '
2617 xxlat = (xlat(j)+xlat(j+1))/2.
2618 IF(flag.AND.glat(j1).GT.xxlat)
THEN
2623 1print*,
' MAKEOA: XX j JST JEN ',j,jst(j),jen(j)
2627 1print*,
' MAKEOA: j JST JEN ',j,jst(j),jen(j)
2629 1print*,
' MAKEOA: j JST JEN ',j,jst(j),jen(j)
2638 jst(jm) = max(jst(jm-1) - (jen(jm-1)-jst(jm-1)),1)
2639 jen(1) = min(jen(2) + (jen(2)-jst(2)),jmn)
2640 print *,
' ***** JST(1) JEN(1) ',jst(1),jen(1)
2641 print *,
' ***** JST(JM) JEN(JM) ',jst(jm),jen(jm)
2646 elvmax(i,j) = oro(i,j)
2655 DO ii1 = 1, ien(i,j) - ist(i,j) + 1
2656 i1 = ist(i,j) + ii1 - 1
2658 IF(i1.LE.0.) i1 = i1 + imn
2659 IF (i1 .GT. imn) i1 = i1 - imn
2661 height = float(zavg(i1,j1))
2662 IF(height.LT.-990.) height = 0.0
2663 IF ( height .gt. oro(i,j) )
then
2664 if ( height .gt. zmax(i,j) )zmax(i,j) = height
2665 xnsum(i,j) = xnsum(i,j) + 1
2669 if ( i .lt. 5 .and. j .ge. jm-5 )
then
2670 print *,
' I,J,ORO(I,J),XNSUM(I,J),ZMAX(I,J):',
2671 1 i,j,oro(i,j),xnsum(i,j),zmax(i,j)
2682 oro1(i,j) = oro(i,j)
2683 elvmax(i,j) = zmax(i,j)
2716 hc = 1116.2 - 0.878 * var(i,j)
2718 DO ii1 = 1, ien(i,j) - ist(i,j) + 1
2719 i1 = ist(i,j) + ii1 - 1
2724 IF(i1.GT.imn) i1 = i1 - imn
2726 IF(float(zavg(i1,j1)) .GT. hc)
2727 1 xnsum1(i,j) = xnsum1(i,j) + 1
2728 xnsum2(i,j) = xnsum2(i,j) + 1
2732 inci = nint((ien(i,j)-ist(i,j)) * 0.5)
2733 isttt = min(max(ist(i,j)-inci,1),imn)
2734 ieddd = min(max(ien(i,j)-inci,1),imn)
2736 incj = nint((jen(j)-jst(j)) * 0.5)
2737 jsttt = min(max(jst(j)-incj,1),jmn)
2738 jeddd = min(max(jen(j)-incj,1),jmn)
2748 IF(float(zavg(i1,j1)) .GT. hc)
2749 1 xnsum3(i,j) = xnsum3(i,j) + 1
2750 xnsum4(i,j) = xnsum4(i,j) + 1
2776 IF (ii .GT. numi(j)) ii = ii - numi(j)
2777 xnpu = xnsum(i,j) + xnsum(i,j+1)
2778 xnpd = xnsum(ii,j) + xnsum(ii,j+1)
2779 IF (xnpd .NE. xnpu) oa4(ii,j+1,1) = 1. - xnpd / max(xnpu , 1.)
2780 ol(ii,j+1,1) = (xnsum3(i,j+1)+xnsum3(ii,j+1))/
2781 1 (xnsum4(i,j+1)+xnsum4(ii,j+1))
2796 IF (ii .GT. numi(j)) ii = ii - numi(j)
2797 xnpu = xnsum(i,j+1) + xnsum(ii,j+1)
2798 xnpd = xnsum(i,j) + xnsum(ii,j)
2799 IF (xnpd .NE. xnpu) oa4(ii,j+1,2) = 1. - xnpd / max(xnpu , 1.)
2800 ol(ii,j+1,2) = (xnsum3(ii,j)+xnsum3(ii,j+1))/
2801 1 (xnsum4(ii,j)+xnsum4(ii,j+1))
2807 IF (ii .GT. numi(j)) ii = ii - numi(j)
2808 xnpu = xnsum(i,j+1) + ( xnsum(i,j) + xnsum(ii,j+1) )*0.5
2809 xnpd = xnsum(ii,j) + ( xnsum(i,j) + xnsum(ii,j+1) )*0.5
2810 IF (xnpd .NE. xnpu) oa4(ii,j+1,3) = 1. - xnpd / max(xnpu , 1.)
2811 ol(ii,j+1,3) = (xnsum1(ii,j)+xnsum1(i,j+1))/
2812 1 (xnsum2(ii,j)+xnsum2(i,j+1))
2818 IF (ii .GT. numi(j)) ii = ii - numi(j)
2819 xnpu = xnsum(i,j) + ( xnsum(ii,j) + xnsum(i,j+1) )*0.5
2820 xnpd = xnsum(ii,j+1) + ( xnsum(ii,j) + xnsum(i,j+1) )*0.5
2821 IF (xnpd .NE. xnpu) oa4(ii,j+1,4) = 1. - xnpd / max(xnpu , 1.)
2822 ol(ii,j+1,4) = (xnsum1(i,j)+xnsum1(ii,j+1))/
2823 1 (xnsum2(i,j)+xnsum2(ii,j+1))
2829 ol(i,1,kwd) = ol(i,2,kwd)
2830 ol(i,jm,kwd) = ol(i,jm-1,kwd)
2838 oa4(i,j,kwd) = sign( min( abs(t), 1. ), t )
2853 t = abs( oa4(i,j,kwd) )
2857 ELSE IF(t .GT. 0. .AND. t .LE. 1.)
THEN
2860 ELSE IF(t .GT. 1. .AND. t .LE. 10.)
THEN
2863 ELSE IF(t .GT. 10. .AND. t .LE. 100.)
THEN
2866 ELSE IF(t .GT. 100. .AND. t .LE. 1000.)
THEN
2869 ELSE IF(t .GT. 1000. .AND. t .LE. 10000.)
THEN
2872 ELSE IF(t .GT. 10000.)
THEN
2880 WRITE(6,*)
"! MAKEOA EXIT"
2896 real dx, lat, degrad
2899 real,
parameter :: radius = 6371000
2901 get_lon_angle = 2*asin( sin(dx/radius*0.5)/cos(lat) )*degrad
2918 real,
parameter :: radius = 6371000
2960 SUBROUTINE makeoa2(ZAVG,zslm,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
2961 1 oro,oro1,xnsum,xnsum1,xnsum2,xnsum3,xnsum4,
2962 2 im,jm,imn,jmn,lon_c,lat_c,lon_t,lat_t,dx,dy,
2963 3 is_south_pole,is_north_pole )
2965 real,
parameter :: missing_value = -9999.
2966 real,
parameter :: d2r = 3.14159265358979/180.
2967 real,
PARAMETER :: r2d=180./3.14159265358979
2968 integer im,jm,imn,jmn
2970 INTEGER zavg(imn,jmn),zslm(imn,jmn)
2971 real oro(im,jm),oro1(im,jm),elvmax(im,jm),zmax(im,jm)
2973 integer ioa4(im,jm,4)
2974 real lon_c(im+1,jm+1), lat_c(im+1,jm+1)
2975 real lon_t(im,jm), lat_t(im,jm)
2976 real dx(im,jm), dy(im,jm)
2977 logical is_south_pole(im,jm), is_north_pole(im,jm)
2978 real xnsum(im,jm),xnsum1(im,jm),xnsum2(im,jm)
2979 real xnsum3(im,jm),xnsum4(im,jm)
2980 real var(im,jm),ol(im,jm,4)
2982 integer i,j,ilist(imn),numx,i1,j1,ii1
2984 real lono(4),lato(4),loni,lati
2985 real delxn,hc,height,xnpu,xnpd,t
2986 integer ns0,ns1,ns2,ns3,ns4,ns5,ns6
2988 real lon,lat,dlon,dlat,dlat_old
2989 real lon1,lat1,lon2,lat2
2990 real xnsum11,xnsum12,xnsum21,xnsum22,xnsumx
2991 real hc_11, hc_12, hc_21, hc_22
2992 real xnsum1_11,xnsum1_12,xnsum1_21,xnsum1_22
2993 real xnsum2_11,xnsum2_12,xnsum2_21,xnsum2_22
2995 integer ist, ien, jst, jen
2996 real xland,xwatr,xl1,xs1,oroavg,slm
3003 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
3005 print *,
' IM=',im,
' JM=',jm,
' IMN=',imn,
' JMN=',jmn
3013 elvmax(i,j) = oro(i,j)
3021 oro1(i,j) = oro(i,j)
3022 elvmax(i,j) = zmax(i,j)
3034 hc = 1116.2 - 0.878 * var(i,j)
3035 lono(1) = lon_c(i,j)
3036 lono(2) = lon_c(i+1,j)
3037 lono(3) = lon_c(i+1,j+1)
3038 lono(4) = lon_c(i,j+1)
3039 lato(1) = lat_c(i,j)
3040 lato(2) = lat_c(i+1,j)
3041 lato(3) = lat_c(i+1,j+1)
3042 lato(4) = lat_c(i,j+1)
3043 call
get_index(imn,jmn,4,lono,lato,delxn,jst,jen,ilist,numx)
3044 do j1 = jst, jen;
do ii1 = 1, numx
3047 lati = -90 + j1*delxn
3049 & lono*d2r,lato*d2r))
then
3051 height = float(zavg(i1,j1))
3052 IF(height.LT.-990.) height = 0.0
3053 IF ( height .gt. oro(i,j) )
then
3054 if ( height .gt. zmax(i,j) )zmax(i,j) = height
3067 oro1(i,j) = oro(i,j)
3068 elvmax(i,j) = zmax(i,j)
3102 if(is_north_pole(i,j))
then
3103 print*,
"set oa1 = 0 and ol=0 at i,j=", i,j
3108 else if(is_south_pole(i,j))
then
3109 print*,
"set oa1 = 0 and ol=1 at i,j=", i,j
3120 if( lat-dlat*0.5<-90.)
then
3121 print*,
"at i,j =", i,j, lat, dlat, lat-dlat*0.5
3122 print*,
"ERROR: lat-dlat*0.5<-90."
3125 if( lat+dlat*2 > 90.)
then
3128 print*,
"at i,j=",i,j,
" adjust dlat from ",
3129 & dlat_old,
" to ", dlat
3137 if(lat1<-90 .or. lat2>90)
then
3138 print*,
"at upper left i=,j=", i, j, lat, dlat,lat1,lat2
3140 xnsum11 =
get_xnsum(lon1,lat1,lon2,lat2,imn,jmn,glat,
3148 if(lat1<-90 .or. lat2>90)
then
3149 print*,
"at lower left i=,j=", i, j, lat, dlat,lat1,lat2
3151 xnsum12 =
get_xnsum(lon1,lat1,lon2,lat2,imn,jmn,glat,
3159 if(lat1<-90 .or. lat2>90)
then
3160 print*,
"at upper right i=,j=", i, j, lat, dlat,lat1,lat2
3162 xnsum21 =
get_xnsum(lon1,lat1,lon2,lat2,imn,jmn,glat,
3170 if(lat1<-90 .or. lat2>90)
then
3171 print*,
"at lower right i=,j=", i, j, lat, dlat,lat1,lat2
3174 xnsum22 =
get_xnsum(lon1,lat1,lon2,lat2,imn,jmn,glat,
3177 xnpu = xnsum11 + xnsum12
3178 xnpd = xnsum21 + xnsum22
3179 IF (xnpd .NE. xnpu) oa4(i,j,1) = 1. - xnpd / max(xnpu , 1.)
3181 xnpu = xnsum11 + xnsum21
3182 xnpd = xnsum12 + xnsum22
3183 IF (xnpd .NE. xnpu) oa4(i,j,2) = 1. - xnpd / max(xnpu , 1.)
3185 xnpu = xnsum11 + (xnsum12+xnsum21)*0.5
3186 xnpd = xnsum22 + (xnsum12+xnsum21)*0.5
3187 IF (xnpd .NE. xnpu) oa4(i,j,3) = 1. - xnpd / max(xnpu , 1.)
3189 xnpu = xnsum12 + (xnsum11+xnsum22)*0.5
3190 xnpd = xnsum21 + (xnsum11+xnsum22)*0.5
3191 IF (xnpd .NE. xnpu) oa4(i,j,4) = 1. - xnpd / max(xnpu , 1.)
3200 if(lat1<-90 .or. lat2>90)
then
3201 print*,
"at upper left i=,j=", i, j, lat, dlat,lat1,lat2
3203 call
get_xnsum2(lon1,lat1,lon2,lat2,imn,jmn,glat,
3204 & zavg,zslm,delxn, xnsum1_11, xnsum2_11, hc_11)
3211 if(lat1<-90 .or. lat2>90)
then
3212 print*,
"at lower left i=,j=", i, j, lat, dlat,lat1,lat2
3214 call
get_xnsum2(lon1,lat1,lon2,lat2,imn,jmn,glat,
3215 & zavg,zslm,delxn, xnsum1_12, xnsum2_12, hc_12)
3222 if(lat1<-90 .or. lat2>90)
then
3223 print*,
"at upper right i=,j=", i, j, lat, dlat,lat1,lat2
3225 call
get_xnsum2(lon1,lat1,lon2,lat2,imn,jmn,glat,
3226 & zavg,zslm,delxn, xnsum1_21, xnsum2_21, hc_21)
3233 if(lat1<-90 .or. lat2>90)
then
3234 print*,
"at lower right i=,j=", i, j, lat, dlat,lat1,lat2
3236 call
get_xnsum2(lon1,lat1,lon2,lat2,imn,jmn,glat,
3237 & zavg,zslm,delxn, xnsum1_22, xnsum2_22, hc_22)
3239 ol(i,j,3) = (xnsum1_22+xnsum1_11)/(xnsum2_22+xnsum2_11)
3240 ol(i,j,4) = (xnsum1_12+xnsum1_21)/(xnsum2_12+xnsum2_21)
3248 if(lat1<-90 .or. lat2>90)
then
3249 print*,
"at upper left i=,j=", i, j, lat, dlat,lat1,lat2
3251 call
get_xnsum3(lon1,lat1,lon2,lat2,imn,jmn,glat,
3252 & zavg,zslm,delxn, xnsum1_11, xnsum2_11, hc_11)
3259 if(lat1<-90 .or. lat2>90)
then
3260 print*,
"at lower left i=,j=", i, j, lat, dlat,lat1,lat2
3263 call
get_xnsum3(lon1,lat1,lon2,lat2,imn,jmn,glat,
3264 & zavg,zslm,delxn, xnsum1_12, xnsum2_12, hc_12)
3271 if(lat1<-90 .or. lat2>90)
then
3272 print*,
"at upper right i=,j=", i, j, lat, dlat,lat1,lat2
3274 call
get_xnsum3(lon1,lat1,lon2,lat2,imn,jmn,glat,
3275 & zavg,zslm,delxn, xnsum1_21, xnsum2_21, hc_21)
3282 if(lat1<-90 .or. lat2>90)
then
3283 print*,
"at lower right i=,j=", i, j, lat, dlat,lat1,lat2
3286 call
get_xnsum3(lon1,lat1,lon2,lat2,imn,jmn,glat,
3287 & zavg,zslm,delxn, xnsum1_22, xnsum2_22, hc_22)
3289 ol(i,j,1) = (xnsum1_11+xnsum1_21)/(xnsum2_11+xnsum2_21)
3290 ol(i,j,2) = (xnsum1_21+xnsum1_22)/(xnsum2_21+xnsum2_22)
3299 oa4(i,j,kwd) = sign( min( abs(t), 1. ), t )
3314 t = abs( oa4(i,j,kwd) )
3318 ELSE IF(t .GT. 0. .AND. t .LE. 1.)
THEN
3321 ELSE IF(t .GT. 1. .AND. t .LE. 10.)
THEN
3324 ELSE IF(t .GT. 10. .AND. t .LE. 100.)
THEN
3327 ELSE IF(t .GT. 100. .AND. t .LE. 1000.)
THEN
3330 ELSE IF(t .GT. 1000. .AND. t .LE. 10000.)
THEN
3333 ELSE IF(t .GT. 10000.)
THEN
3341 WRITE(6,*)
"! MAKEOA2 EXIT"
3356 real,
intent(in) :: theta1, phi1, theta2, phi2
3359 if(theta1 == theta2 .and. phi1 == phi2)
then
3364 dot = cos(phi1)*cos(phi2)*cos(theta1-theta2) + sin(phi1)*sin(phi2)
3365 if(dot > 1. ) dot = 1.
3366 if(dot < -1.) dot = -1.
3390 & bitmap_in,num_out, lon_out,lat_out, iindx, jindx )
3391 integer,
intent(in) :: im_in, jm_in, num_out
3392 real,
intent(in) :: geolon_in(im_in,jm_in)
3393 real,
intent(in) :: geolat_in(im_in,jm_in)
3394 logical*1,
intent(in) :: bitmap_in(im_in,jm_in)
3395 real,
intent(in) :: lon_out(num_out), lat_out(num_out)
3396 integer,
intent(out):: iindx(num_out), jindx(num_out)
3397 real,
parameter :: max_dist = 1.e+20
3398 integer,
parameter :: numnbr = 20
3399 integer :: i_c,j_c,jstart,jend
3402 print*,
"im_in,jm_in = ", im_in, jm_in
3403 print*,
"num_out = ", num_out
3404 print*,
"max and min of lon_in is", minval(geolon_in),
3406 print*,
"max and min of lat_in is", minval(geolat_in),
3408 print*,
"max and min of lon_out is", minval(lon_out),
3410 print*,
"max and min of lat_out is", minval(lat_out),
3412 print*,
"count(bitmap_in)= ", count(bitmap_in), max_dist
3421 if(lat .LE. geolat_in(1,j) .and.
3422 & lat .GE. geolat_in(1,j+1))
then
3426 if(lat > geolat_in(1,1)) j_c = 1
3427 if(lat < geolat_in(1,jm_in)) j_c = jm_in
3430 jstart = max(j_c-numnbr,1)
3431 jend = min(j_c+numnbr,jm_in)
3436 do j = jstart, jend;
do i = 1,im_in
3437 if(bitmap_in(i,j) )
then
3440 & geolon_in(i,j), geolat_in(i,j))
3442 iindx(n) = i; jindx(n) = j
3447 if(iindx(n) ==0)
then
3448 print*,
"lon,lat=", lon,lat
3449 print*,
"jstart, jend=", jstart, jend, dist
3450 print*,
"ERROR in get mismatch_index: not find nearest points"
3471 & num_out, data_out, iindx, jindx)
3472 integer,
intent(in) :: im_in, jm_in, num_out
3473 real,
intent(in) :: data_in(im_in,jm_in)
3474 real,
intent(out):: data_out(num_out)
3475 integer,
intent(in) :: iindx(num_out), jindx(num_out)
3478 data_out(n) = data_in(iindx(n),jindx(n))
3527 SUBROUTINE makeoa3(ZAVG,zslm,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
3528 1 oro,slm,oro1,xnsum,xnsum1,xnsum2,xnsum3,xnsum4,
3529 2 im,jm,imn,jmn,lon_c,lat_c,lon_t,lat_t,
3530 3 is_south_pole,is_north_pole,imi,jmi,oa_in,ol_in,
3531 4 slm_in,lon_in,lat_in)
3533 real,
parameter :: missing_value = -9999.
3534 real,
parameter :: d2r = 3.14159265358979/180.
3535 real,
PARAMETER :: r2d=180./3.14159265358979
3536 integer im,jm,imn,jmn,imi,jmi
3538 INTEGER zavg(imn,jmn),zslm(imn,jmn)
3540 real oro(im,jm),oro1(im,jm),elvmax(im,jm),zmax(im,jm)
3542 integer ioa4(im,jm,4)
3543 real oa_in(imi,jmi,4), ol_in(imi,jmi,4)
3544 real slm_in(imi,jmi)
3545 real lon_in(imi,jmi), lat_in(imi,jmi)
3546 real lon_c(im+1,jm+1), lat_c(im+1,jm+1)
3547 real lon_t(im,jm), lat_t(im,jm)
3548 logical is_south_pole(im,jm), is_north_pole(im,jm)
3549 real xnsum(im,jm),xnsum1(im,jm),xnsum2(im,jm)
3550 real xnsum3(im,jm),xnsum4(im,jm)
3551 real var(im,jm),ol(im,jm,4)
3553 integer i,j,ilist(imn),numx,i1,j1,ii1
3555 real lono(4),lato(4),loni,lati
3556 real delxn,hc,height,xnpu,xnpd,t
3557 integer ns0,ns1,ns2,ns3,ns4,ns5,ns6
3559 real lon,lat,dlon,dlat,dlat_old
3560 real lon1,lat1,lon2,lat2
3561 real xnsum11,xnsum12,xnsum21,xnsum22,xnsumx
3562 real hc_11, hc_12, hc_21, hc_22
3563 real xnsum1_11,xnsum1_12,xnsum1_21,xnsum1_22
3564 real xnsum2_11,xnsum2_12,xnsum2_21,xnsum2_22
3566 integer ist, ien, jst, jen
3567 real xland,xwatr,xl1,xs1,oroavg
3568 integer int_opt, ipopt(20), kgds_input(200), kgds_output(200)
3569 integer count_land_output
3570 integer ij, ijmdl_output, iret, num_mismatch_land, num
3572 logical*1,
allocatable :: bitmap_input(:,:)
3573 logical*1,
allocatable :: bitmap_output(:)
3574 integer,
allocatable :: ijsav_land_output(:)
3575 real,
allocatable :: lats_land_output(:)
3576 real,
allocatable :: lons_land_output(:)
3577 real,
allocatable :: output_data_land(:)
3578 real,
allocatable :: lons_mismatch_output(:)
3579 real,
allocatable :: lats_mismatch_output(:)
3580 real,
allocatable :: data_mismatch_output(:)
3581 integer,
allocatable :: iindx(:), jindx(:)
3587 ijmdl_output = im*jm
3590 glat(j) = -90. + (j-1) * delxn + delxn * 0.5
3592 print *,
' IM=',im,
' JM=',jm,
' IMN=',imn,
' JMN=',jmn
3600 elvmax(i,j) = oro(i,j)
3608 oro1(i,j) = oro(i,j)
3609 elvmax(i,j) = zmax(i,j)
3618 hc = 1116.2 - 0.878 * var(i,j)
3619 lono(1) = lon_c(i,j)
3620 lono(2) = lon_c(i+1,j)
3621 lono(3) = lon_c(i+1,j+1)
3622 lono(4) = lon_c(i,j+1)
3623 lato(1) = lat_c(i,j)
3624 lato(2) = lat_c(i+1,j)
3625 lato(3) = lat_c(i+1,j+1)
3626 lato(4) = lat_c(i,j+1)
3627 call
get_index(imn,jmn,4,lono,lato,delxn,jst,jen,ilist,numx)
3628 do j1 = jst, jen;
do ii1 = 1, numx
3631 lati = -90 + j1*delxn
3633 & lono*d2r,lato*d2r))
then
3635 height = float(zavg(i1,j1))
3636 IF(height.LT.-990.) height = 0.0
3637 IF ( height .gt. oro(i,j) )
then
3638 if ( height .gt. zmax(i,j) )zmax(i,j) = height
3651 oro1(i,j) = oro(i,j)
3652 elvmax(i,j) = zmax(i,j)
3672 kgds_input(4) = 90000
3675 kgds_input(7) = -90000
3676 kgds_input(8) = nint(-360000./imi)
3677 kgds_input(9) = nint((360.0 / float(imi))*1000.0)
3679 kgds_input(10) = jmi /2
3680 kgds_input(12) = 255
3681 kgds_input(20) = 255
3688 kgds_output(4) = 90000
3690 kgds_output(6) = 128
3691 kgds_output(7) = -90000
3692 kgds_output(8) = nint(-360000./im)
3693 kgds_output(9) = nint((360.0 / float(im))*1000.0)
3695 kgds_output(10) = jm /2
3696 kgds_output(12) = 255
3697 kgds_output(20) = 255
3700 print*,
"sum(slm) = ", sum(slm)
3701 do ij = 1, ijmdl_output
3703 i = mod(ij-1,im) + 1
3704 if (slm(i,j) > 0.0)
then
3705 count_land_output=count_land_output+1
3708 allocate(bitmap_input(imi,jmi))
3709 bitmap_input=.false.
3710 print*,
"number of land input=", sum(slm_in)
3711 where(slm_in > 0.0) bitmap_input=.true.
3712 print*,
"count(bitmap_input)", count(bitmap_input)
3714 allocate(bitmap_output(count_land_output))
3715 allocate(output_data_land(count_land_output))
3716 allocate(ijsav_land_output(count_land_output))
3717 allocate(lats_land_output(count_land_output))
3718 allocate(lons_land_output(count_land_output))
3723 do ij = 1, ijmdl_output
3725 i = mod(ij-1,im) + 1
3726 if (slm(i,j) > 0.0)
then
3727 count_land_output=count_land_output+1
3728 ijsav_land_output(count_land_output)=ij
3729 lats_land_output(count_land_output)=lat_t(i,j)
3730 lons_land_output(count_land_output)=lon_t(i,j)
3738 bitmap_output = .false.
3739 output_data_land = 0.0
3740 call ipolates(int_opt, ipopt, kgds_input, kgds_output,
3741 & (imi*jmi), count_land_output,
3742 & 1, 1, bitmap_input, oa_in(:,:,kwd),
3743 & count_land_output, lats_land_output,
3744 & lons_land_output, ibo,
3745 & bitmap_output, output_data_land, iret)
3747 print*,
'- ERROR IN IPOLATES ',iret
3751 num_mismatch_land = 0
3752 do ij = 1, count_land_output
3753 if (bitmap_output(ij))
then
3754 j = (ijsav_land_output(ij)-1)/im + 1
3755 i = mod(ijsav_land_output(ij)-1,im) + 1
3756 oa4(i,j,kwd)=output_data_land(ij)
3758 num_mismatch_land = num_mismatch_land + 1
3761 print*,
"num_mismatch_land = ", num_mismatch_land
3763 if(.not.
allocated(data_mismatch_output))
then
3764 allocate(lons_mismatch_output(num_mismatch_land))
3765 allocate(lats_mismatch_output(num_mismatch_land))
3766 allocate(data_mismatch_output(num_mismatch_land))
3767 allocate(iindx(num_mismatch_land))
3768 allocate(jindx(num_mismatch_land))
3771 do ij = 1, count_land_output
3772 if (.not. bitmap_output(ij))
then
3774 lons_mismatch_output(num) = lons_land_output(ij)
3775 lats_mismatch_output(num) = lats_land_output(ij)
3781 print*,
"before get_mismatch_index", count(bitmap_input)
3783 & lat_in*d2r,bitmap_input,num_mismatch_land,
3784 & lons_mismatch_output*d2r,lats_mismatch_output*d2r,
3788 data_mismatch_output = 0
3790 & num_mismatch_land,data_mismatch_output,iindx,jindx)
3793 do ij = 1, count_land_output
3794 if (.not. bitmap_output(ij))
then
3796 j = (ijsav_land_output(ij)-1)/im + 1
3797 i = mod(ijsav_land_output(ij)-1,im) + 1
3798 oa4(i,j,kwd) = data_mismatch_output(num)
3799 if(i==372 .and. j== 611)
then
3800 print*,
"ij=",ij, num, oa4(i,j,kwd),iindx(num),jindx(num)
3810 bitmap_output = .false.
3811 output_data_land = 0.0
3812 call ipolates(int_opt, ipopt, kgds_input, kgds_output,
3813 & (imi*jmi), count_land_output,
3814 & 1, 1, bitmap_input, ol_in(:,:,kwd),
3815 & count_land_output, lats_land_output,
3816 & lons_land_output, ibo,
3817 & bitmap_output, output_data_land, iret)
3819 print*,
'- ERROR IN IPOLATES ',iret
3823 num_mismatch_land = 0
3824 do ij = 1, count_land_output
3825 if (bitmap_output(ij))
then
3826 j = (ijsav_land_output(ij)-1)/im + 1
3827 i = mod(ijsav_land_output(ij)-1,im) + 1
3828 ol(i,j,kwd)=output_data_land(ij)
3830 num_mismatch_land = num_mismatch_land + 1
3833 print*,
"num_mismatch_land = ", num_mismatch_land
3835 data_mismatch_output = 0
3837 & num_mismatch_land,data_mismatch_output,iindx,jindx)
3840 do ij = 1, count_land_output
3841 if (.not. bitmap_output(ij))
then
3843 j = (ijsav_land_output(ij)-1)/im + 1
3844 i = mod(ijsav_land_output(ij)-1,im) + 1
3845 ol(i,j,kwd) = data_mismatch_output(num)
3846 if(i==372 .and. j== 611)
then
3847 print*,
"ij=",ij, num, ol(i,j,kwd),iindx(num),jindx(num)
3855 deallocate(lons_mismatch_output,lats_mismatch_output)
3856 deallocate(data_mismatch_output,iindx,jindx)
3857 deallocate(bitmap_output,output_data_land)
3858 deallocate(ijsav_land_output,lats_land_output)
3859 deallocate(lons_land_output)
3865 oa4(i,j,kwd) = sign( min( abs(t), 1. ), t )
3880 t = abs( oa4(i,j,kwd) )
3884 ELSE IF(t .GT. 0. .AND. t .LE. 1.)
THEN
3887 ELSE IF(t .GT. 1. .AND. t .LE. 10.)
THEN
3890 ELSE IF(t .GT. 10. .AND. t .LE. 100.)
THEN
3893 ELSE IF(t .GT. 100. .AND. t .LE. 1000.)
THEN
3896 ELSE IF(t .GT. 1000. .AND. t .LE. 10000.)
THEN
3899 ELSE IF(t .GT. 10000.)
THEN
3907 WRITE(6,*)
"! MAKEOA3 EXIT"
3924 REAL f(im,jm), wrk(im,jm)
3934 if (ir .gt. im) ir = ir - im
3961 integer,
intent(in):: im,jm,numi(jm)
3962 real,
intent(inout):: a(im,jm)
3966 r=
real(numi(j))/
real(im)
3968 ir=mod(nint((ig-1)*r),numi(j))+1
3987 integer,
intent(in):: im,jm,numi(jm)
3988 real,
intent(inout):: a(im,jm)
3992 r=
real(numi(j))/
real(im)
4014 real a(im,jm),rmin,rmax
4025 if(a(i,j).ge.rmax)rmax=a(i,j)
4026 if(a(i,j).le.rmin)rmin=a(i,j)
4029 write(6,150)rmin,rmax,title
4030 150
format(
'rmin=',e13.4,2x,
'rmax=',e13.4,2x,a8,
' ')
4049 real a(im,jm),rmin,rmax
4050 integer i,j,im,jm,imax,jmax
4060 if(a(i,j).ge.rmax)
then
4065 if(a(i,j).le.rmin)rmin=a(i,j)
4068 write(6,150)rmin,rmax,title
4069 150
format(
'rmin=',e13.4,2x,
'rmax=',e13.4,2x,a8,
' ')
4108 SUBROUTINE spfft1(IMAX,INCW,INCG,KMAX,W,G,IDIR)
4110 INTEGER,
INTENT(IN):: imax,incw,incg,kmax,idir
4111 COMPLEX,
INTENT(INOUT):: w(incw,kmax)
4112 REAL,
INTENT(INOUT):: g(incg,kmax)
4113 REAL:: aux1(25000+int(0.82*imax))
4114 REAL:: aux2(20000+int(0.57*imax))
4115 INTEGER:: naux1,naux2
4117 naux1=25000+int(0.82*imax)
4118 naux2=20000+int(0.57*imax)
4123 SELECT CASE(digits(1.))
4125 CALL scrft(1,w,incw,g,incg,imax,kmax,-1,1.,
4126 & aux1,naux1,aux2,naux2,0.,0)
4127 CALL scrft(0,w,incw,g,incg,imax,kmax,-1,1.,
4128 & aux1,naux1,aux2,naux2,0.,0)
4130 CALL dcrft(1,w,incw,g,incg,imax,kmax,-1,1.,
4131 & aux1,naux1,aux2,naux2,0.,0)
4132 CALL dcrft(0,w,incw,g,incg,imax,kmax,-1,1.,
4133 & aux1,naux1,aux2,naux2,0.,0)
4138 SELECT CASE(digits(1.))
4140 CALL srcft(1,g,incg,w,incw,imax,kmax,+1,1./imax,
4141 & aux1,naux1,aux2,naux2,0.,0)
4142 CALL srcft(0,g,incg,w,incw,imax,kmax,+1,1./imax,
4143 & aux1,naux1,aux2,naux2,0.,0)
4145 CALL drcft(1,g,incg,w,incw,imax,kmax,+1,1./imax,
4146 & aux1,naux1,aux2,naux2,0.,0)
4147 CALL drcft(0,g,incg,w,incw,imax,kmax,+1,1./imax,
4148 & aux1,naux1,aux2,naux2,0.,0)
4161 integer*2 glob(360*120,180*120)
4166 parameter(ix=40*120,jx=50*120)
4167 parameter(ia=60*120,ja=30*120)
4169 integer*2 idat(ix,jx)
4174 real(kind=8) dloin,dlain,rlon,rlat
4176 open(235, file=
"./fort.235", access=
'direct', recl=43200*21600*2)
4181 call
maxmin(glob,360*120*180*120,
'global0')
4187 rlon= -179.995833333333333333333333d0
4188 rlat= 89.995833333333333333333333d0
4215 integer iaamax, iaamin, len, j, m, ja, kount
4216 integer(8) sum2,std,mean,isum
4217 integer i_count_notset,kount_9
4232 if ( ja .eq. -9999 )
then
4236 if ( ja .eq. -12345 ) i_count_notset=i_count_notset+1
4238 iaamax = max0( iaamax, ja )
4239 iaamin = min0( iaamin, ja )
4250 std = ifix(sqrt(float((sum2/(kount))-mean**2)))
4251 print*,tile,
' max=',iaamax,
' min=',iaamin,
' sum=',isum,
4252 &
' i_count_notset=',i_count_notset
4253 print*,tile,
' mean=',mean,
' std.dev=',std,
4254 &
' ko9s=',kount,kount_9,kount+kount_9
4270 real(kind=4) a(im,jm),rmin,rmax,undef
4271 integer i,j,im,jm,imax,jmax,imin,jmin,iundef
4272 character*8 title,chara
4288 if(a(i,j).ge.rmax)
then
4293 if(a(i,j).le.rmin)
then
4294 if ( a(i,j) .eq. undef )
then
4304 write(6,150)chara,rmin,imin,jmin,rmax,imax,jmax,iundef
4305 150
format(1x,a8,2x,
'rmin=',e13.4,2i6,2x,
'rmax=',e13.4,3i6)
4321 integer,
intent(in) :: siz
4322 real,
intent(in) :: lon(siz), lat(siz)
4323 real,
intent(out) :: x(siz), y(siz), z(siz)
4328 x(n) = cos(lat(n))*cos(lon(n))
4329 y(n) = cos(lat(n))*sin(lon(n))
4343 real,
parameter :: epsln30 = 1.e-30
4344 real,
parameter :: pi=3.1415926535897931
4345 real v1(3), v2(3), v3(3)
4348 real px, py, pz, qx, qy, qz, ddd;
4351 px = v1(2)*v2(3) - v1(3)*v2(2)
4352 py = v1(3)*v2(1) - v1(1)*v2(3)
4353 pz = v1(1)*v2(2) - v1(2)*v2(1)
4355 qx = v1(2)*v3(3) - v1(3)*v3(2);
4356 qy = v1(3)*v3(1) - v1(1)*v3(3);
4357 qz = v1(1)*v3(2) - v1(2)*v3(1);
4359 ddd = (px*px+py*py+pz*pz)*(qx*qx+qy*qy+qz*qz);
4360 if ( ddd <= 0.0 )
then
4363 ddd = (px*qx+py*qy+pz*qz) / sqrt(ddd);
4364 if( abs(ddd-1) < epsln30 ) ddd = 1;
4365 if( abs(ddd+1) < epsln30 ) ddd = -1;
4366 if ( ddd>1. .or. ddd<-1. )
then
4393 real,
parameter :: epsln10 = 1.e-10
4394 real,
parameter :: epsln8 = 1.e-8
4395 real,
parameter :: pi=3.1415926535897931
4396 real,
parameter :: range_check_criteria=0.05
4401 real lon2(npts), lat2(npts)
4402 real x2(npts), y2(npts), z2(npts)
4403 real lon1_1d(1), lat1_1d(1)
4404 real x1(1), y1(1), z1(1)
4405 real pnt0(3),pnt1(3),pnt2(3)
4407 real max_x2,min_x2,max_y2,min_y2,max_z2,min_z2
4409 call
latlon2xyz(npts,lon2, lat2, x2, y2, z2);
4412 call
latlon2xyz(1,lon1_1d, lat1_1d, x1, y1, z1);
4415 if( x1(1) > max_x2+range_check_criteria )
return
4417 if( x1(1)+range_check_criteria < min_x2 )
return
4419 if( y1(1) > max_y2+range_check_criteria )
return
4421 if( y1(1)+range_check_criteria < min_y2 )
return
4423 if( z1(1) > max_z2+range_check_criteria )
return
4425 if( z1(1)+range_check_criteria < min_z2 )
return
4433 if(abs(x1(1)-x2(i)) < epsln10 .and.
4434 & abs(y1(1)-y2(i)) < epsln10 .and.
4435 & abs(z1(1)-z2(i)) < epsln10 )
then
4440 if(ip1>npts) ip1 = 1
4450 anglesum = anglesum + angle
4453 if(abs(anglesum-2*pi) < epsln8)
then
4487 & glat,zavg,zslm,delxn)
4492 real lon1,lat1,lon2,lat2,oro,delxn
4495 integer zavg(imn,jmn),zslm(imn,jmn)
4496 integer i, j, ist, ien, jst, jen, i1
4498 real xland,xwatr,xl1,xs1,slm,xnsum
4501 if( glat(j) .GT. lat1 )
then
4507 if( glat(j) .GT. lat2 )
then
4514 ist = lon1/delxn + 1
4516 if(ist .le.0) ist = ist + imn
4517 if(ien < ist) ien = ien + imn
4528 do i1 = 1, ien - ist + 1
4530 if( i .LE. 0) i = i + imn
4531 if( i .GT. imn) i = i - imn
4532 xland = xland + float(zslm(i,j))
4533 xwatr = xwatr + float(1-zslm(i,j))
4535 height = float(zavg(i,j))
4536 IF(height.LT.-990.) height = 0.0
4537 xl1 = xl1 + height * float(zslm(i,j))
4538 xs1 = xs1 + height * float(1-zslm(i,j))
4541 if( xnsum > 1.)
THEN
4542 slm = float(nint(xland/xnsum))
4554 if( i .LE. 0) i = i + imn
4555 if( i .GT. imn) i = i - imn
4556 height = float(zavg(i,j))
4557 IF(height.LT.-990.) height = 0.0
4594 & glat,zavg,zslm,delxn,xnsum1,xnsum2,hc)
4597 real,
intent(out) :: xnsum1,xnsum2,hc
4599 real lon1,lat1,lon2,lat2,oro,delxn
4602 integer zavg(imn,jmn),zslm(imn,jmn)
4603 integer i, j, ist, ien, jst, jen, i1
4605 real xw1,xw2,slm,xnsum
4608 if( glat(j) .GT. lat1 )
then
4614 if( glat(j) .GT. lat2 )
then
4621 ist = lon1/delxn + 1
4623 if(ist .le.0) ist = ist + imn
4624 if(ien < ist) ien = ien + imn
4632 do i1 = 1, ien - ist + 1
4634 if( i .LE. 0) i = i + imn
4635 if( i .GT. imn) i = i - imn
4637 height = float(zavg(i,j))
4638 IF(height.LT.-990.) height = 0.0
4640 xw2 = xw2 + height ** 2
4643 var = sqrt(max(xw2/xnsum-(xw1/xnsum)**2,0.))
4644 hc = 1116.2 - 0.878 * var
4650 if( i .LE. 0) i = i + imn
4651 if( i .GT. imn) i = i - imn
4652 height = float(zavg(i,j))
4653 IF ( height .gt. hc ) xnsum1 = xnsum1 + 1
4690 & glat,zavg,zslm,delxn,xnsum1,xnsum2,hc)
4693 real,
intent(out) :: xnsum1,xnsum2
4694 real lon1,lat1,lon2,lat2,oro,delxn
4697 integer zavg(imn,jmn),zslm(imn,jmn)
4698 integer i, j, ist, ien, jst, jen, i1
4700 real xw1,xw2,slm,xnsum
4706 if( glat(j) .GT. lat1 )
then
4712 if( glat(j) .GT. lat2 )
then
4719 ist = lon1/delxn + 1
4721 if(ist .le.0) ist = ist + imn
4722 if(ien < ist) ien = ien + imn
4730 if( i .LE. 0) i = i + imn
4731 if( i .GT. imn) i = i - imn
4732 height = float(zavg(i,j))
4733 IF ( height .gt. hc ) xnsum1 = xnsum1 + 1
4754 integer inan1,inan2,inan3,inan4,inaq1,inaq2,inaq3,inaq4
4757 equivalence(itest,word)
4760 data inan1/x
'7F800001'/
4761 data inan2/x
'7FBFFFFF'/
4762 data inan3/x
'FF800001'/
4763 data inan4/x
'FFBFFFFF'/
4767 data inaq1/x
'7FC00000'/
4768 data inaq2/x
'7FFFFFFF'/
4769 data inaq3/x
'FFC00000'/
4770 data inaq4/x
'FFFFFFFF'/
4772 real(kind=8)a(l),rtc,t1,t2
4779 if( (itest .GE. inan1 .AND. itest .LE. inan2) .OR.
4780 * (itest .GE. inan3 .AND. itest .LE. inan4) )
then
4781 print *,
' NaNs detected at word',k,
' ',c
4784 if( (itest .GE. inaq1 .AND. itest .LE. inaq2) .OR.
4785 * (itest .GE. inaq3 .AND. itest .LE. inaq4) )
then
4786 print *,
' NaNq detected at word',k,
' ',c
4794 102
format(
' time to check ',i9,
' words is ',f10.4,
' ',a24)
4803 character(8) :: date
4804 character(10) :: time
4805 character(5) :: zone
4806 integer,
dimension(8) :: values
4809 call date_and_time(date,time,zone,values)
4810 total=(3600*values(5))+(60*values(6))
4812 elapsed=float(total) + (1.0e-3*float(values(8)))
subroutine get_xnsum3(lon1, lat1, lon2, lat2, IMN, JMN, glat, zavg, zslm, delxn, xnsum1, xnsum2, HC)
Count the number of high-resolution orography points that are higher than a critical value inside a m...
logical function inside_a_polygon(lon1, lat1, npts, lon2, lat2)
Check if a point is inside a polygon.
real function spherical_distance(theta1, phi1, theta2, phi2)
Compute a great circle distance between two points.
subroutine tersub(IMN, JMN, IM, JM, NM, NR, NF0, NF1, NW, EFAC, BLAT, OUTGRID, INPUTOROG)
Driver routine to compute terrain.
real function timef()
Get the date/time for the system clock.
subroutine netcdf_err(err, string)
Check NetCDF error code and output the error message.
subroutine latlon2xyz(siz, lon, lat, x, y, z)
Convert from latitude and longitude to x,y,z coordinates.
subroutine spfft1(IMAX, INCW, INCG, KMAX, W, G, IDIR)
Perform multiple fast fourier transforms.
subroutine gg2rg(im, jm, numi, a)
Convert from a full grid to a reduced grid.
subroutine rg2gg(im, jm, numi, a)
Convert from a reduced grid to a full grid.
real function spherical_angle(v1, v2, v3)
Compute spherical angle.
subroutine makeoa3(ZAVG, zslm, VAR, GLAT, OA4, OL, IOA4, ELVMAX, ORO, SLM, oro1, XNSUM, XNSUM1, XNSUM2, XNSUM3, XNSUM4, IM, JM, IMN, JMN, lon_c, lat_c, lon_t, lat_t, is_south_pole, is_north_pole, IMI, JMI, OA_IN, OL_IN, slm_in, lon_in, lat_in)
Create orographic asymmetry and orographic length scale on the model grid.
subroutine nanc(a, l, c)
Report NaNS and NaNQ within an address range for 8-byte real words.
subroutine minmaxj(IM, JM, A, title)
Print out the maximum and minimum values of an array and their i/j location.
subroutine makepc(ZAVG, ZSLM, THETA, GAMMA, SIGMA, GLAT, IST, IEN, JST, JEN, IM, JM, IMN, JMN, XLAT, numi)
Make the principle coordinates - slope of orography, anisotropy, angle of mountain range with respect...
subroutine makemt2(ZAVG, ZSLM, ORO, SLM, land_frac, VAR, VAR4, GLAT, IM, JM, IMN, JMN, lon_c, lat_c)
Create the orography, land-mask, land fraction, standard deviation of orography and the convexity on ...
subroutine write_netcdf(im, jm, slm, land_frac, oro, orf, hprime, ntiles, tile, geolon, geolat, lon, lat)
Write out orography file in netcdf format.
subroutine minmxj(IM, JM, A, title)
Print out the maximum and minimum values of an array.
real function get_lat_angle(dy, DEGRAD)
Convert the 'y' direction distance of a cubed-sphere grid point to the corresponding distance in lati...
subroutine get_index(IMN, JMN, npts, lonO, latO, DELXN, jst, jen, ilist, numx)
Determine the location of a cubed-sphere point within the high-resolution orography data...
subroutine get_xnsum2(lon1, lat1, lon2, lat2, IMN, JMN, glat, zavg, zslm, delxn, xnsum1, xnsum2, HC)
Count the number of high-resolution orography points that are higher than a critical value inside a m...
subroutine mnmxja(IM, JM, A, imax, jmax, title)
Print out the maximum and minimum values of an array.
real function get_xnsum(lon1, lat1, lon2, lat2, IMN, JMN, glat, zavg, zslm, delxn)
Count the number of high-resolution orography points that are higher than the model grid box average ...
subroutine maxmin(ia, len, tile)
Print the maximum, mininum, mean and standard deviation of an array.
subroutine makeoa(ZAVG, VAR, GLAT, OA4, OL, IOA4, ELVMAX, ORO, oro1, XNSUM, XNSUM1, XNSUM2, XNSUM3, XNSUM4, IST, IEN, JST, JEN, IM, JM, IMN, JMN, XLAT, numi)
Create orographic asymmetry and orographic length scale on the model grid.
subroutine interpolate_mismatch(im_in, jm_in, data_in, num_out, data_out, iindx, jindx)
Replace unmapped model land points with the nearest land point on the input grid. ...
subroutine read_g(glob, ITOPO)
Read input global 30-arc second orography data.
subroutine get_mismatch_index(im_in, jm_in, geolon_in, geolat_in, bitmap_in, num_out, lon_out, lat_out, iindx, jindx)
For unmapped land points, find the nearest land point on the input data and pass back its i/j index...
subroutine revers(IM, JM, numi, F, WRK)
Reverse the east-west and north-south axes in a two-dimensional array.
subroutine makemt(ZAVG, ZSLM, ORO, SLM, VAR, VAR4, GLAT, IST, IEN, JST, JEN, IM, JM, IMN, JMN, XLAT, numi)
Create the orography, land-mask, standard deviation of orography and the convexity on a model gaussia...
real function get_lon_angle(dx, lat, DEGRAD)
Convert the 'x' direction distance of a cubed-sphere grid point to the corresponding distance in long...
subroutine makeoa2(ZAVG, zslm, VAR, GLAT, OA4, OL, IOA4, ELVMAX, ORO, oro1, XNSUM, XNSUM1, XNSUM2, XNSUM3, XNSUM4, IM, JM, IMN, JMN, lon_c, lat_c, lon_t, lat_t, dx, dy, is_south_pole, is_north_pole)
Create orographic asymmetry and orographic length scale on the model grid.
subroutine makepc2(ZAVG, ZSLM, THETA, GAMMA, SIGMA, GLAT, IM, JM, IMN, JMN, lon_c, lat_c)
Make the principle coordinates - slope of orography, anisotropy, angle of mountain range with respect...