Ignore:
Timestamp:
Feb 15, 2019, 2:43:57 PM (6 years ago)
Author:
aboissinot
Message:

Fix a bug in thermcell_alim.F90 where vertical and horizontal loops must be inverted.
In thermal plume model, arrays size declaration is standardised (no longer done thanks to dimphy module but by way of arguments).
Clean up some thermal plume model routines (remove uselesss variables...)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_alim.F90

    r2093 r2101  
    22!
    33!
    4       SUBROUTINE thermcell_alim(ngrid,klev,ztv2,zlev,alim_star,lalim,lmin)
     4SUBROUTINE thermcell_alim(ngrid,nlay,ztv2,zlev,alim_star,lalim,lmin)
    55     
    6      
    7       USE thermcell_mod, ONLY: linf, d_temp
    8      
    9       IMPLICIT NONE
    106     
    117!==============================================================================
     
    1410! laterale a la base des panaches thermiques
    1511!==============================================================================
     12     
     13      IMPLICIT NONE
    1614     
    1715     
     
    2422     
    2523      INTEGER, INTENT(IN) :: ngrid
    26       INTEGER, INTENT(IN) :: klev
    27       INTEGER, INTENT(IN) :: lmin(ngrid)        ! plume initial level
     24      INTEGER, INTENT(IN) :: nlay
     25      INTEGER, INTENT(IN) :: lmin(ngrid)           ! plume initial level
    2826     
    29       REAL, INTENT(IN) :: ztv2(ngrid,klev)      ! Virtual potential temperature
    30       REAL, INTENT(IN) :: zlev(ngrid,klev+1)    ! levels altitude
     27      REAL, INTENT(IN) :: ztv2(ngrid,nlay)         ! Virtual potential temperature
     28      REAL, INTENT(IN) :: zlev(ngrid,nlay+1)       ! levels altitude
    3129     
    3230!      outputs:
    3331!      --------
    3432     
    35       INTEGER, INTENT(OUT) :: lalim(ngrid)      ! alimentation maximal level
     33      INTEGER, INTENT(OUT) :: lalim(ngrid)         ! alimentation maximal level
    3634     
    37       REAL, INTENT(OUT) :: alim_star(ngrid,klev)
     35      REAL, INTENT(OUT) :: alim_star(ngrid,nlay)   ! Normalized alimentation
    3836     
    3937!      local:
     
    4240      INTEGER :: ig, l
    4341     
    44       REAL :: alim_star_tot(ngrid)              ! integrated alimentation
     42      REAL :: alim_star_tot(ngrid)                 ! integrated alimentation
    4543     
    4644!==============================================================================
     
    5654!==============================================================================
    5755     
    58       DO l=lmin(ig),klev-1
    59          DO ig=1,ngrid
    60             IF ((ztv2(ig,l)>ztv2(ig,l+1)).and.(ztv2(ig,lmin(ig))>=ztv2(ig,l))) THEN
     56      DO ig=1,ngrid
     57         DO l=lmin(ig),nlay-1
     58            IF ((ztv2(ig,l).gt.ztv2(ig,l+1)).and.(ztv2(ig,lmin(ig)).ge.ztv2(ig,l))) THEN
    6159               alim_star(ig,l) = MAX( (ztv2(ig,l) - ztv2(ig,l+1)), 0.)  &
    6260               &               * sqrt(zlev(ig,l+1))
     
    7371!------------------------------------------------------------------------------
    7472     
    75       DO l=1,klev
     73      DO l=1,nlay
    7674         DO ig=1,ngrid
    7775            IF (alim_star_tot(ig) > 1.e-10 ) THEN
Note: See TracChangeset for help on using the changeset viewer.