program compo_ec implicit none integer::i,j,h,imn,imx,jmn,jmx,syear,eyear,iyear,smonth,emonth,imonth,ice1,jce1,xst,xen,yst,yen,month1,n,nto,nto2,nmx,nt,nnt,out,nout,nto3,it,itmax,tt integer::xst2,xen2,yst2,yen2,xst3,xen3,yst3,yen3,time,time2,time4,itime,t,tmx,tmn,ntmx,nntmx,trid,trid2,xst1,xen1,yst1,yen1,iit integer::day1,hour1,hmx,hmn,hhmn,hhmx,hmx2,ob,nob,nfs,undef integer::xst4,xen4,yst4,yen4 integer::ice2, jce2 parameter(imx=105,jmx=65,hmx=37,syear=1979,eyear=2016,smonth=3,emonth=5,hmn=1,jmn=1,imn=1,tmn=1,hhmn=1,hhmx=40,hmx2=27,itmax=17,nntmx=20000) real::lat1,lon1,jlat,jlon,pi,es,ssp,slpup,slplow,lon2,lat2,minslp,hoge real::slpmin real::hoge1,hoge2,hoge3,hoge4 real,dimension(nntmx)::trid3,time3 real,dimension(imx,jmx,hmx)::slant,def,ept,fmag real,dimension(jmx)::dlam,co,lat real,dimension(imx,jmx,hmx2)::spfh real,dimension(imx,jmx,hmx)::ug,vg,qx1,qy1,qx,qy,qdiv,u,v,vvel,pv real,dimension(-40:40,-40:40,hmx,itmax)::coqdiv,cou,cov,covvel,copv real,dimension(-40:40,-40:40,itmax)::cocold2,cowarm2,cocold,cowarm,cosreh,cosreh2,cosreh3 real,dimension(-40:40,itmax)::sco3,sco4,sco5 real,dimension(imx,jmx)::cold,warm,cape,sreh,ehi,mdvdz,mlapse,psurf,slp,tmp2m,dep,u10m,v10m,rh2m,sp2m,pt2m,cu,cv,suz,svz,shear_u,shear_v,mshear real::p(hmx)=(/1000., 975., 950., 925., 900., 875., 850., 825., 800., 775., 750., 700., & 650., 600., 550., 500., 450., 400., 350., 300., 250., 225., 200., 175., 150., 125., 100., & 70., 50., 30., 20., 10.,7., 5., 3., 2., 1./) real::ber,mdlon,mdlat,bermax integer::ii,jj,in,jn real,dimension(-40:40)::newy,y_ec,ypos real,dimension(-40:40,-40:40)::front,fcold,fwarm real,dimension(-40:40,-40:40,hmx)::qdivxy,uxy,vxy,vvelxy,pvxy real,dimension(-40:40)::newx real,dimension(-40:40,-40:40)::x_ec,xpos real::r,dx,dy,defx,defy,ai,aj,dphi real::xbound1,xbound2,dist,dist2,defx2,defy2 real::spflag,btrid integer::ihoge1,ihoge2,ecnum character::jetpos*8, nmem1*1,nmem*2,mmonth*2,year*4,SEA*3,region*3,CAT*2 logical::fast btrid = 0 fast=.false. ! a little output variables nmx=20000 ntmx=20000 pi=acos(-1.) write(6,*) pi xst=20 yst=20 xen=20 yen=20 xst2=25 yst2=25 xen2=25 yen2=25 xst3=35 yst3=35 xen3=35 yen3=35 xst1=3 xen1=3 yst1=3 yen1=3 xst4 = 4 xen4 = 4 yst4 = 4 yen4 = 8 !slpup=100500. !slplow=99500. slpup=1100. slplow=500. ice1=0 jce1=0 out=0 nout=0 sco3=0. sco4=0. !SEA='MAM' !region='JPN' !CAT='OJ' cosreh=0 cocold=0 cowarm=0 dx=1.25e5 dy=1.25e5 ob=1 nob=0 r=6378.e3 dphi=1.25*pi/180. undef=99999 SEA='DJF' region='JPN' CAT='PO' jetpos='Sjetconf' ecnum = 0 !write(6,*) 'read namelist' !namelist/namdim/CAT,SEA,region !write(6,*) 'category' !write(6,*) CAT,' ',SEA,' ',region !read(5,namdim) do i=-40,40 newx(i)=dx*real(i) enddo do j=-40,40 newy(j)=dy*real(j) enddo do j=jmn,jmx lat(j)=80.-1.25*(j-1) co(j)=cos(lat(j)/180.*pi) enddo do j = jmn, jmx dlam(j) = 1.25*2.*pi/180.*r enddo do it = 1,itmax if(it.le.9) then write(nmem1,'(i1)') it nmem = '0'//nmem1 else write(nmem,'(i2)') it endif ! open(60+it,file='./'//CAT//'/yemem_'//nmem//'_sfvar_DRATE05_100_'//CAT//'_'//SEA//'_long.data',status='unknown',form='unformatted') enddo do iyear=syear,eyear write(year,'(i4)') iyear open(28,file='./EC_MAXDEV/'//year//''//SEA//''//CAT//'_MAXDEV_LONLAT'//region//'_vavelowpass5day_'//jetpos//'_190E_1000_700' ,status='old',form='formatted') ! open(28,file='./EC_MAXDEV/'//year//''//SEA//''//CAT//'_MAXDEV_LONLAT'//region//'_vavelowpass5day_'//jetpos//'_190E' ,status='old',form='formatted') ! open(38,file='./EC_MINSLP/'//year//''//SEA//''//CAT//'_MINSLP_LONLAT'//region//'_vavelowpass5day_'//jetpos ,status='old',form='formatted') do nt=1,ntmx read(28,*,end=120) mdlon, mdlat, trid2, time2, bermax write(6,*) mdlon, mdlat, trid2, time2, slpmin write(6,*) 'KT',iyear,trid2,time2,bermax minslp=100000. !if(slpmin.ge.slplow.and.slpmin.le.slpup.and.bermax.gt.0.and.bermax.le.10.0.and.trid2.ne.undef) then if(bermax.gt.0.and.bermax.le.10.0.and.trid2.ne.undef) then it=0 iit=-4 do itime=time2-itmax/2,time2+itmax/2 ecnum = 0 !do itime=time2,time2 write(year,'(i4)') iyear write(6,*) 'itime is from',time2-itmax/2,'to',time2+itmax/2 write(6,*) 'keytime=',time2 !write(6,*) 'iyear=', iyear,'itime=',itime if(SEA.eq.'MAM') then if(itime.le.31*4) then month1=3 mmonth='03' tmx=31*4 if(mod(itime,4)==0) then day1=itime/4 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1 hour1=12 endif elseif(itime.le.31*4+30*4) then month1=4 mmonth='04' tmx=30*4 if(mod(itime,4)==0) then day1=itime/4-31 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1-31 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1-31 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1-31 hour1=12 endif write(6,*) 'pass',iyear,trid,minslp,time2 else month1=5 mmonth='05' tmx=31*4 if(mod(itime,4)==0) then day1=itime/4-31-30 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1-31-30 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1-31-30 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1-31-30 hour1=12 endif endif endif !write(6,*) month1 if(SEA.eq.'SON') then if(itime.le.30*4) then month1=9 mmonth='09' tmx=30*4 if(mod(itime,4)==0) then day1=itime/4 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1 hour1=12 endif elseif(itime.le.31*4+30*4) then month1=10 mmonth='10' tmx=31*4 if(mod(itime,4)==0) then day1=itime/4-30 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1-30 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1-30 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1-30 hour1=12 endif write(6,*) 'pass',iyear,trid,minslp,time2 else month1=11 mmonth='11' tmx=30*4 if(mod(itime,4)==0) then day1=itime/4-31-30 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1-31-30 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1-31-30 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1-31-30 hour1=12 endif endif endif !write(6,*) month1 if(SEA.eq.'DJF') then if(itime.le.31*4) then month1=0 mmonth='12' tmx=31*4 if(mod(itime,4)==0) then day1=itime/4 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1 hour1=12 endif elseif(itime.le.31*4+31*4) then month1=1 mmonth='01' tmx=31*4 if(mod(itime,4)==0) then day1=itime/4-31 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1-31 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1-31 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1-31 hour1=12 endif else month1=2 mmonth='02' if(mod(iyear,4).eq.0) then tmx=29*4 else tmx=28*4 endif if(mod(itime,4)==0) then day1=itime/4-31-31 hour1=18 elseif(mod(itime,4)==1) then day1=itime/4+1-31-31 hour1=0 elseif(mod(itime,4)==2) then day1=itime/4+1-31-31 hour1=6 elseif(mod(itime,4)==3) then day1=itime/4+1-31-31 hour1=12 endif endif endif !write(6,*) 'month=', mmonth,' ',year iit=iit+1 !write(6,*) month1 open(26,file='./EC_TRACK/'//year//''//SEA//''//CAT//'_track_EC_'//region//'_190E',status='old',form='formatted') do nnt=1,nntmx read(26,*,end=130) lon1,lat1,time3(nnt),trid3(nnt),ber if(trid2.eq.trid3(nnt)) then !write(6,*) 'pass2',trid2 if(itmax.ge.2) then do tt=1,itmax/2 !do tt=1,8 if(time3(nnt).eq.time2-itmax/2+tt.and.it.eq.0) then it=it+tt endif enddo endif if(month1.eq.0) then write(year,'(i4)') iyear-1 else write(year,'(i4)') iyear endif !open(50,file='/data2/tochimoto/work/jra55/data/'//region//'/NEW_TFPWF1000_0_JRA55_'//region//'.'//year//'.'//mmonth//'.data',status='old',form='unformatted') do t=tmn,tmx if(month1.eq.0) then time4=t endif if(month1.eq.1) then time4=t+31*4 endif if(month1.eq.2) then time4=t+31*4+31*4 endif if(month1.eq.3) then time4=t endif if(month1.eq.4) then time4=t+31*4 endif if(month1.eq.5) then time4=t+30*4+31*4 endif if(month1.eq.9) then time4=t endif if(month1.eq.10) then time4=t+30*4 endif if(month1.eq.11) then time4=t+30*4+31*4 endif open(80, file = '/home/tochimoto/breeze1/tochimoto/jra55/'//region//'/NEW_SURF1000_0_JRA55_'//region//'.'//year//'.'//mmonth//'.data',status = 'old',form = 'unformatted') read(80) ((slp(i, j), i = imn, imx), j = jmn, jmx) slp = slp / 100. do i=imn,imx do j=jmn,jmx jlat = 80. - 1.25 * real(j - 1) if(region == 'USA') then jlon = 220. + 1.25*real(i - 1) else jlon = 80. + 1.25*real(i - 1) endif if(lat1.ge.jlat-1.25*0.5.and.lat1.le.jlat+1.25*0.5.and.lon1.ge.jlon-1.25*0.5.and.lon1.le.jlon+1.25*0.5) then ice1=i jce1=j lon2=jlon lat2=jlat endif enddo enddo !write(6,*) 'itime==time4?', itime,time4,time3(nnt) if(itime.eq.time4.and.itime.eq.time3(nnt)) then it = it+1 if(it .eq. itmax/2 + 1) then out = out+1 endif slpmin = slp(ice1,jce1) if(jce1 .ge.3 .and. ice1 .ge. 3 .and. jce1 .le. jmx-2 .and. ice1 .le. imx-2) then do j = jce1 - yst1, jce1 + yen1 do i = ice1 - xst1, ice1 + xen1 if(slp(i,j) .lt. slpmin) then slpmin = slp(i,j) ice2 = i jce2 = j endif enddo enddo endif if(it.le.9) then write(nmem1,'(i1)') it nmem = '0'//nmem1 else write(nmem,'(i2)') it endif open(57,file = 'SLPMIN_'//jetpos//'_'//nmem//'_'//CAT//'_'//SEA//'_long_160E_190E_1000_700.data', position = 'append', form = 'formatted') !if(lon1 .ge. 160.) then if(mdlon .ge. 160.) then write(57,*) slpmin ecnum = ecnum + 1 endif endif ! pick up EC enddo !time loop endif close(80) enddo !nntloop 130 continue close(26) !write(6,*) n,nt,nnt,iyear enddo ! itimeloop endif !write(6,*) n,nt enddo !ntloop 120 continue !write(6,*) n,nt close(28) enddo !year loop ! write(6,*) 'out=',out,'ecnum=',ecnum endprogram compo_ec