文件
tem3dfdtd-open/tem3dfdtd/module/constant-parameters.f90
2023-12-19 10:49:54 +08:00

70 行
6.6 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
MODULE CONSTANTPARAMETERS
INTEGER NX,NY,NZ
! Nx,Ny,Nz is the number of grid in x, y and z directions respectively;
REAL*8 SourceLength ! The length of source
INTEGER SourceGridNum ! The number of grids in source area (x direction)
INTEGER NXB,NYB,NZB !Nxb=Nx+1, Nyb=Ny+1, Nzb=Nz+1
INTEGER NXS,NYS,NZS !This parameter mostly represents the middle grid's number, Nxs=Nx/2 or Nxs=Nxb/2, Nys=Ny/2 or Nys=Nyb/2, Nzs=Nz/2
REAL*8 BACKGROUND_CONDUCTIVITY,TUNNEL_LENGTH !The conductivity of background; the length of tunnel
CHARACTER*8 CAL_TYPE !The type of Calculation, in this case, it is semi which represents semi_airborne
REAL*8 SIGMA_MIN !The minimum value of sigma
REAL(KIND=8) TIME_MAX !The maximum value of iteration time step
INTEGER NSTOP !The number of total iteration steps
REAL*8 MAX_OFF_TIME !The maximum calculation time, in ms
INTEGER LOOP !Iteration step
REAL*8, PARAMETER:: CC=2.99792458D8 !The velocity of light
REAL*8, PARAMETER:: PI=3.141592653589793238462643383276D0 !PI
REAL*8, PARAMETER:: SCALE_PAR=1.05d0 !The ratio of adjacent grid's length
REAL*8, PARAMETER:: MAX_RATIO=50.0D0 !The maximum value of scale_par
REAL*8 GridSize !The size of a single grid, it represents the size of uniform grid.
REAL(KIND=8), DIMENSION(:),ALLOCATABLE:: CDELX !The array of all grid size in x direction, designed for the recording of ununiform meshing.
REAL(KIND=8), DIMENSION(:),ALLOCATABLE:: CDELY !The array of all grid size in y direction, designed for the recording of ununiform meshing.
REAL(KIND=8), DIMENSION(:),ALLOCATABLE:: CDELZ !The array of all grid size in z direction, designed for the recording of ununiform meshing.
integer::mstop(100000),mstart(100000),num_fra_com !
! The entire computation process is cut into hundreds of computing fractions. At the begining of each computation fraction, data is sent to GPU--
! --device, then the computation of this section starts in device, and the data is sent back to host when the comutation is finished in device-------
! --then we record electromagnetic field value to the hard disk. This procedure keeps running until the end of the entire computation.
! mstop is an array used to store the iteration steps in a section, the length is set to 10000 because we can not know the number of sections at--
! --the beginning of computation and it's value usually is smaller than 10000. Thus you should change it when there are more than 10000 computation--
! --fractions in some certain computing task.
! mstart is used to store the value of the beginning iteration step number of the entire iteration process. It has the same length with mstop.
! num_fra_com is the number of computation fractions of the entire computation process.
REAL*8, PARAMETER:: MU0=4.0*PI*1.0D-7 !The permeability of vaccum.
REAL*8, PARAMETER:: EPS0=1.0/(CC*CC*MU0) !The dielectric constant of vaccum.
CHARACTER(LEN=20) SOURCE_TYPE !The type of source, most commonly used one is tixing_upcos.
character*30,allocatable::RecHzFile(:,:),RecHEFile(:,:),RecFile(:,:) !The filename of Recording file, RecHzFile for the Hz mode which only record the value of Hz--
! --RecHEFile for HE mode which record every component of electromagnetic filed, RecFile is used in the filename distribution process.
character*30 PostProcessFile,SplitFile !The filename of PostProcessFileList.dat which stores the name of files need to be post processed.
character*2 RecFlag !Recording mode flag, possible values are: Hz and HE. It is specified in input.dat file.
integer,allocatable::RecHzFilePid(:,:),RecHEFilePid(:,:),RecFilePid(:,:) !File pid of RecHzFile, RecHeFile and RecFile.
integer PostProcessFilePid,SplitFilePid !The pid of PostProcessFileList.dat
Integer,Allocatable::is_ex_in_source(:,:)
!An array used in GetSourcePosition subroutine, the dimension of it is (Nx,Ny), in the source area, the value of this array is 1, else it is 0.
integer,allocatable::is_ey_in_source(:,:)
!The same as above.
integer RecPointMin,RecPointMax
integer,allocatable::RecLine(:),RecPoint(:)
!Two dimensional array which stores the value of grid number as (x,y) at which the value of EM filed need to be recorded.
integer,allocatable::FlightHeight(:) !This is the flight height of semi_airborne TEM or you can see it as the height of recording plane.
character*3,allocatable::Height(:) !This is used in the filename distribution process
INTEGER,allocatable:: GridNumHeight(:) !The number of grids between flight height plane and ground in z direction.
INTEGER,allocatable:: NZS_AIR(:) !The grid number in z direction of flight height plane
INTEGER NumRecLines,NumRecPoints,NumRecHeights !The number of total recording points and recording heights
REAL(KIND=8), DIMENSION(:), ALLOCATABLE:: SOURCE !Nstop length array which stores the value of amplitude of source.
INTEGER, DIMENSION(:), ALLOCATABLE:: TAR_X1 !The left grid number of anomalous body in x direction.
INTEGER, DIMENSION(:), ALLOCATABLE:: TAR_X2 !The right grid number of anomalous body in x direction.
INTEGER, DIMENSION(:), ALLOCATABLE:: TAR_Y1 !The left grid number of anomalous body in y direction.
INTEGER, DIMENSION(:), ALLOCATABLE:: TAR_Y2 !The right grid number of anomalous body in y direction.
INTEGER, DIMENSION(:), ALLOCATABLE:: TAR_Z1 !The left grid number of anomalous body in z direction.
INTEGER, DIMENSION(:), ALLOCATABLE:: TAR_Z2 !The right grid number of anomalous body in z direction.
REAL(KIND=8), DIMENSION(:), ALLOCATABLE:: TAR_CONDUCTIVITY !The conductivity array of anomalous body
real*8,allocatable::Eps_r(:),Cq(:) !Nstop length array of fictitious dielectric constant; cq is a middle variable used in the iteration part.
REAL*8 RAISETIME,RAMP,WAVE,AMP !The time of raising edge, ramp edge and duration in trapezoidal waveform, amp is the amplitude of source
REAL*8 RAISESTEP,WAVESTEP,RAMPSTEP,TIMESTEP
! The iteration time step in raise, duration, ramp and cutoff period.
real*8,allocatable::Coordix3(:),Coordiy3(:),Coordiz3(:) !This is used to store the coordination of each grid in x,y and z direction.
ENDMODULE CONSTANTPARAMETERS