Changeset 8a65cb0 in flexpart.git for src/readreleases.f90


Ignore:
Timestamp:
Mar 2, 2015, 3:11:55 PM (9 years ago)
Author:
Espen Sollum ATMOS <espen@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
1d207bb
Parents:
60403cd
Message:

Added code, makefile for dev branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readreleases.f90

    rb7ae015 r8a65cb0  
    6363  ! num_min_discrete    if less, release cannot be randomized and happens at   *
    6464  !                     time mid-point of release interval                     *
     65  ! lroot               true if serial version, or if MPI and root process     *
    6566  !                                                                            *
    6667  !*****************************************************************************
     
    125126
    126127  ! prepare namelist output if requested
    127   if (nmlout.eqv..true.) then
    128     !open(unitreleasesout,file=path(2)(1:length(2))//'RELEASES.namelist',access='append',status='new',err=1000)
    129     open(unitreleasesout,file=path(2)(1:length(2))//'RELEASES.namelist',err=1000)
     128  if (nmlout.and.lroot) then
     129    open(unitreleasesout,file=path(2)(1:length(2))//'RELEASES.namelist',access='append',status='replace',err=1000)
    130130  endif
    131131
     
    259259  if (stat.ne.0) write(*,*)'ERROR: could not allocate xmasssave'
    260260
    261   if (verbosity.gt.0) then
    262     write (*,*) 'readreleases> Releasepoints : ', numpoint
    263   endif
     261  if (lroot) write (*,*) 'Releasepoints : ', numpoint
    264262
    265263  do i=1,numpoint
     
    291289
    292290  ! namelist output
    293   if (nmlout.eqv..true.) then
     291  if (nmlout.and.lroot) then
    294292    write(unitreleasesout,nml=releases_ctrl)
    295293  endif
    296294
    297295  do i=1,nspec
    298     if (verbosity.gt.0) then
    299       print*, 'readreleases> call readspecies', i
    300     endif
    301  
    302296    if (readerror.ne.0) then
    303297      read(unitreleases,*,err=998) specnum_rel(i)
     
    356350        vsetaver(i)=vsetaver(i)-vset(i,j)*fract(i,j)
    357351      end do
    358       write(*,*) 'Average settling velocity: ',i,vsetaver(i)
     352      if (lroot) write(*,*) 'Average settling velocity: ',i,vsetaver(i)
    359353    endif
    360354
     
    364358    dryvel(i)=dryvel(i)*0.01         ! conversion to m/s
    365359
    366     ! Check if wet deposition or OH reaction shall be calculated
    367     !***********************************************************
    368     if (weta(i).gt.0.)  then
     360  ! Check if wet deposition or OH reaction shall be calculated
     361  !***********************************************************
     362! NIK 15.02.2015, with new wet dep scheme either A or B parameters can be assigned a positive value which switches on wet dep
     363    if (weta(i).gt.0. .or. wetb(i).gt.0.)  then
    369364      WETDEP=.true.
    370       write (*,*) 'Below-cloud scavenging: ON'
    371       if (verbosity.gt.0) then
    372       write (*,*) 'Below-cloud scavenging coefficients: ',weta(i),i
    373       endif
     365      if (lroot) then
     366        write (*,*) 'Below-cloud scavenging: ON'
     367      write (*,*) 'Below-cloud scavenging coefficients: ',weta(i),i
     368      end if
    374369    else
    375       if (verbosity.gt.0) then
    376       write (*,*) 'Below-cloud scavenging: OFF'
    377       endif
     370      if (lroot) write (*,*) 'Below-cloud scavenging: OFF'
    378371    endif
    379372   
    380     ! NIK 31.01.2013 + 10.12.2013
    381     if (weta_in(i).gt.0.)  then
     373! NIK 31.01.2013 + 10.12.2013 + 15.02.2015
     374    if (weta_in(i).gt.0. .or. wetb_in(i).gt.0.)  then
    382375      WETDEP=.true.
    383       write (*,*) 'In-cloud scavenging: ON'
    384       if (verbosity.gt.0) then
    385       write (*,*) 'In-cloud scavenging coefficients: ',weta_in(i),wetb_in(i), wetc_in(i), wetd_in(i),i
    386       endif 
    387   else
    388       if (verbosity.gt.0) then
    389       write (*,*) 'In-cloud scavenging: OFF'
    390       endif
    391     endif
    392 
    393     if (ohreact(i).gt.0) then
     376      if (lroot) then
     377        write (*,*) 'In-cloud scavenging: ON'
     378        write (*,*) 'In-cloud scavenging coefficients: ',&
     379           &weta_in(i),wetb_in(i),i !,wetc_in(i), wetd_in(i),i
     380      end if
     381    else
     382      if (lroot) write (*,*) 'In-cloud scavenging: OFF'
     383    endif
     384
     385    if (ohcconst(i).gt.0.) then
    394386      OHREA=.true.
    395       write (*,*) 'OHreaction: ON (',ohreact(i),i,')'
     387      write (*,*) 'OHreaction switched on: ',ohcconst(i),i
    396388    endif
    397389
     
    439431
    440432    ! namelist output
    441     if (nmlout.eqv..true.) then
     433    if (nmlout.and.lroot) then
    442434      write(unitreleasesout,nml=release)
    443435    endif
     
    482474
    483475    ! namelist output
    484     if (nmlout.eqv..true.) then
     476    if (nmlout.and.lroot) then
    485477      idate1=id1
    486478      itime1=it1
     
    509501  endif ! if namelist format
    510502
    511 
    512   if (verbosity.gt.1 .and. numpoint.eq.1) then ! verbosity 2 or larger
    513     write(*,*) 'numpoint=', numpoint
    514     print*,  id1,it1
    515     print*,  id2,it2
    516     print*,  xpoint1(numpoint)
    517     print*,  ypoint1(numpoint)
    518     print*,  xpoint2(numpoint)
    519     print*,  ypoint2(numpoint)
    520     print*,  'kindz=' , kindz(numpoint)
    521     print*,  zpoint1(numpoint)
    522     print*,  zpoint2(numpoint)
    523     print*,  npart(numpoint)
    524     do i=1,nspec
    525       !mass(i)=
    526       print*, 'xmass=', xmass(numpoint,i)
    527     end do
    528     print*, compoint(numpoint)
    529   endif
    530 
    531 
    532503  ! If a release point contains no particles, stop and issue error message
    533504  !***********************************************************************
     
    572543        write(*,*) 'after simulation stops.'
    573544        write(*,*) 'Make files COMMAND and RELEASES consistent.'
    574         write(*,*) jul1, ' < ' , bdate
    575         write(*,*) ' .or. '
    576         write(*,*) jul2 , ' > ', edate
    577        
    578545        stop
    579546      endif
     
    603570  endif
    604571
    605   if (verbosity.gt.1 .and. numpoint.eq.1) then ! verbosity 2 or larger
    606     print*, 'ireleasestart(',numpoint,')', ireleasestart(numpoint)
    607     print*, 'ireleaseend(',numpoint,')', ireleaseend(numpoint)
    608   endif
    609 
    610572  ! Determine the release rate (particles per second) and total number
    611573  ! of particles released during the simulation
     
    623585250   close(unitreleases)
    624586
    625   if (nmlout.eqv..true.) then
     587  if (nmlout.and.lroot) then
    626588    close(unitreleasesout)
    627589  endif
    628590
    629   write (*,*) 'Particles allocated (maxpart)  : ',maxpart
    630   write (*,*) 'Particles released (numpartmax): ',numpartmax
     591  if (lroot) write (*,*) 'Particles allocated (maxpart)  : ',maxpart
     592  if (lroot) write (*,*) 'Particles released (numpartmax): ',numpartmax
    631593  numpoint=numpoint-1
    632594
     
    643605  if (releaserate.gt. &
    644606       0.99*real(maxpart)/real(lage(nageclass))) then
    645     if (numpartmax.gt.maxpart) then
     607    if (numpartmax.gt.maxpart.and.lroot) then
    646608  write(*,*) '#####################################################'
    647609  write(*,*) '#### FLEXPART MODEL SUBROUTINE READRELEASES:     ####'
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG