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

113 行
4.7 KiB
Fortran

此文件含有模棱两可的 Unicode 字符

此文件含有可能会与其他字符混淆的 Unicode 字符。 如果您是想特意这样的,可以安全地忽略该警告。 使用 Escape 按钮显示他们。

!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 GETDATA
USE CONSTANTPARAMETERS
!this line is added by Huaifeng Sun to get the dir 2016-10-30
USE IFPORT
IMPLICIT NONE
LOGICAL ALIVE
INTEGER TEMP_II,III
!this following lines 10-21 are added by Huaifeng Sun to get the dir 2016-10-30
CHARACTER(255) dir
CHARACTER(255) InputFileName
INTEGER(4) length
length = GETDRIVEDIRQQ(dir)
IF (length .GT. 0) THEN
!WRITE (*,*) 'Current directory is: '
!WRITE (*,*) dir
InputFileName=trim(dir)//'//example//input.dat'
ELSE
WRITE (*,*) 'Failed to get current directory'
pause
END IF
!the following inputfilename type are modified by HFSun 2016-10-30
!INQUIRE(FILE='input.dat', EXIST=ALIVE)
INQUIRE(FILE=InputFileName, EXIST=ALIVE)
IF(.NOT. ALIVE) THEN
WRITE(10005,*) "input.dat DOES NOT EXIST."
STOP
ELSE
!OPEN(234,FILE='example/input.dat',STATUS='OLD')
OPEN(234,FILE=InputFileName,STATUS='OLD')
READ(234,'(a4)')CAL_TYPE !This is the calculation type, possible values are shown below.
IF(CAL_TYPE=='TUNNEL' .OR. CAL_TYPE=='tunnel')THEN
WRITE(10005,*)'隧道模型计算开关设置正确!'
ELSEIF(CAL_TYPE=='SEMI' .OR. CAL_TYPE=='semi')THEN
WRITE(10005,*)'SEMI-AIRBORNE计算开关设置正确'
ELSEIF(CAL_TYPE=='GROUND' .OR. CAL_TYPE=='ground')THEN
WRITE(10005,*)'地面模型计算开关设置正确!'
ELSE
WRITE(10005,*)'模型计算开关设置不正确,请确定采用地面模型还是隧道模型!'
STOP
ENDIF
READ(234,*)SourceLength
!The length of source, unit of which is meter, and you are supposed to set SourceLengh/GridSize as an odd number for the consideration of there will exist a central point within the source loop.
READ(234,*)NX,NY,NZ !The value of Nx, Ny and Nz varies from model to model.
READ(234,*)GridSize !Most commonly used value is 10m
READ(234,*)BACKGROUND_CONDUCTIVITY !Most commonly used value is 1e-2
READ(234,*)TEMP_II !It depends on your model, and it should be set to 0 if you are doing homogeneous model calculation.
ALLOCATE(TAR_X1(TEMP_II))
ALLOCATE(TAR_X2(TEMP_II))
ALLOCATE(TAR_Y1(TEMP_II))
ALLOCATE(TAR_Y2(TEMP_II))
ALLOCATE(TAR_Z1(TEMP_II))
ALLOCATE(TAR_Z2(TEMP_II))
ALLOCATE(TAR_CONDUCTIVITY(TEMP_II))
DO III=1,TEMP_II
READ(234,*)TAR_X1(III),TAR_X2(III)
READ(234,*)TAR_Y1(III),TAR_Y2(III)
READ(234,*)TAR_Z1(III),TAR_Z2(III)
READ(234,*)TAR_CONDUCTIVITY(III)
ENDDO
READ(234,*)NSTOP !The maximum iteration number.
READ(234,*)MAX_OFF_TIME !The maximum computation time, unit of which is ms
READ(234,*)RAISETIME,RAISESTEP !Most commonly used value is: Raisetime=1e-6, Raisestep=1e-9
READ(234,*)WAVE !,WAVESTEP
READ(234,*)RAMP,RAMPSTEP !Most commonly used value is: Ramp=1e-6, Rampstep=1e-9
READ(234,*)TIMESTEP !Most commonly used value is 1e-7
READ(234,*)AMP !It denotes the value of amplitude of transmitting source.
read(234,*)NumRecHeights !It is determined by your recording configuration
allocate(FlightHeight(NumRecHeights),GridNumHeight(NumRecHeights),Nzs_Air(NumRecHeights))
READ(234,*)(FlightHeight(iii),iii=1,NumRecHeights)
READ(234,'(a12)')SOURCE_TYPE !Currently the only possible value of Source_type is 'TIXING_UPCOS'
read(234,'(a2)')RecFlag !Possible values are 'HE' and 'Hz'
READ(234,*)NumRecLines
read(234,*)RecPointMin,RecPointMax
NumRecPoints=RecPointMax-RecPointMin+1
IF(NumRecLines .EQ. 0)THEN
WRITE(10005,*)'没有设置额外的接收点,程序继续运行!'
ELSEIF(NumRecLines .GT. 0)THEN
ALLOCATE(RecLine(NumRecLines),RecPoint(NumRecPoints))
ELSE
WRITE(10005,*)'额外接收点设置错误,请参阅输入数据文件格式说明,程序异常终止!'
STOP
ENDIF
CLOSE(234)
ENDIF
do iii=1,NumRecHeights
GridNumHeight(iii)=FlightHeight(iii)/GridSize
end do
do iii=1,NumRecPoints,1
RecPoint(iii)=iii+RecPointMin-1
end do
!计算CONSTANTPARAMETERS中的其他常数
NXB=NX+1
NYB=NY+1
NZB=NZ+1
NXS=NX/2+1
NYS=NY/2+1
NZS=NZ/2
do iii=1,NumRecHeights
NZS_AIR(iii)=NZS-GridNumHeight(iii)
end do
do iii=1,NumRecLines,1
RecLine(iii)=nxs-(NumRecLines-1)/2+iii-1
end do
!将电流转换成电流密度
AMP=AMP/(GridSize*GridSize)
SourceGridNum=int(SourceLength/GridSize)
ALLOCATE(SOURCE(NSTOP))
ENDSUBROUTINE GETDATA