Changeset 2611


Ignore:
Timestamp:
Aug 3, 2016, 5:41:26 PM (8 years ago)
Author:
jyg
Message:

Introduction of a new option inhibiting the
evolution of the state variables, while calling
all parametrizations. The option is controlled by
the parameter flag_inhib_tend.

For the time being the flag is set to 0 (= no

inhibition of tendencies).

jyg for jld.

Location:
LMDZ5/trunk/libf/phylmd
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/add_pbl_tend.F90

    r2346 r2611  
    1 SUBROUTINE add_pbl_tend(zdu, zdv, zdt, zdq, zdql, zdqi, paprs, text,abortphy)
     1SUBROUTINE add_pbl_tend(zdu, zdv, zdt, zdq, zdql, zdqi, paprs, text,abortphy,flag_inhib_tend)
    22  ! ======================================================================
    33  ! Ajoute les tendances de couche limite, soit determinees par la
     
    3434  CHARACTER *(*) text
    3535  REAL paprs(klon,klev+1)
     36  INTEGER flag_inhib_tend ! if flag_inhib_tend != 0, tendencies are not added
    3637
    3738  ! Local :
     
    5657    PRINT *, ' add_pbl_tend, zzdt ', zzdt
    5758    PRINT *, ' add_pbl_tend, zzdq ', zzdq
    58     CALL add_phys_tend(zdu, zdv, zzdt, zzdq, zdql, zdqi, paprs, text,abortphy)
     59    CALL add_phys_tend(zdu, zdv, zzdt, zzdq, zdql, zdqi, paprs, text,abortphy,flag_inhib_tend)
    5960  ELSE
    60     CALL add_phys_tend(zdu, zdv, zdt, zdq, zdql, zdqi, paprs, text,abortphy)
     61    CALL add_phys_tend(zdu, zdv, zdt, zdq, zdql, zdqi, paprs, text,abortphy,flag_inhib_tend)
    6162  END IF
    6263
  • LMDZ5/trunk/libf/phylmd/add_phys_tend.F90

    r2400 r2611  
    22! $Id$
    33!
    4 SUBROUTINE add_phys_tend (zdu,zdv,zdt,zdq,zdql,zdqi,paprs,text,abortphy)
     4SUBROUTINE add_phys_tend (zdu,zdv,zdt,zdq,zdql,zdqi,paprs,text,abortphy,flag_inhib_tend)
    55!======================================================================
    66! Ajoute les tendances des variables physiques aux variables
     
    2020USE geometry_mod, ONLY: longitude_deg, latitude_deg
    2121USE print_control_mod, ONLY: prt_level
     22USE cmp_seri_mod
    2223IMPLICIT none
    2324  include "YOMCST.h"
     
    3132CHARACTER*(*) text
    3233INTEGER abortphy
     34INTEGER flag_inhib_tend ! if flag_inhib_tend != 0, tendencies are not added
    3335
    3436! Local :
     
    5557! Initialisations
    5658
    57       IF (abortphy==1) RETURN ! on n ajoute pas les tendance si le modele
     59     IF (prt_level >= 5) then
     60        write (*,*) "In add_phys_tend, after ",text
     61        call flush
     62     end if
     63
     64     ! if flag_inhib_tend != 0, tendencies are not added
     65     IF (flag_inhib_tend /= 0) then
     66        ! If requiered, diagnostics are shown
     67        IF (flag_inhib_tend > 0) then
     68           ! print some diagnostics if xxx_seri have changed
     69           call cmp_seri(flag_inhib_tend,text)
     70        END IF
     71        RETURN ! on n ajoute pas les tendance
     72     END IF
     73
     74     IF (abortphy==1) RETURN ! on n ajoute pas les tendance si le modele
    5875                              ! a deja plante.
    5976
     
    259276
    260277
    261       RETURN
    262       END
     278  RETURN
     279END SUBROUTINE add_phys_tend
  • LMDZ5/trunk/libf/phylmd/dyn1d/lmdz1d.F90

    r2602 r2611  
    248248      integer jcode
    249249      INTEGER read_climoz
     250!
     251      integer :: it_end ! iteration number of the last call
    250252!Al1
    251253      integer ecrit_slab_oc !1=ecrit,-1=lit,0=no file
    252254      data ecrit_slab_oc/-1/
     255!
     256!     if flag_inhib_forcing = 0, tendencies of forcing are added
     257!                           <> 0, tendencies of forcing are not added
     258      INTEGER :: flag_inhib_forcing = 0
    253259
    254260!=====================================================================
     
    747753        pbl_tke(:,2,:)=1.e-2
    748754        PRINT *, ' pbl_tke dans lmdz1d '
    749        DO nsrf = 1,4
    750          PRINT *,'pbl_tke(1,:,',nsrf,') ',pbl_tke(1,:,nsrf)
    751        ENDDO
     755        if (prt_level .ge. 5) then
     756         DO nsrf = 1,4
     757           PRINT *,'pbl_tke(1,:,',nsrf,') ',pbl_tke(1,:,nsrf)
     758         ENDDO
     759        end if
    752760
    753761!>jyg
     
    900908!=====================================================================
    901909           
    902       do while(it.le.nint(fnday*day_step))
     910      it_end = nint(fnday*day_step)
     911!test JLD     it_end = 10
     912      do while(it.le.it_end)
    903913
    904914       if (prt_level.ge.1) then
    905915         print*,'XXXXXXXXXXXXXXXXXXX ITAP,day,time=',                       &
    906      &             it,day,time,nint(fnday*day_step),day_step
     916     &             it,day,time,it_end,day_step
    907917         print*,'PAS DE TEMPS ',timestep
    908918       endif
    909919!Al1 demande de restartphy.nc
    910        if (it.eq.nint(fnday*day_step)) lastcall=.True.
     920       if (it.eq.it_end) lastcall=.True.
    911921
    912922!---------------------------------------------------------------------
     
    938948         write(*,*) 'firstcall,lastcall,phis',                               &
    939949     &               firstcall,lastcall,phis
     950       end if
     951       if (prt_level>=5) then
    940952         write(*,'(a10,2a4,4a13)') 'BEFOR1 IT=','it','l',                   &
    941953     &        'presniv','plev','play','phi'
     
    959971
    960972!---------------------------------------------------------------------
    961 ! Listing output for debug prt_level>=1
    962 !---------------------------------------------------------------------
    963         if (prt_level>=1) then
     973! Listing output for debug
     974!---------------------------------------------------------------------
     975        if (prt_level>=5) then
    964976          write(*,'(a11,2a4,4a13)') 'AFTER1 IT=','it','l',                  &
    965977     &        'presniv','plev','play','phi'
     
    9981010        endif
    9991011
    1000       IF (prt_level >= 1) print*, 'fcoriolis, xlat,mxcalc ', &
     1012      IF (prt_level >= 5) print*, 'fcoriolis, xlat,mxcalc ', &
    10011013                                   fcoriolis, xlat,mxcalc
    10021014
     
    10481060!! Increment state variables
    10491061!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1062    IF (flag_inhib_forcing == 0) then ! if tendency of forcings should be added
     1063
    10501064! pour les cas sandu et astex, on reclacule u,v,q,temp et teta dans 1D_nudge_sandu_astex.h
    10511065! au dessus de 700hpa, on relaxe vers les profils initiaux
     
    10661080     &               +d_q_nudge(1:mxcalc,:) )
    10671081
    1068         if (prt_level.ge.1) then
     1082        if (prt_level.ge.3) then
    10691083          print *,                                                          &
    10701084     &    'physiq-> temp(1),dt_phys(1),d_th_adv(1),dt_cooling(1) ',         &
     
    11131127!cc        q(1:mxcalc,2)=tmpvar(1:mxcalc)
    11141128
     1129   END IF ! end if tendency of tendency should be added
     1130
    11151131!---------------------------------------------------------------------
    11161132!   Air temperature :
  • LMDZ5/trunk/libf/phylmd/physiq_mod.F90

    r2606 r2611  
    216216
    217217    USE paramLMDZ_phy_mod
     218
     219    USE cmp_seri_mod
    218220
    219221    !IM stations CFMIP
     
    801803    ! eva: evaporation de l'eau liquide nuageuse
    802804    ! vdf: couche limite (Vertical DiFfusion)
    803 
     805    !
    804806    ! tendance nulles
    805807    REAL, dimension(klon,klev):: du0, dv0, dt0, dq0, dql0, dqi0
     808    !
     809    ! Flag pour pouvoir ne pas ajouter les tendances.
     810    ! Par defaut, les tendances doivente etre ajoutees et
     811    ! flag_inhib_tend = 0
     812    ! flag_inhib_tend > 0 : tendances non ajoutees, avec un nombre
     813    ! croissant de print quand la valeur du flag augmente
     814    !!! attention, ce flag doit etre change avec prudence !!!
     815    INTEGER :: flag_inhib_tend = 0 !  0 is the default value
     816!!    INTEGER :: flag_inhib_tend = 2
    806817
    807818    !
     
    17721783       ENDDO
    17731784    ENDDO
     1785    ! Initialize variables used for diagnostic purpose
     1786    if (flag_inhib_tend .ne. 0) call init_cmp_seri
    17741787    !IM
    17751788    IF (ip_ebil_phy.ge.1) THEN
     
    22172230          CALL add_pbl_tend &
    22182231               (d_u_vdf,d_v_vdf,d_t_vdf+d_t_diss,d_q_vdf,dql0,dqi0,paprs,&
    2219                'vdf',abortphy)
     2232               'vdf',abortphy,flag_inhib_tend)
    22202233       ELSE
    22212234          CALL add_phys_tend &
    22222235               (d_u_vdf,d_v_vdf,d_t_vdf+d_t_diss,d_q_vdf,dql0,dqi0,paprs,&
    2223                'vdf',abortphy)
     2236               'vdf',abortphy,flag_inhib_tend)
    22242237       ENDIF
    22252238       !--------------------------------------------------------------------
     
    25992612
    26002613    CALL add_phys_tend(d_u_con, d_v_con, d_t_con, d_q_con, dql0, dqi0, paprs, &
    2601          'convection',abortphy)
     2614         'convection',abortphy,flag_inhib_tend)
    26022615
    26032616    !-------------------------------------------------------------------------
     
    27722785       d_q_wake(:,:)=dq_wake(:,:)*dtime
    27732786       CALL add_phys_tend(du0,dv0,d_t_wake,d_q_wake,dql0,dqi0,paprs,'wake', &
    2774             abortphy)
     2787            abortphy,flag_inhib_tend)
    27752788       !------------------------------------------------------------------------
    27762789
     
    29192932          !
    29202933          CALL add_phys_tend(d_u_ajs,d_v_ajs,d_t_ajs,d_q_ajs,  &
    2921                              dql0,dqi0,paprs,'thermals', abortphy)
     2934                             dql0,dqi0,paprs,'thermals', abortphy,flag_inhib_tend)
    29222935          !
    29232936          !>jyg
     
    29832996          ! ajout des tendances de l'ajustement sec ou des thermiques
    29842997          CALL add_phys_tend(du0,dv0,d_t_ajsb,d_q_ajsb,dql0,dqi0,paprs, &
    2985                'ajsb',abortphy)
     2998               'ajsb',abortphy,flag_inhib_tend)
    29862999          d_t_ajs(:,:)=d_t_ajs(:,:)+d_t_ajsb(:,:)
    29873000          d_q_ajs(:,:)=d_q_ajs(:,:)+d_q_ajsb(:,:)
     
    30423055
    30433056    CALL add_phys_tend(du0,dv0,d_t_lsc,d_q_lsc,d_ql_lsc,d_qi_lsc,paprs, &
    3044          'lsc',abortphy)
     3057         'lsc',abortphy,flag_inhib_tend)
    30453058    !---------------------------------------------------------------------------
    30463059    DO k = 1, klev
     
    38043817    ENDDO
    38053818
    3806     CALL add_phys_tend(du0,dv0,d_t_swr,dq0,dql0,dqi0,paprs,'SW',abortphy)
    3807     CALL add_phys_tend(du0,dv0,d_t_lwr,dq0,dql0,dqi0,paprs,'LW',abortphy)
     3819    CALL add_phys_tend(du0,dv0,d_t_swr,dq0,dql0,dqi0,paprs,'SW',abortphy,flag_inhib_tend)
     3820    CALL add_phys_tend(du0,dv0,d_t_lwr,dq0,dql0,dqi0,paprs,'LW',abortphy,flag_inhib_tend)
    38083821
    38093822    !
     
    38893902       ! ajout des tendances de la trainee de l'orographie
    38903903       CALL add_phys_tend(d_u_oro,d_v_oro,d_t_oro,dq0,dql0,dqi0,paprs,'oro', &
    3891             abortphy)
     3904            abortphy,flag_inhib_tend)
    38923905       !----------------------------------------------------------------------
    38933906       !
     
    39353948       ! ajout des tendances de la portance de l'orographie
    39363949       CALL add_phys_tend(d_u_lif, d_v_lif, d_t_lif, dq0, dql0, dqi0, paprs, &
    3937             'lif', abortphy)
     3950            'lif', abortphy,flag_inhib_tend)
    39383951    ENDIF ! fin de test sur ok_orolf
    39393952
     
    39583971       d_t_hin(:, :)=0.
    39593972       CALL add_phys_tend(du_gwd_hines, dv_gwd_hines, d_t_hin, dq0, dql0, &
    3960             dqi0, paprs, 'hin', abortphy)
     3973            dqi0, paprs, 'hin', abortphy,flag_inhib_tend)
    39613974    ENDIF
    39623975
     
    39753988
    39763989       CALL add_phys_tend(du_gwd_front, dv_gwd_front, dt0, dq0, dql0, dqi0, &
    3977             paprs, 'front_gwd_rando', abortphy)
     3990            paprs, 'front_gwd_rando', abortphy,flag_inhib_tend)
    39783991    ENDIF
    39793992
     
    39833996            du_gwd_rando, dv_gwd_rando, east_gwstress, west_gwstress)
    39843997       CALL add_phys_tend(du_gwd_rando, dv_gwd_rando, dt0, dq0, dql0, dqi0, &
    3985             paprs, 'flott_gwd_rando', abortphy)
     3998            paprs, 'flott_gwd_rando', abortphy,flag_inhib_tend)
    39863999       zustr_gwd_rando=0.
    39874000       zvstr_gwd_rando=0.
     
    40464059       ! ajout de la tendance d'humidite due au methane
    40474060       CALL add_phys_tend(du0, dv0, dt0, d_q_ch4*dtime, dql0, dqi0, paprs, &
    4048             'q_ch4', abortphy)
     4061            'q_ch4', abortphy,flag_inhib_tend)
    40494062    END IF
    40504063    !
  • LMDZ5/trunk/libf/phylmd/radlwsw_m.F90

    r2530 r2611  
    465465        PWV(i,k) = MAX (q(iof+i,k), 1.0e-12)
    466466        PQS(i,k) = PWV(i,k)
     467!       Confert from  column density of ozone in a cell, in kDU, to a mass fraction
    467468        POZON(i,k, :) = wo(iof+i, k, :) * RG * dobson_u * 1e3 &
    468469             / (paprs(iof+i, k) - paprs(iof+i, k+1))
Note: See TracChangeset for help on using the changeset viewer.