Program tc_detect ! By: hapt, 2018 Implicit none Integer:: total_num Integer, parameter:: max_tcstep=100 Integer:: inum, istep, itc, ntc, jnum Integer:: nstep Integer,dimension(300):: tc_step, new_tc_step Integer:: life_length=6 Real,parameter:: flag=-99.99 Real, dimension (:,:), allocatable:: tc_lon, tc_lat Integer, dimension (:,:), allocatable:: tc_year, tc_mon, tc_day, tc_hour Real, dimension (:,:), allocatable:: new_tc_lon, new_tc_lat Integer, dimension (:,:), allocatable:: new_tc_year, new_tc_mon, new_tc_day, new_tc_hour Integer, dimension (:), allocatable:: tc_flag Character:: ctmp Character*100:: iDir, oDir Character*100:: cfile, ofile Integer,parameter:: nmon=12 Integer, dimension(nmon):: ntc_mon Integer:: imon, itmp Integer:: day_crit=2 Real:: radius_crit=20 Integer:: tmp_day, tmp_step Real:: tmp_radius Integer,dimension(12):: tc_mon_count Integer:: tc_start, tc_end ! Namelist namelist/nml/iDir,cfile,oDir,life_length Open (111,file='info.txt',status='unknown') Read(111,nml) ! Write(*,*) iDir Close(111) itc=0 ntc_mon=0 tc_mon_count=0 write(*,*) trim(iDir)//trim(cfile)//".txt" Open (11, file=trim(iDir)//trim(cfile)//".txt", status="unknown") Read (11,*) ctmp, total_num Allocate (tc_lon(total_num,max_tcstep)) Allocate (tc_lat(total_num,max_tcstep)) Allocate (tc_year(total_num,max_tcstep)) Allocate (tc_mon(total_num,max_tcstep)) Allocate (tc_day(total_num,max_tcstep)) Allocate (tc_hour(total_num,max_tcstep)) Allocate (tc_flag(total_num)) Allocate (new_tc_lon(total_num,max_tcstep)) Allocate (new_tc_lat(total_num,max_tcstep)) Allocate (new_tc_year(total_num,max_tcstep)) Allocate (new_tc_mon(total_num,max_tcstep)) Allocate (new_tc_day(total_num,max_tcstep)) Allocate (new_tc_hour(total_num,max_tcstep)) !Write (*,*) total_num Do inum=1,total_num Read(11,*) Read(11,*) Read(11,*) ctmp, nstep !If (nstep.ge.life_length) then itc=itc+1 tc_step(itc)=nstep !Write(*,*) itc, nstep Do istep=1,nstep Read(11,*) tc_year(itc,istep), tc_mon(itc,istep), & tc_day(itc,istep), tc_hour(itc,istep), tc_lon(itc,istep), tc_lat(itc,istep) If (istep.eq.1) then ntc_mon(tc_mon(itc,istep))=ntc_mon(tc_mon(itc,istep))+1 End if End do !Else ! Do istep=1,nstep ! Read(11,*) ! !Write(*,*) inum ! End do !End if Do imon=1,12 If (tc_mon(itc,1).eq.imon) then tc_mon_count(imon)=tc_mon_count(imon)+1 End if End do End do Close(11) ntc=itc total_num=ntc ! ---- new criteria itmp=0 tc_flag=0 new_tc_step=0 !Open (12, file="for_check.txt",status="unknown") Do inum=1,total_num-1 Do jnum=inum+1,total_num !If(tc_mon(inum,1).eq.1) then If (tc_mon(inum,1).eq.tc_mon(jnum,1)) then tmp_day=abs(tc_day(inum,1)-tc_day(jnum,1)) If (tmp_day.le.day_crit) then tmp_radius=sqrt((tc_lon(inum,1)-tc_lon(jnum,1))**2+(tc_lat(inum,1)-tc_lat(jnum,1))**2) If (tmp_radius.le.radius_crit) then !print*, inum, jnum, tc_mon(inum,1),tc_day(inum,1) If (tc_step(inum).gt.tc_step(jnum)) then tc_flag(jnum)=1 tc_flag(inum)=0 Else tc_flag(jnum)=0 tc_flag(inum)=1 End if print*, inum, tc_flag(inum),jnum,tc_flag(jnum),tc_mon(inum,1),tc_day(inum,1) End if End if End if !End if End do End do ntc=0 Do inum=1,total_num If (tc_flag(inum).eq.0) then ntc=ntc+1 End if End do itmp=0 Open(4,file="for_check.txt",status="unknown") Write(4,*) "TC# ", ntc Do itc=1,total_num If (tc_flag(itc).eq.0) then itmp=itmp+1 Write(4,*) " ---------------------------------- " Write(4,*) "TC#", itmp Write(4,*) "Num_Obs:", tc_step(itc) Do istep=1,tc_step(itc) Write(4,"(2(I4,3x),I4,2x,I4,2x,3(F6.1,2x))") tc_year(itc,istep),tc_mon(itc,istep),& tc_day(itc,istep), tc_hour(itc,istep),tc_lon(itc,istep), tc_lat(itc,istep) End do End if End do Close(4) End