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

85 行
4.0 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 SubOpenRecFiles(Flag)
use constantparameters
implicit none
integer ii,jj
character*2 Flag
character*30 string
do ii=1,NumRecHeights,1
write(Height(ii),'(i3.3)')FlightHeight(ii) !Convert real kind of variable to character so that it can be used in the filename distribution process
Height(ii)=trim(adjustl(Height(ii)))
end do
write(PostProcessFilePid,*) (NumRecLines)*(1+NumRecHeights),RecPointMin,RecPointMax !The number of total recording files
write(SplitFilePid,*)NumRecLines,NumRecPoints,NumRecHeights
do ii=1,NumRecLines,1
write(SplitFilePid,*)RecLine(ii)
end do
do ii=1,NumRecPoints,1
write(SplitFilePid,*)RecPoint(ii)
end do
do ii=1,NumRecHeights,1
write(SplitFilePid,*)FlightHeight(ii)
end do
close(SplitFilePid)
! -------------------------------------------------check for RecFilePid------------------------------------!
! if NumRecPoints is greater than 500, then the value of RecFilePid must be reset
! ----------------------------------------------------------------------------------------------------------------!
if(NumRecLines.ge.2000)then
print*,'NumRecLines is greater than 1000! Reset the value of RecFilePid in subroutine "OpenRecFiles"'
! This is because the distribution of file pid. You should modify the distribution part if your recording files number is greater than 1000.
stop
end if
! ----------------------------------------------------------------------------------------------------------------!
! -------------------------------------File Pid Distribution------------------------------------------------!
! Change it whenever you need to do so
! ----------------------------------------------------------------------------------------------------------------!
if(Flag.eq.'Hz')then
do jj=1,NumRecLines,1
RecFilePid(1,jj)=20000+jj !For the ground plane.
do ii=1,NumRecHeights,1
RecFilePid(ii+1,jj)=20000+ii*2000+jj !For the air plane, with multiple height
end do
enddo
RecHzFilePid=RecFilePid !Transfer the value of RecFilePid to RecHzFilePid if Flag.eq.'Hz'
elseif(Flag.eq.'HE')then
do jj=1,NumRecLines,1
RecFilePid(1,jj)=20000+(NumRecHeights+1)*2000+jj
do ii=1,NumRecHeights,1
RecFilePid(ii+1,jj)=20000+(NumRecHeights+1+ii)*2000+jj
end do
enddo
RecHEFilePid=RecFilePid
end if
! --------------------------------------end of File Pid Distribution----------------------------------------------!
!------------------------------------------File name Distribution-------------------------------------------------!
do jj=1,NumRecLines,1
write(string,'(I3.3)')RecLine(jj)
RecFile(1,jj)='Ground-Line'//'='//trim(adjustl(string))//'.dat'
write(PostProcessFilePid,*)RecFile(1,jj)
do ii=1,NumRecHeights,1
RecFile(ii+1,jj)='Air-Line='//trim(adjustl(string))//'-H='//Height(ii)//'.dat'
write(PostProcessFilePid,*)RecFile(ii+1,jj)
end do
end do
select case(Flag)
case('Hz')
RecHzFile=RecFile
case('HE')
RecHEFile=RecFile
end select
! ------------------------------------end of File name Distribution---------------------------------------------!
! --------------------------------------open file code-------------------------------------------!
! if the compiler reports the error: 'Too Many Open FIles!', you can come to tdem.org website and find the solutions.
! -----------------------------------------------------------------------------------------------------!
do ii=1,NumRecHeights+1,1
do jj=1,NumRecLines,1
open(RecFilePid(ii,jj),file=RecFile(ii,jj))
end do
end do
! -----------------------------------end of opening file----------------------------------------!
end subroutine SubOpenRecFiles