Changes in src/getfields.f90 [2eefa58:6ecb30a] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/getfields.f90

    r2eefa58 r6ecb30a  
    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
    9389
    9490  integer :: indmin = 1
     
    15715340  indmin=indj
    158154
    159     if (WETBKDEP) then
    160       call writeprecip(itime,memind(1))
    161     endif
     155   if (WETBKDEP) then
     156        call writeprecip(itime,memind(1))
     157   endif
    162158
    163159  else
     
    20820460  indmin=indj
    209205
    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
     206   if (WETBKDEP) then
     207        call writeprecip(itime,memind(1))
     208   endif
     209
     210  endif
    238211
    239212  lwindinterv=abs(memtime(2)-memtime(1))
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG