Ignore:
Timestamp:
Mar 24, 2014, 9:46:50 AM (11 years ago)
Author:
aslmd
Message:

LMDZ.MARS + MESOSCALE

A quite major commit, at least for MESOSCALE.
In a word: any ngrid deserves to be free.

  • no need to recompile when changing number of horizontal grid points or number of processors
  • latest version of LMDZ.MARS physics can be used
  • WARNING! Nesting is still yet to be fixed (since r1027)

Also some small bug fixes to LMDZ.MARS.

Changes in LMDZ.MARS


--> fixed a potential bug in thermal plume model because zlmax was computed both in thermcell_main_mars and calltherm_interface... so made it an OUT argument of calltherm_interface. also: changed the name to limz. and added precompiling flags to avoid the use of planetwide in MESOSCALE. in MESOSCALE we just go high enough (nlayer-5) and do not care about computational cost (although we certainly gain from not using MAXVAL).
--> moved allocations upward in inifis. does not change anything for GCM, but make MESOSCALE modifications simpler, and overall make inifis better organized: first allocations, then reading callphys.def file.
--> added precompiling flags around lines that are both useless for MESOSCALE (notably I/O) and recently adapted to parallel computations in the GCM
--> tidied up what is MESOSCALE vs. GCM in surfini

Changes in MESOSCALE


