Ignore:
Timestamp:
Dec 23, 2013, 6:23:38 PM (10 years ago)
Author:
igpis
Message:

move version 9.1.8 form branches to trunk. Contributions from HSO, saeck, pesei, NIK, RT, XKF, IP and others

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/timemanager.f90

    r4 r20  
    128128  !**********************************************************************
    129129
    130   !write (*,*) 'starting simulation'
     130
     131  if (verbosity.gt.0) then
     132    write (*,*) 'timemanager> starting simulation'
     133    if (verbosity.gt.1) then
     134      CALL SYSTEM_CLOCK(count_clock)
     135      WRITE(*,*) 'timemanager> SYSTEM CLOCK',(count_clock - count_clock0)/real(count_rate)
     136    endif     
     137  endif
     138
    131139  do itime=0,ideltas,lsynctime
    132140
     
    142150  !********************************************************************
    143151
    144     if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) &
     152    if (WETDEP .and. itime .ne. 0 .and. numpart .gt. 0) then
     153        if (verbosity.gt.0) then
     154           write (*,*) 'timemanager> call wetdepo'
     155        endif     
    145156         call wetdepo(itime,lsynctime,loutnext)
     157    endif
    146158
    147159    if (OHREA .and. itime .ne. 0 .and. numpart .gt. 0) &
     
    156168  !*************************************
    157169
    158       if ((ldirect.eq.-1).and.(lconvection.eq.1).and.(itime.lt.0)) &
    159            call convmix(itime)
     170   if ((ldirect.eq.-1).and.(lconvection.eq.1).and.(itime.lt.0)) then
     171        if (verbosity.gt.0) then
     172           write (*,*) 'timemanager> call convmix -- backward'
     173        endif         
     174      call convmix(itime)
     175        if (verbosity.gt.1) then
     176          !CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     177          CALL SYSTEM_CLOCK(count_clock)
     178          WRITE(*,*) 'timemanager> SYSTEM CLOCK',(count_clock - count_clock0)/real(count_rate)
     179        endif
     180   endif
    160181
    161182  ! Get necessary wind fields if not available
    162183  !*******************************************
    163 
     184    if (verbosity.gt.0) then
     185           write (*,*) 'timemanager> call getfields'
     186    endif
    164187    call getfields(itime,nstop1)
     188        if (verbosity.gt.1) then
     189          CALL SYSTEM_CLOCK(count_clock)
     190          WRITE(*,*) 'timemanager> SYSTEM CLOCK',(count_clock - count_clock0)/real(count_rate)
     191        endif
    165192    if (nstop1.gt.1) stop 'NO METEO FIELDS AVAILABLE'
     193
    166194  ! Release particles
    167195  !******************
    168196
     197    if (verbosity.gt.0) then
     198           write (*,*) 'timemanager>  Release particles'
     199    endif
     200
    169201    if (mdomainfill.ge.1) then
    170202      if (itime.eq.0) then
     203        if (verbosity.gt.0) then
     204          write (*,*) 'timemanager>  call init_domainfill'
     205        endif       
    171206        call init_domainfill
    172207      else
     208        if (verbosity.gt.0) then
     209          write (*,*) 'timemanager>  call boundcond_domainfill'
     210        endif   
    173211        call boundcond_domainfill(itime,loutend)
    174212      endif
    175213    else
     214      if (verbosity.gt.0) then
     215        print*,'call releaseparticles' 
     216      endif
    176217      call releaseparticles(itime)
     218      if (verbosity.gt.1) then
     219        CALL SYSTEM_CLOCK(count_clock)
     220        WRITE(*,*) 'timemanager> SYSTEM CLOCK',(count_clock - count_clock0)/real(count_rate)
     221      endif
    177222    endif
    178223
     
    182227  !**************************************************************
    183228
    184       if ((ldirect.eq.1).and.(lconvection.eq.1)) &
    185            call convmix(itime)
    186 
     229   if ((ldirect.eq.1).and.(lconvection.eq.1)) then
     230     if (verbosity.gt.0) then
     231       write (*,*) 'timemanager> call convmix -- forward'
     232     endif   
     233     call convmix(itime)
     234   endif
    187235
    188236  ! If middle of averaging period of output fields is reached, accumulated
     
    299347      if ((itime.eq.loutend).and.(outnum.gt.0.)) then
    300348        if ((iout.le.3.).or.(iout.eq.5)) then
     349          if (surf_only.ne.1) then
    301350          call concoutput(itime,outnum,gridtotalunc, &
    302351               wetgridtotalunc,drygridtotalunc)
    303           if (nested_output.eq.1) call concoutput_nest(itime,outnum)
     352          else 
     353  if (verbosity.eq.1) then
     354     print*,'call concoutput_surf '
     355     CALL SYSTEM_CLOCK(count_clock)
     356     WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
     357  endif
     358          call concoutput_surf(itime,outnum,gridtotalunc, &
     359               wetgridtotalunc,drygridtotalunc)
     360  if (verbosity.eq.1) then
     361     print*,'called concoutput_surf '
     362     CALL SYSTEM_CLOCK(count_clock)
     363     WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
     364  endif
     365          endif
     366
     367          if ((nested_output.eq.1).and.(surf_only.ne.1)) call concoutput_nest(itime,outnum)
     368          if ((nested_output.eq.1).and.(surf_only.eq.1)) call concoutput_surf_nest(itime,outnum)
    304369          outnum=0.
    305370        endif
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG