Changeset 1070b4c in flexpart.git for src/concoutput_nest_mpi.f90


Ignore:
Timestamp:
Aug 27, 2020, 9:51:56 PM (4 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
GFS_025, dev
Children:
b0ecb61
Parents:
8c0ae9b (diff), a803521 (diff)
Note: this is a merge changeset, the changes displayed below correspond to the merge itself.
Use the (diff) links above to see all the changes relative to each parent.
Message:

Merge branch 'espen' into dev

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/concoutput_nest_mpi.f90

    r92fab65 ra803521  
    3939  !                                                                            *
    4040  !*****************************************************************************
    41 
    4241
    4342  use unc_mod
     
    5655  real :: sp_fact
    5756  real :: outnum,densityoutrecept(maxreceptor),xl,yl
     57! RLT
     58  real :: densitydryrecept(maxreceptor)
     59  real :: factor_dryrecept(maxreceptor)
    5860
    5961  !real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
     
    8284  character :: adate*8,atime*6
    8385  character(len=3) :: anspec
     86  logical :: lexist
    8487  integer :: mind
    8588! mind        eso:added to ensure identical results between 2&3-fields versions
     
    158161        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
    159162             rho(iix,jjy,kzz-1,mind)*dz2)/dz
     163! RLT
     164        densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
     165             rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz
    160166      end do
    161167    end do
     
    169175    !densityoutrecept(i)=rho(iix,jjy,1,2)
    170176    densityoutrecept(i)=rho(iix,jjy,1,mind)
     177! RLT
     178    densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
    171179  end do
    172180
     181! RLT
     182! conversion factor for output relative to dry air
     183  factor_drygrid=densityoutgrid/densitydrygrid
     184  factor_dryrecept=densityoutrecept/densitydryrecept
    173185
    174186  ! Output is different for forward and backward simulations
     
    193205
    194206  write(anspec,'(i3.3)') ks
     207 
     208  if (DRYBKDEP.or.WETBKDEP) then !scavdep output
     209      if (DRYBKDEP) &
     210      open(unitoutgrid,file=path(2)(1:length(2))//'grid_drydep_nest_'//adate// &
     211           atime//'_'//anspec,form='unformatted')
     212      if (WETBKDEP) &
     213      open(unitoutgrid,file=path(2)(1:length(2))//'grid_wetdep_nest_'//adate// &
     214           atime//'_'//anspec,form='unformatted')
     215      write(unitoutgrid) itime
     216  else
    195217  if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
    196218    if (ldirect.eq.1) then
     
    205227     write(unitoutgrid) itime
    206228   endif
     229  endif
    207230
    208231  if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
     
    535558  end do
    536559
    537 
    538 
    539   ! Reinitialization of grid
    540   !*************************
    541 
    542   do ks=1,nspec
    543     do kp=1,maxpointspec_act
    544       do i=1,numreceptor
    545         creceptor(i,ks)=0.
    546       end do
    547       do jy=0,numygridn-1
    548         do ix=0,numxgridn-1
    549           do l=1,nclassunc
    550             do nage=1,nageclass
    551               do kz=1,numzgrid
    552                 griduncn(ix,jy,kz,ks,kp,l,nage)=0.
    553               end do
    554             end do
    555           end do
    556         end do
     560! RLT Aug 2017
     561! Write out conversion factor for dry air
     562  inquire(file=path(2)(1:length(2))//'factor_drygrid_nest',exist=lexist)
     563  if (lexist) then
     564    ! open and append
     565    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
     566            status='old',action='write',access='append')
     567  else
     568    ! create new
     569    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
     570            status='new',action='write')
     571  endif
     572  sp_count_i=0
     573  sp_count_r=0
     574  sp_fact=-1.
     575  sp_zer=.true.
     576  do kz=1,numzgrid
     577    do jy=0,numygridn-1
     578      do ix=0,numxgridn-1
     579        if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
     580          if (sp_zer.eqv..true.) then ! first value not equal to one
     581            sp_count_i=sp_count_i+1
     582            sparse_dump_i(sp_count_i)= &
     583                  ix+jy*numxgridn+kz*numxgridn*numygridn
     584            sp_zer=.false.
     585            sp_fact=sp_fact*(-1.)
     586          endif
     587          sp_count_r=sp_count_r+1
     588          sparse_dump_r(sp_count_r)= &
     589               sp_fact*factor_drygrid(ix,jy,kz)
     590        else ! factor is one
     591          sp_zer=.true.
     592        endif
    557593      end do
    558594    end do
    559595  end do
    560 
     596  write(unitoutfactor) sp_count_i
     597  write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
     598  write(unitoutfactor) sp_count_r
     599  write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
     600  close(unitoutfactor)
     601
     602  ! Reinitialization of grid
     603  !*************************
     604
     605  ! do ks=1,nspec
     606  !   do kp=1,maxpointspec_act
     607  !     do i=1,numreceptor
     608  !       creceptor(i,ks)=0.
     609  !     end do
     610  !     do jy=0,numygridn-1
     611  !       do ix=0,numxgridn-1
     612  !         do l=1,nclassunc
     613  !           do nage=1,nageclass
     614  !             do kz=1,numzgrid
     615  !               griduncn(ix,jy,kz,ks,kp,l,nage)=0.
     616  !             end do
     617  !           end do
     618  !         end do
     619  !       end do
     620  !     end do
     621  !   end do
     622  ! end do
     623  creceptor(:,:)=0.
     624  griduncn(:,:,:,:,:,:,:)=0.
     625 
    561626  if (mp_measure_time) call mpif_mtime('iotime',1)
    562627  ! if (mp_measure_time) then
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG