Subroutine get_time USE Numeric_Kinds_Module USE CommonInfo_Module USE Time_Module Implicit None !==================================================================== ! This routine obtains the propagation time parameters ! ! Variables: (atomic units) ! deltat = time step interval (grid spacing) ! tdelay = time when analysis of final wave packet begin ! tdelaystep = time step corresponding to tdelay ! tmax = total propagation time (begins at t=0) ! tstep = number of time steps (not counting t=0) !====================================================================== ! I N T E R N A L S Integer :: istat Real(dp) :: tmax !===================================================================== ! N A M E L I S T S Namelist /time/ tmax,tstep,tdelay !===================================================================== ! Read input from NAMELIST OPEN(UNIT=Input_Unit,FILE=Trim(inputfile1),IOSTAT=istat,STATUS='old',ACTION='read') IF (istat.ne.0) STOP 'OPEN failed - gettime' READ(Input_Unit,time) CLOSE(UNIT=Input_Unit,IOSTAT=istat,STATUS='keep') IF (istat.ne.0) STOP 'CLOSE failed - gettime' !==================================================================== ! Check that input values are within valid ranges If (tmax.lt.0.0d0) Then Print*,'Invalid tmax provided : cannot be less than 0' Print*,'tmax = ',tmax Print*,'Check NAMELIST time' Stop 'gettime' End If If (tstep.lt.1) Then Print*,'Invalid tstep provided : must be >= 1' Print*,'tstep = ',tstep Print*,'Check NAMELIST time' Stop 'gettime' End If If (tdelay.ge.tmax) Then Print*,'Invalid delay provided: must be < tmax' Print*,'tdelay = ',tdelay Print*,'tmax = ',tmax Stop 'gettime' End If If (tdelay.eq.0.d0.and.MOD(tstep,2).eq.0) Then Print*,'TSTEP must be odd : TSTEP = ',tstep Print*,'Correcting error by adding 1 point' tstep=tstep+1 End If !================================================================== ! Calculate time grid spacing deltat=tmax/tstep !=================================================================== ! Determine which time step corresponds to the delay time ! Check that there are an odd number of points to be integrated ! If even, subtract a point to make it odd. IF (tdelay.gt.0.d0) THEN tdelaystep=CEILING(tdelay/deltat) ELSE tdelaystep=1 ENDIF If (tdelay.ne.0.d0.and.MOD(tstep-tdelaystep+1,2).eq.0) Then tdelaystep=tdelaystep-1 End If !==================================================================== ! Write to output log Write(Out_Unit,21) 'Time Info:','au' Write(Out_Unit,22) 'tmax ',tmax, 'tstep ',tstep Write(Out_Unit,22) 'tdelay',tdelay,'tdelaystep',tdelaystep Write(Out_Unit,23) 'deltat',deltat Write(*,24) 'tmax ',tmax Write(*,25) 'tstep ',tstep Write(*,24) 'tdelay',tdelay 21 FORMAT(/1X,a,T22,a,/1X,50('-')) 22 FORMAT(1X,a,10('.'),F9.1,5X,a,10('.'),I5) 23 FORMAT(1X,a,10('.'),F8.3) 24 FORMAT(1X,a,9('.'),F8.1,' au') 25 FORMAT(1X,a,9('.'),I5) End subroutine get_time