Changeset 2eefa58 in flexpart.git for src/getfields.f90


Ignore:
Timestamp:
May 27, 2019, 3:28:44 PM (5 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug
Children:
6741557
Parents:
f963113
Message:

Added Ronas changes for inversion output

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/getfields.f90

    r6ecb30a r2eefa58  
    8787  real :: pvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,maxnests)
    8888  real :: wwhn(0:nxmaxn-1,0:nymaxn-1,nwzmax,maxnests)
     89! RLT added partial pressure water vapor
     90  real :: pwater(0:nxmax-1,0:nymax-1,nzmax,numwfmem)
     91  integer :: kz, ix
     92  character(len=100) :: rowfmt
    8993
    9094  integer :: indmin = 1
     
    15315740  indmin=indj
    154158
    155    if (WETBKDEP) then
    156         call writeprecip(itime,memind(1))
    157    endif
     159    if (WETBKDEP) then
     160      call writeprecip(itime,memind(1))
     161    endif
    158162
    159163  else
     
    20420860  indmin=indj
    205209
    206    if (WETBKDEP) then
    207         call writeprecip(itime,memind(1))
    208    endif
    209 
    210   endif
     210    if (WETBKDEP) then
     211      call writeprecip(itime,memind(1))
     212    endif
     213
     214  end if
     215
     216  ! RLT calculate dry air density
     217  pwater=qv*prs/((r_air/r_water)*(1.-qv)+qv)
     218  rho_dry=(prs-pwater)/(r_air*tt)
     219
     220  ! test density
     221!  write(rowfmt,'(A,I6,A)') '(',nymax,'(E11.4,1X))'
     222!  if(itime.eq.0) then
     223!    open(500,file=path(2)(1:length(2))//'rho_dry.txt',status='replace',action='write')
     224!    do kz=1,nzmax
     225!      do ix=1,nxmax
     226!        write(500,fmt=rowfmt) rho_dry(ix,:,kz,1)
     227!      end do
     228!    end do
     229!    close(500)
     230!    open(500,file=path(2)(1:length(2))//'rho.txt',status='replace',action='write')
     231!    do kz=1,nzmax
     232!      do ix=1,nxmax
     233!        write(500,fmt=rowfmt) rho(ix,:,kz,1)
     234!      end do
     235!    end do
     236!    close(500)
     237!  endif
    211238
    212239  lwindinterv=abs(memtime(2)-memtime(1))
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG