Changeset 3592 for LMDZ6/trunk/libf


Ignore:
Timestamp:
Oct 27, 2019, 5:48:03 PM (5 years ago)
Author:
fhourdin
Message:

Plein de petites corrections pour le format commun.
Semble fonctionner correctement pour ARMCU/REF et RICO/REF

Location:
LMDZ6/trunk/libf/phylmd/dyn1d
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/dyn1d/1D_interp_cases.h

    r3541 r3592  
    1616     &       ,uw_cas,vw_cas,q1_cas,q2_cas,tke_cas                                           &
    1717!
    18      &       ,ts_prof_cas,plev_prof_cas,t_prof_cas,theta_prof_cas,thv_prof_cas  &
     18     &       ,ts_prof_cas,ps_prof_cas,plev_prof_cas,t_prof_cas,theta_prof_cas,thv_prof_cas  &
    1919     &       ,thl_prof_cas,qv_prof_cas,ql_prof_cas,qi_prof_cas                              &
    2020     &       ,u_prof_cas,v_prof_cas,ug_prof_cas,vg_prof_cas,vitw_prof_cas,omega_prof_cas    &
     
    163163
    164164      do l = 1, llm
     165
     166!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    165167! Modif w_mod_cas -> omega_mod_cas (MM+MPL 20170309)
    166        omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     168       !!! omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     169       omega(l) = omega_mod_cas(l)
     170       omega2(l)= omega_mod_cas(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     171
    167172       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
    168173
     
    170175        d_u_adv(l)=du_mod_cas(l)
    171176        d_v_adv(l)=dv_mod_cas(l)
    172         d_t_adv(l)=alpha*omega(l)/rcpd+dt_mod_cas(l)
     177        !!! d_t_adv(l)=alpha*omega(l)/rcpd+dt_mod_cas(l)
     178        !d_t_adv(l)=alpha*omega_mod_cas(l)/rcpd+dt_mod_cas(l)
     179        d_t_adv(l)=dt_mod_cas(l)
     180        !print*,'d_t_adv(l) ', alpha,omega_mod_cas(l),rcpd,dt_mod_cas(l)*86400,d_t_adv(l)*86400
    173181        d_q_adv(l,1)=dq_mod_cas(l)
    174182
    175         if (forc_w==1) then
    176            d_q_adv(l,1)=d_q_adv(l,1)-d_q_dyn_z(l)
    177            d_t_adv(l)=d_t_adv(l)-d_t_dyn_z(l)
    178            d_v_adv(l)=d_v_adv(l)-d_v_dyn_z(l)
    179            d_u_adv(l)=d_u_adv(l)-d_u_dyn_z(l)
    180         endif
     183!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     184!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     185!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     186!if (forc_w==1) then
     187!          d_q_adv(l,1)=d_q_adv(l,1)-d_q_dyn_z(l)
     188!          d_t_adv(l)=d_t_adv(l)-d_t_dyn_z(l)
     189!          d_v_adv(l)=d_v_adv(l)-d_v_dyn_z(l)
     190!          d_u_adv(l)=d_u_adv(l)-d_u_dyn_z(l)
     191!       endif
     192!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    181193         
    182194        if (trad.eq.1) then
  • LMDZ6/trunk/libf/phylmd/dyn1d/1D_read_forc_cases.h

    r3541 r3592  
    1717         call read_SCM_cas
    1818         write(*,*) 'Forcing read'
     19         print*,'PS ps_cas',ps_cas
    1920
    2021!Time interpolation for initial conditions using interpolation routine
     
    2930     &       ,uw_cas,vw_cas,q1_cas,q2_cas,tke_cas                                           &
    3031!
    31      &       ,ts_prof_cas,plev_prof_cas,t_prof_cas,theta_prof_cas,thv_prof_cas  &
     32     &       ,ts_prof_cas,ps_prof_cas,plev_prof_cas,t_prof_cas,theta_prof_cas,thv_prof_cas  &
    3233     &       ,thl_prof_cas,qv_prof_cas,ql_prof_cas,qi_prof_cas                              &
    3334     &       ,u_prof_cas,v_prof_cas,ug_prof_cas,vg_prof_cas,vitw_prof_cas,omega_prof_cas    &
     
    5859     &         ,dth_mod_cas,hth_mod_cas,vth_mod_cas,mxcalc)
    5960
    60 !       write(*,*) 'Profil initial forcing case interpole',t_mod
    6161
    6262! initial and boundary conditions :
    6363!      tsurf = ts_prof_cas
     64      psurf = ps_prof_cas
    6465      ts_cur = ts_prof_cas
    65       psurf=plev_prof_cas(1)
    66       write(*,*) 'SST initiale: ',tsurf
    6766      do l = 1, llm
    6867       temp(l) = t_mod_cas(l)
     
    8079!on applique le forcage total au premier pas de temps
    8180!attention: signe different de toga
    82        d_t_adv(l) = alpha*omega(l)/rcpd+(ht_mod_cas(l)+vt_mod_cas(l))
    83        d_t_adv(l) = alpha*omega(l)/rcpd+(ht_mod_cas(l)+vt_mod_cas(l))
     81       !d_t_adv(l) = alpha*omega(l)/rcpd+(ht_mod_cas(l)+vt_mod_cas(l))
     82       d_t_adv(l) = ht_mod_cas(l)+vt_mod_cas(l)
     83       print*,'DTADV MODIFIE '
     84!print*,'d_t_adv ',d_t_adv(1:20)*86400
    8485!      d_q_adv(l,1) = (hq_mod_cas(l)+vq_mod_cas(l))
    8586       d_q_adv(l,1) = dq_mod_cas(l)
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read2.F90

    r3541 r3592  
    840840       enddo
    841841!-----------------------------------------------------------------------
     842
    842843
    843844         return
  • LMDZ6/trunk/libf/phylmd/dyn1d/mod_1D_cases_read_std.F90

    r3541 r3592  
    221221
    222222        print*,'Allocations OK'
    223         call read_SCM (nid,nlev_cas,nt_cas,                                                                     &
     223        CALL read_SCM (nid,nlev_cas,nt_cas,                                                                     &
    224224     &     ap_cas,bp_cas,z_cas,plev_cas,zh_cas,plevh_cas,t_cas,th_cas,thv_cas,thl_cas,qv_cas,                    &
    225225     &     ql_cas,qi_cas,rh_cas,rv_cas,u_cas,v_cas,vitw_cas,omega_cas,ug_cas,vg_cas,du_cas,hu_cas,vu_cas,        &
     
    228228     &     uw_cas,vw_cas,q1_cas,q2_cas,orog_cas,albedo_cas,emiss_cas,t_skin_cas,q_skin_cas,mom_rough,heat_rough, &
    229229     &     o3_cas,rugos_cas,clay_cas,sand_cas)
    230         print*,'Read2 cas OK'
     230        print*,'read_SCM cas OK'
    231231        do ii=1,nlev_cas
    232         print*,'apres read2_cas, plev_cas=',ii,plev_cas(ii,1)
     232        print*,'apres read2_SCM, plev_cas=',ii,plev_cas(ii,1)
     233        !print*,'apres read_SCM, plev_cas=',ii,omega_cas(ii,nt_cas/2+1)
    233234        enddo
    234235
     
    302303
    303304!=====================================================================
    304       subroutine read_cas2(nid,nlevel,ntime                          &
     305      SUBROUTINE read_cas2(nid,nlevel,ntime                          &
    305306     &     ,zz,pp,temp,qv,rh,theta,rv,u,v,ug,vg,w,                   &
    306307     &     du,hu,vu,dv,hv,vv,dt,dtrad,ht,vt,dq,hq,vq,                     &
     
    421422
    422423         return
    423          end subroutine read_cas2
     424         END SUBROUTINE read_cas2
    424425!======================================================================
    425       subroutine read2_cas(nid,nlevel,ntime,                                       &
     426      SUBROUTINE read2_cas(nid,nlevel,ntime,                                       &
    426427     &     ap,bp,zz,pp,zzh,pph,temp,theta,thv,thl,qv,ql,qi,rh,rv,u,v,vitw,omega,ug,vg,&
    427428     &     du,hu,vu,dv,hv,vv,dt,ht,vt,dq,hq,vq,                                    &
     
    604605!-----------------------------------------------------------------------
    605606
     607        print*,'omega STD ', omega
     608        stop
    606609         return
    607          end subroutine read2_cas
     610         END SUBROUTINE read2_cas
    608611
    609612!======================================================================
    610       subroutine read_SCM(nid,nlevel,ntime,                                       &
     613      SUBROUTINE read_SCM(nid,nlevel,ntime,                                       &
    611614     &     ap,bp,zz,pp,zzh,pph,temp,theta,thv,thl,qv,ql,qi,rh,rv,u,v,vitw,omega,ug,vg,&
    612615     &     du,hu,vu,dv,hv,vv,dt,ht,vt,dq,hq,vq,                                    &
     
    665668!-----------------------------------------------------------------------
    666669
    667      print*,'ON EST LA'
    668670       do i=1,nbvar3d
    669671         ierr=NF_INQ_VARID(nid,name_var(i),var3didin(i))
     
    837839
    838840         return
    839          end subroutine read_SCM
     841         END SUBROUTINE read_SCM
    840842!======================================================================
    841843
     
    854856     &         ,uw_cas,vw_cas,q1_cas,q2_cas,tke_cas                               &
    855857!
    856      &         ,ts_prof_cas,plev_prof_cas,t_prof_cas,theta_prof_cas               &
     858     &         ,ts_prof_cas,ps_prof_cas,plev_prof_cas,t_prof_cas,theta_prof_cas               &
    857859     &         ,thv_prof_cas,thl_prof_cas,qv_prof_cas,ql_prof_cas,qi_prof_cas     &
    858860     &         ,u_prof_cas,v_prof_cas,ug_prof_cas,vg_prof_cas                     &
     
    913915        real dtrad_prof_cas(nlev_cas)
    914916        real dq_prof_cas(nlev_cas),hq_prof_cas(nlev_cas),vq_prof_cas(nlev_cas)
    915         real lat_prof_cas,sens_prof_cas,tke_prof_cas,ts_prof_cas,ustar_prof_cas
     917        real lat_prof_cas,sens_prof_cas,tke_prof_cas,ts_prof_cas,ps_prof_cas,ustar_prof_cas
    916918        real uw_prof_cas(nlev_cas),vw_prof_cas(nlev_cas),q1_prof_cas(nlev_cas),q2_prof_cas(nlev_cas)
    917919! local:
     
    10011003       ts_prof_cas = ts_cas(it_cas2)                                     &
    10021004     &          -frac*(ts_cas(it_cas2)-ts_cas(it_cas1))
     1005       ps_prof_cas = ps_cas(it_cas2)                                     &
     1006     &          -frac*(ps_cas(it_cas2)-ps_cas(it_cas1))
    10031007       ustar_prof_cas = ustar_cas(it_cas2)                               &
    10041008     &          -frac*(ustar_cas(it_cas2)-ustar_cas(it_cas1))
  • LMDZ6/trunk/libf/phylmd/dyn1d/scm.F90

    r3541 r3592  
    1414       zgam, zmax0, zmea, zpic, zsig, &
    1515       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl, ql_ancien, qs_ancien, &
    16        prlw_ancien, prsw_ancien, prw_ancien
     16       prlw_ancien, prsw_ancien, prw_ancien, &
     17       u10m,v10m,ale_wake,ale_bl_stat
     18
    1719 
    1820   USE dimphy
     
    518520
    519521#include "1D_read_forc_cases.h"
     522   print*,'A d_t_adv ',d_t_adv(1:20)*86400
    520523
    521524      if (forcing_GCM2SCM) then
     
    714717        v_ancien(1,:)=v(:)
    715718 
     719u10m=0.
     720v10m=0.
     721ale_wake=0.
     722ale_bl_stat=0.
     723
    716724!------------------------------------------------------------------------
    717725! Make file containing restart for the physics (startphy.nc)
     
    842850
    843851#include "1D_interp_cases.h"
    844 
    845       if (forcing_GCM2SCM) then
    846         write (*,*) 'forcing_GCM2SCM not yet implemented'
    847         stop 'in time loop'
    848       endif ! forcing_GCM2SCM
     852   ! Vertical advection
     853!  call lstendH(llm,nqtot,omega,dt_dyn,dq_dyn,q,temp,u,v,play)
     854!  print*,'B d_t_adv ',d_t_adv(1:20)*86400
     855!  print*,'B dt_dyn ',dt_dyn(1:20)*86400
     856!  print*,'B dt omega ',omega
     857   teta=temp*(pzero/play)**rkappa
     858   do l=2,llm-1
     859     dt_dyn(l)=-(omega(l)*(teta(l+1)-teta(l-1))/(play(l+1)-play(l-1)))/(pzero/play(l))**rkappa
     860     dq_dyn(l,1)=-omega(l)*(q(l+1,1)-q(l-1,1))/(play(l+1)-play(l-1))
     861   enddo
     862   d_t_adv(:)=d_t_adv(:)+dt_dyn(:)
     863   d_q_adv(:,1)=d_q_adv(:,1)+dq_dyn(:,1)
    849864
    850865!---------------------------------------------------------------------
     
    876891     &   presnivs(l),u(l),v(l),temp(l),q(l,1),q(l,2),omega2(l),l=1,llm)
    877892       endif
     893
     894       CALL iophys_ecrit('dtadv',klev,'dtadv','K/day',86400*d_t_adv)
     895       CALL iophys_ecrit('dtdyn',klev,'dtdyn','K/day',86400*dt_dyn)
    878896
    879897!---------------------------------------------------------------------
     
    911929
    912930       fcoriolis=2.*sin(rpi*xlat/180.)*romega
    913        if (forcing_radconv .or. forcing_fire) then
    914          fcoriolis=0.0
    915          dt_cooling=0.0
    916          d_t_adv=0.0
    917          d_q_adv=0.0
    918        endif
    919 !      print*, 'calcul de fcoriolis ', fcoriolis
    920 
    921        if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice            &
    922      &    .or.forcing_amma .or. forcing_type.eq.101) then
    923          fcoriolis=0.0 ; ug=0. ; vg=0.
    924        endif
    925 
    926        if(forcing_rico) then
    927           dt_cooling=0.
    928        endif
    929 
     931
     932!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     933!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     934!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     935!       if (forcing_radconv .or. forcing_fire) then
     936!         fcoriolis=0.0
     937!         dt_cooling=0.0
     938!         d_t_adv=0.0
     939!         d_q_adv=0.0
     940!       endif
     941!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     942
     943!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     944!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     945!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     946!      if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice            &
     947!    &    .or.forcing_amma .or. forcing_type.eq.101) then
     948!        fcoriolis=0.0 ; ug=0. ; vg=0.
     949!      endif
     950!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     951
     952!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     953!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     954!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     955!      if(forcing_rico) then
     956!         dt_cooling=0.
     957!      endif
     958!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     959
     960!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     961!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     962!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    930963!CRio:Attention modif sp??cifique cas de Caroline
    931       if (forcing_type==-1) then
    932          fcoriolis=0.
    933 !Nudging
    934        
     964!     if (forcing_type==-1) then
     965!        fcoriolis=0.
     966!       
    935967!on calcule dt_cooling
    936         do l=1,llm
    937         if (play(l).ge.20000.) then
    938             dt_cooling(l)=-1.5/86400.
    939         elseif ((play(l).ge.10000.).and.((play(l).lt.20000.))) then
    940             dt_cooling(l)=-1.5/86400.*(play(l)-10000.)/(10000.)-1./86400.*(20000.-play(l))/10000.*(temp(l)-200.)
    941         else
    942             dt_cooling(l)=-1.*(temp(l)-200.)/86400.
    943         endif
    944         enddo
    945 
    946       endif     
    947 !RC
    948       if (forcing_sandu) then
    949          ug(1:llm)=u_mod(1:llm)
    950          vg(1:llm)=v_mod(1:llm)
    951       endif
     968!       do l=1,llm
     969!       if (play(l).ge.20000.) then
     970!           dt_cooling(l)=-1.5/86400.
     971!       elseif ((play(l).ge.10000.).and.((play(l).lt.20000.))) then
     972!           dt_cooling(l)=-1.5/86400.*(play(l)-10000.)/(10000.)-1./86400.*(20000.-play(l))/10000.*(temp(l)-200.)
     973!       else
     974!           dt_cooling(l)=-1.*(temp(l)-200.)/86400.
     975!       endif
     976!       enddo
     977!
     978!     endif     
     979!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     980
     981!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     982!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     983!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     984!     if (forcing_sandu) then
     985!        ug(1:llm)=u_mod(1:llm)
     986!        vg(1:llm)=v_mod(1:llm)
     987!     endif
     988!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    952989
    953990      IF (prt_level >= 5) print*, 'fcoriolis, xlat,mxcalc ', &
     
    9921029      endif
    9931030!
    994        if (forcing_fire) THEN
    995 
    996 !let ww=if ( alt le 1100 ) then alt*-0.00001 else 0
    997 !let wt=if ( alt le 1100 ) then min( -3.75e-5 , -7.5e-8*alt)  else 0
    998 !let wq=if ( alt le 1100 ) then max( 1.5e-8 , 3e-11*alt)  else 0
    999            d_t_adv=0.
    1000            d_q_adv=0.
    1001            teta=temp*(pzero/play)**rkappa
    1002            d_t_adv=0.
    1003            d_q_adv=0.
    1004            do l=2,llm-1
    1005               if (zlay(l)<=1100) then
    1006                   wwww=-0.00001*zlay(l)
    1007                   d_t_adv(l)=-wwww*(teta(l)-teta(l+1))/(zlay(l)-zlay(l+1)) /(pzero/play(l))**rkappa
    1008                   d_q_adv(l,1:2)=-wwww*(q(l,1:2)-q(l+1,1:2))/(zlay(l)-zlay(l+1))
    1009                   d_t_adv(l)=d_t_adv(l)+min(-3.75e-5 , -7.5e-8*zlay(l))
    1010                   d_q_adv(l,1)=d_q_adv(l,1)+max( 1.5e-8 , 3e-11*zlay(l))
    1011               endif
    1012            enddo
    1013 
    1014         endif
     1031!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1032!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     1033!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1034!       if (forcing_fire) THEN
     1035!               print*,'Enlever cette section rapidement'
     1036!               stop
     1037!               
     1038!
     1039!!let ww=if ( alt le 1100 ) then alt*-0.00001 else 0
     1040!!let wt=if ( alt le 1100 ) then min( -3.75e-5 , -7.5e-8*alt)  else 0
     1041!!let wq=if ( alt le 1100 ) then max( 1.5e-8 , 3e-11*alt)  else 0
     1042!           d_t_adv=0.
     1043!           d_q_adv=0.
     1044!           teta=temp*(pzero/play)**rkappa
     1045!           d_t_adv=0.
     1046!           d_q_adv=0.
     1047!           do l=2,llm-1
     1048!              if (zlay(l)<=1100) then
     1049!                  wwww=-0.00001*zlay(l)
     1050!                  d_t_adv(l)=-wwww*(teta(l)-teta(l+1))/(zlay(l)-zlay(l+1)) /(pzero/play(l))**rkappa
     1051!                  d_q_adv(l,1:2)=-wwww*(q(l,1:2)-q(l+1,1:2))/(zlay(l)-zlay(l+1))
     1052!                  d_t_adv(l)=d_t_adv(l)+min(-3.75e-5 , -7.5e-8*zlay(l))
     1053!                  d_q_adv(l,1)=d_q_adv(l,1)+max( 1.5e-8 , 3e-11*zlay(l))
     1054!              endif
     1055!           enddo
     1056!
     1057!        endif
     1058!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    10151059
    10161060!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    10261070    IF (flag_inhib_forcing == 0) then ! if tendency of forcings should be added
    10271071
     1072!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1073!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     1074!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    10281075! pour les cas sandu et astex, on reclacule u,v,q,temp et teta dans 1D_nudge_sandu_astex.h
    10291076! au dessus de 700hpa, on relaxe vers les profils initiaux
    1030       if (forcing_sandu .OR. forcing_astex) then
    1031 #include "1D_nudge_sandu_astex.h"
    1032       else
     1077!     if (forcing_sandu .OR. forcing_astex) then
     1078!#include "1D_nudge_sandu_astex.h"
     1079!      else
     1080!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    10331081        u(1:mxcalc)=u(1:mxcalc) + timestep*(                                &
    10341082     &              du_phys(1:mxcalc)                                       &
     
    10621110     &             +dt_cooling(1:mxcalc))  ! Taux de chauffage ou refroid.
    10631111
    1064       endif  ! forcing_sandu or forcing_astex
     1112       print*,'MXCALC d_t_adv ',mxcalc,d_t_adv(1:20)*86400
     1113
     1114!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1115!! CONSERVE EN ATTENDANT QUE LE CAS EN QUESTION FONCTIONNE EN STD !!
     1116!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1117!     endif  ! forcing_sandu or forcing_astex
     1118!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    10651119
    10661120        teta=temp*(pzero/play)**rkappa
Note: See TracChangeset for help on using the changeset viewer.