文件
tem3dfdtd-open/tem3dfdtd/lib/time-serious.f90
2023-12-19 10:49:54 +08:00

69 行
3.1 KiB
Fortran

!Copyright (c) 2013 by tdem.org under guide of Xiu Li(lixiu@chd.edu.cn)
!written by Huaifeng Sun(sunhuaifeng@gmail.com) and Xushan Lu(luxushan@gmail.com)
!Code distribution @ tdem.org or sunhuaifeng.com
SUBROUTINE TIME_SERIOUS
USE CONSTANTPARAMETERS
USE ELECTROMAGNETIC_VARIABLES
USE RES_MODEL_PARAMETER
USE TIME_PARAMETER
USE OMP_LIB
!本子程序将计算初始时间和时间序列
IMPLICIT NONE
INTEGER NSTOP_TEMP,i,j,k
TIME_MAX=100*GridSize*SQRT(EPS0*MU0/3.0) !Time_max can be set to larger value if the value of GridSize if less than 1m, otherwise you will spend a much longer time in calculation.
!GENERATE THE TOTAL TIME WHEN THE TIME STEP CHANGES FROM RAMPSTEP TO WAVESTEP(TIME_MAX)
TIME_RAMP2WAVE_SUM=RAMPSTEP
TIME_RAMP2WAVE_TEMP=RAMPSTEP
DO WHILE(TIME_RAMP2WAVE_TEMP .LT. TIME_MAX)
TIME_RAMP2WAVE_SUM=TIME_RAMP2WAVE_SUM+TIME_RAMP2WAVE_TEMP
TIME_RAMP2WAVE_TEMP=TIME_RAMP2WAVE_TEMP*1.0005
ENDDO
if(time_ramp2wave_sum.ge.wave/2.0d0)then
time_ramp2wave_sum=wave/2.0d0
end if
SELECT CASE (SOURCE_TYPE)
CASE('TIXING_RAMP')
CALL TIXING_SOURCE
CASE('TIXING_UPCOS') !Currently, this is the only possibility in input.dat file, so that you are surpposed to only take a look at this subroutine among the four.
CALL TIXING_SOURCE_UPCOS
CASE('HALF_SIN')
CALL SIN_SOURCE
CASE('TRIANGLE')
CALL TRIANGLE_SOURCE
CASE DEFAULT
WRITE(*,*)'SOURCE TYPE INPUT ERROR'
ENDSELECT
MAX_OFF_TIME=MAX_OFF_TIME*1.0D-3 !The unit of Max_off_time in input.dat should be ms, and here the value is transformed into s
DO I=1,NSTOP
IF(CTIME(I) .LE. MAX_OFF_TIME)THEN
NSTOP_TEMP=I+1
ENDIF
ENDDO !This subroutine computes the value of Nstop which satisfies the requirement of Max_off_time
IF(NSTOP_TEMP .LT. NSTOP)THEN
NSTOP=NSTOP_TEMP !Change the value of Nstop to a smaller value according to the above computation
WRITE(10005,*)'NSTOP改变为',NSTOP
OPEN(9,FILE='CTIME_TIXING_UPCOS.DAT',STATUS='UNKNOWN')
DO I=1,NSTOP
WRITE(9,'(3E24.16)')CTIME(I),DELT(I),SOURCE(I)
ENDDO
CLOSE(9)
WRITE(10005,*)'采用升余弦函数和降余弦函数处理的梯形波发射波形时间序列已经写入文件CTIME_TIXING_UPCOS.DAT'
ELSEIF(NSTOP_TEMP .EQ. NSTOP)THEN
NSTOP=NSTOP_TEMP
WRITE(10005,*)'NSTOP没有改变,可能无法满足最大最大延时设置,请重新设置NSTOP.'
OPEN(9,FILE='CTIME_TIXING_UPCOS.DAT',STATUS='UNKNOWN')
DO I=1,NSTOP
WRITE(9,'(3E24.16)')CTIME(I),DELT(I),SOURCE(I)
ENDDO
CLOSE(9)
WRITE(10005,*)'采用升余弦函数和降余弦函数处理的梯形波发射波形时间序列已经写入文件CTIME_TIXING_UPCOS.DAT'
ELSE
WRITE(10005,*)'The number of iteration steps exceeds the range given in the input.dat, please change it. now the Nstop value is determined by Max_off_time.'
print*,'The number of iteration steps exceeds the range given in the input.dat, please change it. now the Nstop value is determined by Max_off_time.'
print*,'I give you a pause here, you should decide to continue or to quit'
pause
Nstop=Nstop_temp
ENDIF
RETURN
ENDSUBROUTINE TIME_SERIOUS