--> changed makemeso to allow dynamically set nx ny nprocs
--> changed makemeso to remove links to Fortran code adapted to parallel GCM and useless for mesoscale
--> changed ngridmx to ngrid in inifis includes

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/aeroptproperties.F

    r1047 r1212  
    12471247            ENDDO ! ig
    12481248          ENDDO ! lg
     1249#ifndef MESOSCALE
    12491250          write(out_str(1:1),'(i1.1)') out_nchannel
    12501251          call WRITEDIAGFI(ngrid,'qextvis'//out_str,"Ext.efficiency","",
     
    12541255          call WRITEDIAGFI(ngrid,'gvis'//out_str,"Asym.Factor","",
    12551256     &                     out_ndim,out_g)
     1257#endif
    12561258c     -------------------------------------------------------------
    12571259        ENDDO ! out_nchannel
     
    12681270            ENDDO ! ig
    12691271          ENDDO ! lg
     1272#ifndef MESOSCALE
    12701273          write(out_str(1:1),'(i1.1)') out_nchannel
    12711274       call WRITEDIAGFI(ngrid,'qextir'//out_str,"Ext.efficiency","",
     
    12751278       call WRITEDIAGFI(ngrid,'gir'//out_str,"Asym.Factor","",
    12761279     &                     out_ndim,out_g)
     1280#endif
    12771281c     -------------------------------------------------------------
    12781282        ENDDO ! out_nchannel
     1283#ifndef MESOSCALE
    12791284        call WRITEDIAGFI(ngrid,"omegvisref","Sing.Scat.Alb.","",
    12801285     &                   out_ndim,omegaREFvis3d(1,1,out_iaer))
    12811286        call WRITEDIAGFI(ngrid,"omegirref","Sing.Scat.Alb.","",
    12821287     &                   out_ndim,omegaREFir3d(1,1,out_iaer))
     1288#endif
    12831289      ENDIF ! out_qwg
    12841290c==================================================================
  • trunk/LMDZ.MARS/libf/phymars/calltherm_interface.F90

    r1036 r1212  
    133133      REAL zzw2(ngrid,nlayer+1)
    134134      REAL zmax(ngrid)
    135       INTEGER ndt,zlmax
     135      INTEGER ndt,limz
    136136
    137137!--------------------------------------------------------
     
    231231     &      ,zu,zv,zt,pq_therm,q2_therm  &
    232232     &      ,d_t_the,d_q_the  &
    233      &      ,zfm_therm,zentr_therm,zdetr_therm,lmax,zmax  &
     233     &      ,zfm_therm,zentr_therm,zdetr_therm,lmax,zmax,limz  &
    234234     &      ,zzw2,fraca,zpopsk &
    235235     &      ,zheatFlux,zheatFlux_down &
     
    279279!****************************************************************
    280280
    281 !     Do we have thermals that are too high ?
    282 
    283       lmax(:)=nint(lmax_real(:))
    284       zlmax=MAXVAL(lmax(:))+2
    285       if (zlmax .ge. nlayer) then
    286         print*,'thermals have reached last layer of the model'
    287         print*,'this is not good !'
    288       endif
    289 
    290 
    291281! Now that we have computed total entrainment and detrainment, we can
    292282! advect u, v, and q in thermals. (potential temperature and co2 MMR
     
    304294! this ensure mass flux conservation
    305295      detrmod(:,:)=0.
    306       do l=1,zlmax
     296      do l=1,limz
    307297         do ig=1,ngrid
    308298            detrmod(ig,l)=fm_therm(ig,l)-fm_therm(ig,l+1) &
     
    320310      call thermcell_dqup(ngrid,nlayer,ptimestep                &
    321311     &      ,fm_therm,entr_therm,detrmod,  &
    322      &     masse,zu,d_u_ajs,ndt,zlmax)
     312     &     masse,zu,d_u_ajs,ndt,limz)
    323313
    324314      ! v component of wind velocity advection in thermals
     
    326316      call thermcell_dqup(ngrid,nlayer,ptimestep    &
    327317     &       ,fm_therm,entr_therm,detrmod,  &
    328      &     masse,zv,d_v_ajs,ndt,zlmax)
     318     &     masse,zv,d_v_ajs,ndt,limz)
    329319
    330320      ! non co2 tracers advection in thermals
     
    336326      call thermcell_dqup(ngrid,nlayer,ptimestep     &
    337327     &     ,fm_therm,entr_therm,detrmod,  &
    338      &    masse,pq_therm(:,:,iq),d_q_ajs(:,:,iq),ndt,zlmax)
     328     &    masse,pq_therm(:,:,iq),d_q_ajs(:,:,iq),ndt,limz)
    339329      endif
    340330      ENDDO
     
    346336      call thermcell_dqup(ngrid,nlayer,ptimestep     &
    347337     &     ,fm_therm,entr_therm,detrmod,  &
    348      &    masse,q2_therm,dq2_therm,ndt,zlmax)
     338     &    masse,q2_therm,dq2_therm,ndt,limz)
    349339      endif
    350340
     
    367357! **********************************************************************
    368358
    369       do l=1,zlmax
     359      do l=1,limz
    370360        pdu_th(:,l)=d_u_ajs(:,l)
    371361        pdv_th(:,l)=d_v_ajs(:,l)
     
    377367               do iq=1,nq
    378368                if (iq .ne. igcm_co2) then
    379                   do l=1,zlmax
     369                  do l=1,limz
    380370                     pdq_th(:,l,iq)=d_q_ajs(:,l,iq) !non-co2 tracers d_q_ajs are dq/dt (kg/kg/s)
    381371                  enddo
    382372                else
    383                   do l=1,zlmax
     373                  do l=1,limz
    384374                     pdq_th(:,l,iq)=d_q_ajs(:,l,iq)/ptimestep !co2 tracer d_q_ajs is dq (kg/kg)
    385375                  enddo
     
    400390
    401391           ! update output variable for temperature. d_t_ajs is delta T in (K), pdt_th is dT/dt in (K/s)
    402            do l=1,zlmax
     392           do l=1,limz
    403393              pdt_th(:,l)=d_t_ajs(:,l)/ptimestep
    404394           enddo
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds.F

    r1047 r1212  
    476476     &     countcells*100/(nlay*ngrid), '% for microphys computation'
    477477
     478#ifndef MESOSCALE
    478479!      IF (ngrid.ne.1) THEN ! 3D
    479480!         call WRITEDIAGFI(ngrid,"satu","ratio saturation","",3,
     
    531532!     &                    rhocloud)
    532533!      ENDIF
     534#endif
    533535     
    534536      ENDIF ! endif test_flag
  • trunk/LMDZ.MARS/libf/phymars/inifis.F

    r1130 r1212  
    116116!      h2o = .false.
    117117
     118
     119!!! 1. ALLOCATIONS
     120!!! --------------
     121
     122      ! allocate "slope_mod" arrays
     123      call ini_slope_mod(ngrid)
     124
     125      ! allocate "comsaison_h" arrays
     126      call ini_comsaison_h(ngrid)
     127
     128      ! allocate "surfdat_h" arrays
     129      call ini_surfdat_h(ngrid)
     130
     131      ! allocate "comgeomfi_h" arrays
     132      allocate(lati(ngrid))
     133      allocate(long(ngrid))
     134      allocate(area(ngrid))
     135
     136      ! fill "comgeomfi_h" data
     137      CALL SCOPY(ngrid,plon,1,long,1)
     138      CALL SCOPY(ngrid,plat,1,lati,1)
     139      CALL SCOPY(ngrid,parea,1,area,1)
     140      totarea=SSUM(ngrid,area,1)
     141
     142      ! allocate "comdiurn_h" data
     143      allocate(sinlat(ngrid))
     144      allocate(coslat(ngrid))
     145      allocate(sinlon(ngrid))
     146      allocate(coslon(ngrid))
     147
     148      ! fill "comdiurn_h" data
     149      DO ig=1,ngrid
     150         sinlat(ig)=sin(plat(ig))
     151         coslat(ig)=cos(plat(ig))
     152         sinlon(ig)=sin(plon(ig))
     153         coslon(ig)=cos(plon(ig))
     154      ENDDO
     155
     156      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
     157
     158      ! allocate "comsoil_h" arrays
     159      call ini_comsoil_h(ngrid)
     160
     161      ! set some variables in "dimradmars_mod"
     162      call ini_dimradmars_mod(ngrid,nlayer)
     163
     164      ! allocate arrays in "yomaer_h"
     165      call ini_yomaer_h
     166
     167      ! allocate arrays in "yomlw_h"
     168      call ini_yomlw_h(ngrid)
     169
     170      ! allocate arrays in "conc_mod"
     171      call ini_conc_mod(ngrid,nlayer)
     172
     173
     174!!! 2. SETTINGS and CONSTANTS
     175!!! -------------------------
     176
    118177      rad=prad
    119178      cpp=pcpp
     
    125184
    126185      nqmx=nq
     186
     187!! MESOSCALE INITIALIZATIONS
     188#ifdef MESOSCALE
     189#include "meso_inc/meso_inc_inifisini.F"
     190#endif
    127191
    128192! --------------------------------------------------------
     
    797861      CLOSE(99)
    798862
    799 !-----------------------------------------------------------------------
    800 !     Some more initialization:
    801 !     ------------------------
    802 
    803       ! allocate "slope_mod" arrays
    804       call ini_slope_mod(ngrid)
    805      
    806       ! allocate "comsaison_h" arrays
    807       call ini_comsaison_h(ngrid)
    808      
    809       ! allocate "surfdat_h" arrays
    810       call ini_surfdat_h(ngrid)
    811      
    812       ! allocate "comgeomfi_h" arrays
    813       allocate(lati(ngrid))
    814       allocate(long(ngrid))
    815       allocate(area(ngrid))
    816      
    817       ! fill "comgeomfi_h" data
    818       CALL SCOPY(ngrid,plon,1,long,1)
    819       CALL SCOPY(ngrid,plat,1,lati,1)
    820       CALL SCOPY(ngrid,parea,1,area,1)
    821       totarea=SSUM(ngrid,area,1)
    822 
    823       ! allocate "comdiurn_h" data
    824       allocate(sinlat(ngrid))
    825       allocate(coslat(ngrid))
    826       allocate(sinlon(ngrid))
    827       allocate(coslon(ngrid))
    828      
    829       ! fill "comdiurn_h" data
    830       DO ig=1,ngrid
    831          sinlat(ig)=sin(plat(ig))
    832          coslat(ig)=cos(plat(ig))
    833          sinlon(ig)=sin(plon(ig))
    834          coslon(ig)=cos(plon(ig))
    835       ENDDO
    836 
    837       pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
    838 
    839       ! allocate "comsoil_h" arrays
    840       call ini_comsoil_h(ngrid)
    841            
    842       ! set some variables in "dimradmars_mod"
    843       call ini_dimradmars_mod(ngrid,nlayer)
    844      
    845       ! allocate arrays in "yomaer_h"
    846       call ini_yomaer_h
    847      
    848       ! allocate arrays in "yomlw_h"
    849       call ini_yomlw_h(ngrid)
    850      
    851       ! allocate arrays in "conc_mod"
    852       call ini_conc_mod(ngrid,nlayer)
    853    
    854 !! MESOSCALE INITIALIZATIONS
    855 #ifdef MESOSCALE
    856 #include "meso_inc/meso_inc_inifisini.F"
    857 #endif
    858  
    859863      END
  • trunk/LMDZ.MARS/libf/phymars/pbl_parameters.F

    r662 r1212  
    472472      ENDIF ! of if calltherm
    473473
     474#ifndef MESOSCALE
    474475            call WRITEDIAGFI(ngrid,'rib_pbl',
    475476     &   'Richardson in pbl parameter','m/s',2,rib)
     
    491492     &   'flottabilité','ms',2,pz0tcomp)
    492493       call WRITEDIAGFI(ngrid,'zz1','flottabilité','m',2,zzlay(:,1))
     494#endif
    493495
    494496      RETURN
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r1208 r1212  
    1919      use comsoil_h, only: inertiedat, ! soil thermal inertia
    2020     &                     nsoilmx ! number of subsurface layers
    21       use eofdump_mod, only: eofdump
    2221      use comgeomfi_h, only: long, lati, area
    2322      use comdiurn_h, only: sinlon, coslon, sinlat, coslat
     
    2928      use conc_mod, only: rnew, cpnew, mmean
    3029      use control_mod, only: iphysiq, day_step, ecritstart
    31       use phyredem, only: physdem0, physdem1
    32 
    3330#ifdef MESOSCALE
    3431      use comsoil_h, only: mlayer,layer
    3532      use surfdat_h, only: z0_default
     33#else
     34      use phyredem, only: physdem0, physdem1
     35      use eofdump_mod, only: eofdump
    3636#endif
    3737
     
    16901690         endif ! of if (tracer)
    16911691
     1692#ifndef MESOSCALE
    16921693c        -----------------------------------------------------------------
    16931694c        WSTATS: Saving statistics
     
    19031904            CALL eofdump(ngrid, nlayer, zu, zv, zt, rho, ps)
    19041905         ENDIF
     1906#endif
     1907!endif of ifndef MESOSCALE
     1908
    19051909
    19061910
     
    22782282c        ==========================================================
    22792283#endif
     2284! of ifdef MESOSCALE
    22802285
    22812286      ELSE     ! if(ngrid.eq.1)
    22822287
     2288#ifndef MESOSCALE
    22832289         write(*,'("Ls =",f11.6," tauref(",f4.0," Pa) =",f9.6)')
    22842290     &    zls*180./pi,odpref,tauref
     
    25082514     &                   log(zplay(1,nlayer)/zplay(1,nlayer-1))*
    25092515     &                   rnew(1,nlayer)*tmean/g
     2516#endif
    25102517
    25112518      END IF       ! if(ngrid.ne.1)
  • trunk/LMDZ.MARS/libf/phymars/surfini.F

    r1207 r1212  
    88     &                     albedo_h2o_ice, inert_h2o_ice, albedodat,
    99     &                     albedice
     10#ifndef MESOSCALE
    1011      use mod_grid_phy_lmdz, only : klon_glo ! # of physics point on full grid
    1112      use mod_phys_lmdz_para, only : is_master, gather, scatter
     13#endif
    1214      IMPLICIT NONE
    1315c=======================================================================
     
    5557      REAL        zelat,zelon
    5658
     59#ifndef MESOSCALE
    5760      INTEGER nb_ice(klon_glo,2)   ! number of counts | detected ice for GCM grid
     61#endif
    5862      INTEGER latice(jjm,2),lonice (iim,2) ! number of counts | detected ice along lat & lon axis
    5963
     
    6771      character (len=100) :: zedatafile
    6872
    69       ! to handle parallel cases
    70 #if CPP_PARA
    71       logical watercaptag_glo(klon_glo)
    72       real dryness_glo(klon_glo)
    73       real lati_glo(klon_glo)
    74       real long_glo(klon_glo)
    75 #else
    76       logical watercaptag_glo(ngrid)
    77       real dryness_glo(ngrid)
    78       real lati_glo(ngrid)
    79       real long_glo(ngrid)
    80 #endif
    81 
    82 c
    83 c=======================================================================
    84 ! Initialize watercaptag (default is false)
    85       watercaptag_glo(:)=.false.
    86 
    87 c     water ice outliers
    88 c     ------------------------------------------
    89 
    90       IF ((water) .and. (caps)) THEN
    91      
    92 c Perennial H20 north cap defined by watercaptag=true (allows surface to be
    93 c hollowed by sublimation in vdifc).
    94 
    95 c We might not want albedodat to be modified because it is used to write
    96 c restart files. Instead, albedo is directly modified when needed (i.e.
    97 c if we have watercaptag and no co2 ice), below and in albedocaps.F90
    98 
    99 c       "Dryness coefficient" controlling the evaporation and
    100 c        sublimation from the ground water ice (close to 1)
    101 c        HERE, the goal is to correct for the fact
    102 c        that the simulated permanent water ice polar caps
    103 c        is larger than the actual cap and the atmospheric
    104 c        opacity not always realistic.
    105 
    106          alternate = 0
    107          
    108          if (ngrid .ne. 1) then
    109            watercaptag(:) = .false.
    110            longwatercaptag(:) = .false.
    111          endif
    112          
    113          write(*,*) "surfini: Ice dryness ?"
    114          icedryness=1. ! default value
    115          call getin("icedryness",icedryness)
    116          write(*,*) "surfini: icedryness = ",icedryness
    117          dryness (:) = icedryness
    118          
    119        
    12073#ifdef MESOSCALE
    12174
     
    13891                 watercaptag(ig)  = .false.
    13992                 dryness(ig)      = 1.
    140          endif
     93         endif
     94
     95      enddo
     96#endif
     97! problem with nested precompiling flags
     98
     99#ifndef MESOSCALE
     100      ! to handle parallel cases
     101#if CPP_PARA
     102      logical watercaptag_glo(klon_glo)
     103      real dryness_glo(klon_glo)
     104      real lati_glo(klon_glo)
     105      real long_glo(klon_glo)
     106#else
     107      logical watercaptag_glo(ngrid)
     108      real dryness_glo(ngrid)
     109      real lati_glo(ngrid)
     110      real long_glo(ngrid)
     111#endif
     112#endif
     113
     114#ifndef MESOSCALE
     115
     116c
     117c=======================================================================
     118! Initialize watercaptag (default is false)
     119      watercaptag_glo(:)=.false.
     120
     121c     water ice outliers
     122c     ------------------------------------------
     123
     124      IF ((water) .and. (caps)) THEN
     125     
     126c Perennial H20 north cap defined by watercaptag=true (allows surface to be
     127c hollowed by sublimation in vdifc).
     128
     129c We might not want albedodat to be modified because it is used to write
     130c restart files. Instead, albedo is directly modified when needed (i.e.
     131c if we have watercaptag and no co2 ice), below and in albedocaps.F90
     132
     133c       "Dryness coefficient" controlling the evaporation and
     134c        sublimation from the ground water ice (close to 1)
     135c        HERE, the goal is to correct for the fact
     136c        that the simulated permanent water ice polar caps
     137c        is larger than the actual cap and the atmospheric
     138c        opacity not always realistic.
     139
     140         alternate = 0
    141141         
    142       enddo
    143 #else
    144 
     142         if (ngrid .ne. 1) then
     143           watercaptag(:) = .false.
     144           longwatercaptag(:) = .false.
     145         endif
     146         
     147         write(*,*) "surfini: Ice dryness ?"
     148         icedryness=1. ! default value
     149         call getin("icedryness",icedryness)
     150         write(*,*) "surfini: icedryness = ",icedryness
     151         dryness (:) = icedryness
     152         
    145153      ! To be able to run in parallel, we work on the full grid
    146154      ! and dispatch results afterwards
     
    453461       call scatter(watercaptag_glo,watercaptag)
    454462       
    455 #endif     
    456463! end of #else of #ifdef MESOSCALE
    457464       ENDIF ! (caps & water)
    458        
     465#endif       
    459466
    460467c ===============================================================
  • trunk/LMDZ.MARS/libf/phymars/thermcell_dqup.F90

    r1033 r1212  
    2525
    2626      subroutine thermcell_dqup(ngrid,nlayer,ptimestep,fm,entr,detr,  &
    27      &    masse0,q_therm,dq_therm,ndt,zlmax)
     27     &    masse0,q_therm,dq_therm,ndt,limz)
    2828      implicit none
    2929
     
    3838      REAL, INTENT(IN) :: masse0(ngrid,nlayer) ! mass of cells
    3939      INTEGER, INTENT(IN) :: ndt ! number of subtimesteps
    40       INTEGER, INTENT(IN) :: zlmax ! index of maximum layer
     40      INTEGER, INTENT(IN) :: limz ! index of maximum layer
    4141
    4242! ============================ OUTPUTS ===========================
     
    7070       enddo
    7171
    72         do k=2,zlmax
     72        do k=2,limz
    7373           do ig=1,ngrid
    7474              if ((fm(ig,k+1)+detr(ig,k))*ptimestep.gt.  &
     
    8282        enddo
    8383
    84         do k=1,zlmax
     84        do k=1,limz
    8585          q(:,k)=q(:,k)+         &
    8686     &    (detr(:,k)*qa(:,k)-entr(:,k)*q(:,k) &
     
    9393! ====== Derivative ==============================================
    9494
    95          do k=1,zlmax
     95         do k=1,limz
    9696          dq_therm(:,k)=(q(:,k)-q_therm(:,k))/ptimestep
    9797         enddo
  • trunk/LMDZ.MARS/libf/phymars/thermcell_main_mars.F90

    r1130 r1212  
    3737     &                  ,pu,pv,pt,pq,pq2  &
    3838     &                  ,pdtadj,pdqadj  &
    39      &                  ,fm,entr,detr,lmax,zmax  &
     39     &                  ,fm,entr,detr,lmax,zmax,limz  &
    4040     &                  ,zw2,fraca &
    4141     &                  ,zpopsk,heatFlux,heatFlux_down &
     
    4343
    4444      USE comtherm_h
     45#ifndef MESOSCALE
    4546      use planetwide_mod, only: planetwide_maxval
     47#endif
    4648
    4749      IMPLICIT NONE
     
    8587      REAL, INTENT(OUT) :: heatFlux_down(ngrid,nlayer) ! interface heat flux from downdraft
    8688
     89      INTEGER, INTENT(OUT) :: limz ! limit vertical index for integration
     90
    8791! ============== LOCAL ================
    8892      REAL :: pdqadj(ngrid,nlayer,nq) !tracer change from thermals dq/dt, only for CO2 (the rest can be advected outside of the loop)
     
    153157      REAL denom(ngrid)
    154158      REAL zlevinter(ngrid)
    155       INTEGER zlmax
    156159
    157160! =========================================
     
    765768! ===========================================================================
    766769
    767       !zlmax=MAXVAL(lmax(:))+2 ! OK, but in serial mode only; use planet
    768       call planetwide_maxval(lmax,zlmax)
    769       zlmax=zlmax+2
     770#ifdef MESOSCALE
     771      limz= nlayer-5 ! the most important is limz > max(PBLheight)+2
     772                     ! nlayer-5 is more than enough!
     773#else
     774      call planetwide_maxval(lmax,limz)
     775      limz=limz+2
     776#endif
    770777     
    771       if (zlmax .ge. nlayer) then
     778      if (limz .ge. nlayer) then
    772779        print*,'thermals have reached last layer of the model'
    773780        print*,'this is not good !'
    774         zlmax=nlayer
     781        limz=nlayer
    775782      endif
    776783! alim_star_clos is the source profile used for closure. It consists of the
     
    794801
    795802! llmax is the index of the heighest thermal in the simulation domain
    796       !llmax=1
    797       !do ig=1,ngrid
    798       !   if (lalim(ig)>llmax) llmax=lalim(ig)
    799       !enddo
     803#ifdef MESOSCALE
     804      !! AS: THIS IS PARALLEL SENSITIVE!!!!! to be corrected?
     805      llmax=1
     806      do ig=1,ngrid
     807         if (lalim(ig)>llmax) llmax=lalim(ig)
     808      enddo
     809#else
    800810      call planetwide_maxval(lalim,llmax)
     811#endif
    801812
    802813! Integral of a**2/(rho* Delta z), see equation 13 of appendix 4.2 in paper
     
    856867!-------------------------------------------------------------------------
    857868
    858       do l=1,zlmax
     869      do l=1,limz
    859870         entr(:,l)=f(:)*(entr_star(:,l)+alim_star(:,l))
    860871         detr(:,l)=f(:)*detr_star(:,l)
     
    863874! Reconstruct the updraft mass flux everywhere
    864875
    865       do l=1,zlmax
     876      do l=1,limz
    866877         do ig=1,ngrid
    867878            if (l.lt.lmax(ig)) then
     
    890901!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    891902
    892       do l=1,zlmax !loop on the levels
     903      do l=1,limz !loop on the levels
    893904!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    894905
     
    9921003!-----------------------------------------------------------------------
    9931004
    994       do l=1,zlmax
     1005      do l=1,limz
    9951006         do ig=1,ngrid
    9961007            eee0=entr(ig,l)
     
    11401151!------------------------------------------------------------------
    11411152      fraca(:,:)=0.
    1142       do l=2,zlmax
     1153      do l=2,limz
    11431154         do ig=1,ngrid
    11441155            if (zw2(ig,l).gt.1.e-10) then
     
    11611172      if (igcm_co2.ne.0) then
    11621173      detrmod(:,:)=0.
    1163       do k=1,zlmax
     1174      do k=1,limz
    11641175         do ig=1,ngrid
    11651176            detrmod(ig,k)=fm(ig,k)-fm(ig,k+1) &
     
    11741185      call thermcell_dqup(ngrid,nlayer,ptimestep     &
    11751186     &     ,fm,entr,detrmod,  &
    1176      &    masse,pq(:,:,igcm_co2),pdqadj(:,:,igcm_co2),ndt,zlmax)
     1187     &    masse,pq(:,:,igcm_co2),pdqadj(:,:,igcm_co2),ndt,limz)
    11771188
    11781189! Compute the ratio between theta and theta_m
    11791190     
    1180        do l=1,zlmax
     1191       do l=1,limz
    11811192          do ig=1,ngrid
    11821193             ratiom(ig,l)=1./(A*(pq(ig,l,igcm_co2)+pdqadj(ig,l,igcm_co2)*ptimestep)+B)
     
    11911202
    11921203      pdtadj(:,:)=0.
    1193       do l=1,zlmax
     1204      do l=1,limz
    11941205         do ig=1,ngrid
    11951206         pdtadj(ig,l)=(zdthladj(ig,l)+zdthladj_down(ig,l))*zpopsk(ig,l)*ratiom(ig,l)
     
    12251236        buoyancyEst(:,:)=0.
    12261237        heatFlux_down(:,:)=0.
    1227       do l=1,zlmax
     1238      do l=1,limz
    12281239       do ig=1,ngrid
    12291240        heatFlux(ig,l)=fm(ig,l)*(teta_th_int(ig,l)-teta_env_int(ig,l))/(rhobarz(ig,l))
Note: See TracChangeset for help on using the changeset viewer.