Ignore:
Timestamp:
Sep 29, 2016, 11:26:46 PM (8 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2593:2640 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/dyn1d/lmdz1d.F90

    r2594 r2641  
    1616       ftsol, pbl_tke, pctsrf, radsol, rain_fall, snow_fall, ratqs, &
    1717       rnebcon, rugoro, sig1, w01, solaire_etat0, sollw, sollwdown, &
    18        solsw, t_ancien, q_ancien, u_ancien, v_ancien, wake_cstar, wake_deltaq, &
    19        wake_deltat, wake_delta_pbl_TKE, delta_tsurf, wake_fip, wake_pe, &
    20        wake_s, zgam, &
    21        zmax0, zmea, zpic, zsig, &
     18       solsw, t_ancien, q_ancien, u_ancien, v_ancien, wake_cstar, &
     19       wake_delta_pbl_TKE, delta_tsurf, wake_fip, wake_pe, &
     20       wake_deltaq, wake_deltat, wake_s, wake_dens, &
     21       zgam, zmax0, zmea, zpic, zsig, &
    2222       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl
    23    use dimphy
    24    use surface_data, only : type_ocean,ok_veget
    25    use pbl_surface_mod, only : ftsoil, pbl_surface_init,                    &
    26      &                            pbl_surface_final
    27       use fonte_neige_mod, only : fonte_neige_init, fonte_neige_final
    28 
    29    use infotrac ! new
    30    use control_mod
     23   USE dimphy
     24   USE surface_data, only : type_ocean,ok_veget
     25   USE pbl_surface_mod, only : ftsoil, pbl_surface_init, &
     26                                 pbl_surface_final
     27   USE fonte_neige_mod, only : fonte_neige_init, fonte_neige_final
     28
     29   USE infotrac ! new
     30   USE control_mod
    3131   USE indice_sol_mod
    3232   USE phyaqua_mod
     
    3737   USE mod_const_mpi, ONLY: comm_lmdz
    3838   USE physiq_mod, ONLY: physiq
     39   USE comvert_mod, ONLY: presnivs, ap, bp, dpres,nivsig, nivsigs, pa, &
     40                          preff
     41   USE temps_mod, ONLY: annee_ref, calend, day_end, day_ini, day_ref, &
     42                        itau_dyn, itau_phy, start_time
    3943
    4044      implicit none
    4145#include "dimensions.h"
    4246#include "YOMCST.h"
    43 #include "temps.h"
    4447!!#include "control.h"
    4548#include "clesphys.h"
     
    4750!#include "indicesol.h"
    4851
    49 #include "comvert.h"
    5052#include "compar1d.h"
    5153#include "flux_arp.h"
     
    246248      integer jcode
    247249      INTEGER read_climoz
     250!
     251      integer :: it_end ! iteration number of the last call
    248252!Al1
    249253      integer ecrit_slab_oc !1=ecrit,-1=lit,0=no file
    250254      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
    251259
    252260!=====================================================================
     
    745753        pbl_tke(:,2,:)=1.e-2
    746754        PRINT *, ' pbl_tke dans lmdz1d '
    747        DO nsrf = 1,4
    748          PRINT *,'pbl_tke(1,:,',nsrf,') ',pbl_tke(1,:,nsrf)
    749        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
    750760
    751761!>jyg
     
    777787        wake_pe = 0.
    778788        wake_s = 0.
     789        wake_dens = 0.
    779790        ale_bl = 0.
    780791        ale_bl_trig = 0.
     
    800811! t_ancien,q_ancien,,frugs(:,is_oce),clwcon(:,1),rnebcon(:,1),ratqs(:,1)
    801812! run_off_lic_0,pbl_tke(:,1:klev,nsrf), zmax0,f0,sig1,w01
    802 ! wake_deltat,wake_deltaq,wake_s,wake_cstar,wake_fip,wake_delta_pbl_tke(:,1:klev,nsrf)
     813! wake_deltat,wake_deltaq,wake_s,wake_dens,wake_cstar,
     814! wake_fip,wake_delta_pbl_tke(:,1:klev,nsrf)
    803815!
    804816! NB2: The content of the startphy.nc file depends on some flags defined in
     
    898910!=====================================================================
    899911           
    900       do while(it.le.nint(fnday*day_step))
     912      it_end = nint(fnday*day_step)
     913!test JLD     it_end = 10
     914      do while(it.le.it_end)
    901915
    902916       if (prt_level.ge.1) then
    903917         print*,'XXXXXXXXXXXXXXXXXXX ITAP,day,time=',                       &
    904      &             it,day,time,nint(fnday*day_step),day_step
     918     &             it,day,time,it_end,day_step
    905919         print*,'PAS DE TEMPS ',timestep
    906920       endif
    907921!Al1 demande de restartphy.nc
    908        if (it.eq.nint(fnday*day_step)) lastcall=.True.
     922       if (it.eq.it_end) lastcall=.True.
    909923
    910924!---------------------------------------------------------------------
     
    936950         write(*,*) 'firstcall,lastcall,phis',                               &
    937951     &               firstcall,lastcall,phis
     952       end if
     953       if (prt_level>=5) then
    938954         write(*,'(a10,2a4,4a13)') 'BEFOR1 IT=','it','l',                   &
    939955     &        'presniv','plev','play','phi'
     
    950966!---------------------------------------------------------------------
    951967       call physiq(ngrid,llm, &
    952                     firstcall,lastcall,timestep, &
    953                     plev,play,phi,phis,presnivs, &
    954                     u,v, rot, temp,q,omega2, &
    955                     du_phys,dv_phys,dt_phys,dq,dpsrf)
    956                 firstcall=.false.
    957 
    958 !---------------------------------------------------------------------
    959 ! Listing output for debug prt_level>=1
    960 !---------------------------------------------------------------------
    961         if (prt_level>=1) then
     968                    firstcall,lastcall,timestep, &
     969                    plev,play,phi,phis,presnivs, &
     970                    u,v, rot, temp,q,omega2, &
     971                    du_phys,dv_phys,dt_phys,dq,dpsrf)
     972                firstcall=.false.
     973
     974!---------------------------------------------------------------------
     975! Listing output for debug
     976!---------------------------------------------------------------------
     977        if (prt_level>=5) then
    962978          write(*,'(a11,2a4,4a13)') 'AFTER1 IT=','it','l',                  &
    963979     &        'presniv','plev','play','phi'
     
    9961012        endif
    9971013
    998       IF (prt_level >= 1) print*, 'fcoriolis, xlat,mxcalc ', &
     1014      IF (prt_level >= 5) print*, 'fcoriolis, xlat,mxcalc ', &
    9991015                                   fcoriolis, xlat,mxcalc
    10001016
     
    10461062!! Increment state variables
    10471063!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1064    IF (flag_inhib_forcing == 0) then ! if tendency of forcings should be added
     1065
    10481066! pour les cas sandu et astex, on reclacule u,v,q,temp et teta dans 1D_nudge_sandu_astex.h
    10491067! au dessus de 700hpa, on relaxe vers les profils initiaux
     
    10641082     &               +d_q_nudge(1:mxcalc,:) )
    10651083
    1066         if (prt_level.ge.1) then
     1084        if (prt_level.ge.3) then
    10671085          print *,                                                          &
    10681086     &    'physiq-> temp(1),dt_phys(1),d_th_adv(1),dt_cooling(1) ',         &
     
    11111129!cc        q(1:mxcalc,2)=tmpvar(1:mxcalc)
    11121130
     1131   END IF ! end if tendency of tendency should be added
     1132
    11131133!---------------------------------------------------------------------
    11141134!   Air temperature :
Note: See TracChangeset for help on using the changeset viewer.