Changes in src/verttransform.f90 [6481010:341f4b7] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/verttransform.f90

    r6481010 r341f4b7  
    9191
    9292  logical :: init = .true.
    93   logical :: init_w = .false.
    94   logical :: init_r = .false.
    95 
    9693
    9794  !ZHG SEP 2014 tests 
     
    106103  ! CHARACTER(LEN=3)  :: aspec
    107104  ! integer :: virr=0
    108   !real :: tot_cloud_h
    109   !real :: dbg_height(nzmax)
     105  real :: tot_cloud_h
     106  real :: dbg_height(nzmax)
    110107!ZHG
    111108
     
    126123  if (init) then
    127124
    128 
    129     if (init_r) then
    130 
    131         open(333,file='heights.txt', &
    132           form='formatted')
    133         do kz=1,nuvz
    134             read(333,*) height(kz)
    135         end do
    136         close(333)
    137         write(*,*) 'height read'
    138     else
    139 
    140 
    141125! Search for a point with high surface pressure (i.e. not above significant topography)
    142126! Then, use this point to construct a reference z profile, to be used at all times
     
    177161    end do
    178162
    179     if (init_w) then
    180         open(333,file='heights.txt', &
    181           form='formatted')
    182         do kz=1,nuvz
    183               write(333,*) height(kz)
    184         end do
    185         close(333)
    186     endif
    187 
    188     endif ! init
    189163
    190164! Determine highest levels that can be within PBL
     
    204178    init=.false.
    205179
    206 !    dbg_height = height
     180    dbg_height = height
    207181
    208182  endif
     
    624598        convp=convprec(ix,jy,1,n)
    625599        prec=lsp+convp
    626 !        tot_cloud_h=0
     600        tot_cloud_h=0
    627601! Find clouds in the vertical
    628602        do kz=1, nz-1 !go from top to bottom
     
    630604! assuming rho is in kg/m3 and hz in m gives: kg/kg * kg/m3 *m3/kg /m = m2/m3
    631605            clw(ix,jy,kz,n)=(clwc(ix,jy,kz,n)*rho(ix,jy,kz,n))*(height(kz+1)-height(kz))
    632 !            tot_cloud_h=tot_cloud_h+(height(kz+1)-height(kz))
     606            tot_cloud_h=tot_cloud_h+(height(kz+1)-height(kz))
    633607           
    634608!            icloud_stats(ix,jy,4,n)= icloud_stats(ix,jy,4,n)+clw(ix,jy,kz,n)          ! Column cloud water [m3/m3]
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG