Ignore:
Timestamp:
Jul 18, 2013, 10:20:28 AM (11 years ago)
Author:
Ehouarn Millour
Message:

Version testing basee sur la r1794


Testing release based on r1794

Location:
LMDZ5/branches/testing
Files:
11 edited
1 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phy1d/1DUTILS.h_no_writelim

    r1707 r1795  
    2727#include "compar1d.h"
    2828#include "flux_arp.h"
     29#include "tsoilnudge.h"
    2930#include "fcg_gcssold.h"
    3031#include "fcg_racmo.h"
     
    100101!             initial profiles from RICO idealized
    101102!             LS convergence imposed from  RICO (cst)
     103!         = 6 ==> forcing_amma = .true.
    102104!         = 40 ==> forcing_GCSSold = .true.
    103105!             initial profile from GCSS file
    104106!             LS convergence imposed from GCSS file
     107!         = 59 ==> forcing_sandu = .true.
     108!             initial profiles from sanduref file: see prof.inp.001
     109!             SST varying with time and divergence constante: see ifa_sanduref.txt file
     110!             Radiation has to be computed interactively
     111!         = 60 ==> forcing_astex = .true.
     112!             initial profiles from file: see prof.inp.001
     113!             SST,divergence,ug,vg,ufa,vfa varying with time : see ifa_astex.txt file
     114!             Radiation has to be computed interactively
     115!         = 61 ==> forcing_armcu = .true.
     116!             initial profiles from file: see prof.inp.001
     117!             sensible and latent heat flux imposed: see ifa_arm_cu_1.txt
     118!             large scale advective forcing & radiative tendencies applied below 1000m: see ifa_arm_cu_2.txt
     119!             use geostrophic wind ug=10m/s vg=0m/s. Duration of the case 53100s
     120!             Radiation to be switched off
    105121!
    106122       forcing_type = 0
     
    126142       CALL getin('ok_flux_surf',ok_flux_surf)
    127143
     144!Config  Key  = ok_old_disvert
     145!Config  Desc = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
     146!Config  Def  = false
     147!Config  Help = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
     148       ok_old_disvert = .FALSE.
     149       CALL getin('ok_old_disvert',ok_old_disvert)
     150
    128151!Config  Key  = time_ini
    129152!Config  Desc = meaningless in this  case
     
    227250       zpicinp = 300.
    228251       CALL getin('zpicinp',zpicinp)
     252!Config key = nudge_tsoil
     253!Config  Desc = activation of soil temperature nudging
     254!Config  Def  = .FALSE.
     255!Config  Help = ...
     256
     257       nudge_tsoil=.FALSE.
     258       CALL getin('nudge_tsoil',nudge_tsoil)
     259
     260!Config key = isoil_nudge
     261!Config  Desc = level number where soil temperature is nudged
     262!Config  Def  = 3
     263!Config  Help = ...
     264
     265       isoil_nudge=3
     266       CALL getin('isoil_nudge',isoil_nudge)
     267
     268!Config key = Tsoil_nudge
     269!Config  Desc = target temperature for tsoil(isoil_nudge)
     270!Config  Def  = 300.
     271!Config  Help = ...
     272
     273       Tsoil_nudge=300.
     274       CALL getin('Tsoil_nudge',Tsoil_nudge)
     275
     276!Config key = tau_soil_nudge
     277!Config  Desc = nudging relaxation time for tsoil
     278!Config  Def  = 3600.
     279!Config  Help = ...
     280
     281       tau_soil_nudge=3600.
     282       CALL getin('tau_soil_nudge',tau_soil_nudge)
     283
     284
    229285
    230286
     
    250306      write(lunout,*)' qsolinp = ', qsolinp
    251307      write(lunout,*)' zpicinp = ', zpicinp
     308      write(lunout,*)' nudge_tsoil = ', nudge_tsoil
     309      write(lunout,*)' isoil_nudge = ', isoil_nudge
     310      write(lunout,*)' Tsoil_nudge = ', Tsoil_nudge
     311      write(lunout,*)' tau_soil_nudge = ', tau_soil_nudge
    252312      IF (forcing_type .eq.40) THEN
    253313        write(lunout,*) '--- Forcing type GCSS Old --- with:'
     
    703763      RETURN
    704764      END
    705       subroutine scopy(n,sx,incx,sy,incy)
    706 !
    707       IMPLICIT NONE
    708 !
    709       integer n,incx,incy,ix,iy,i
    710       real sx((n-1)*incx+1),sy((n-1)*incy+1)
    711 !
    712       iy=1
    713       ix=1
    714       do 10 i=1,n
    715          sy(iy)=sx(ix)
    716          ix=ix+incx
    717          iy=iy+incy
    718 10    continue
    719 !
    720       return
    721       end
    722765      subroutine wrgradsfi(if,nl,field,name,titlevar)
    723766      implicit none
     
    956999      END
    9571000 
    958       SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
    959  
     1001      SUBROUTINE disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
     1002 
     1003!    Ancienne version disvert dont on a modifie nom pour utiliser
     1004!    le disvert de dyn3d (qui permet d'utiliser grille avec ab,bp imposes)
     1005!    (MPL 18092012)
     1006!
    9601007!    Auteur :  P. Le Van .
    9611008!
     
    14021449          end
    14031450
     1451c-------------------------------------------------------------------------
     1452      SUBROUTINE read_sandu(fich_sandu,nlev_sandu,nt_sandu,ts_sandu)
     1453      implicit none
     1454
     1455c-------------------------------------------------------------------------
     1456c Read I.SANDU case forcing data
     1457c-------------------------------------------------------------------------
     1458
     1459      integer nlev_sandu,nt_sandu
     1460      real ts_sandu(nt_sandu)
     1461      character*80 fich_sandu
     1462
     1463      integer no,l,k,ip
     1464      real riy,rim,rid,rih,bid
     1465
     1466      integer iy,im,id,ih
     1467
     1468       real plev_min
     1469
     1470       plev_min = 55000.  ! pas de tendance de vap. d eau au-dessus de 55 hPa
     1471
     1472      open(21,file=trim(fich_sandu),form='formatted')
     1473      read(21,'(a)')
     1474      do ip = 1, nt_sandu
     1475      read(21,'(a)')
     1476      read(21,'(a)')
     1477      read(21,223) iy, im, id, ih, ts_sandu(ip)
     1478      print *,'ts=',iy,im,id,ih,ip,ts_sandu(ip)
     1479      enddo
     1480      close(21)
     1481
     1482  223 format(4i3,f8.2)
     1483  226 format(f7.1,1x,10f8.2)
     1484  227 format(f7.1,1x,1p,4e11.3)
     1485  230 format(6f9.3,4e11.3)
     1486
     1487          return
     1488          end
     1489
     1490!=====================================================================
     1491c-------------------------------------------------------------------------
     1492      SUBROUTINE read_astex(fich_astex,nlev_astex,nt_astex,div_astex,
     1493     : ts_astex,ug_astex,vg_astex,ufa_astex,vfa_astex)
     1494      implicit none
     1495
     1496c-------------------------------------------------------------------------
     1497c Read Astex case forcing data
     1498c-------------------------------------------------------------------------
     1499
     1500      integer nlev_astex,nt_astex
     1501      real div_astex(nt_astex),ts_astex(nt_astex),ug_astex(nt_astex)
     1502      real vg_astex(nt_astex),ufa_astex(nt_astex),vfa_astex(nt_astex)
     1503      character*80 fich_astex
     1504
     1505      integer no,l,k,ip
     1506      real riy,rim,rid,rih,bid
     1507
     1508      integer iy,im,id,ih
     1509
     1510       real plev_min
     1511
     1512       plev_min = 55000.  ! pas de tendance de vap. d eau au-dessus de 55 hPa
     1513
     1514      open(21,file=trim(fich_astex),form='formatted')
     1515      read(21,'(a)')
     1516      read(21,'(a)')
     1517      do ip = 1, nt_astex
     1518      read(21,'(a)')
     1519      read(21,'(a)')
     1520      read(21,223) iy, im, id, ih, div_astex(ip),ts_astex(ip),
     1521     :ug_astex(ip),vg_astex(ip),ufa_astex(ip),vfa_astex(ip)
     1522      ts_astex(ip)=ts_astex(ip)+273.15
     1523      print *,'ts=',iy,im,id,ih,ip,div_astex(ip),ts_astex(ip),
     1524     :ug_astex(ip),vg_astex(ip),ufa_astex(ip),vg_astex(ip)
     1525      enddo
     1526      close(21)
     1527
     1528  223 format(4i3,e13.2,f7.2,f7.3,f7.2,f7.3,f7.2)
     1529  226 format(f7.1,1x,10f8.2)
     1530  227 format(f7.1,1x,1p,4e11.3)
     1531  230 format(6f9.3,4e11.3)
     1532
     1533          return
     1534          end
    14041535!=====================================================================
    14051536      subroutine read_twpice(fich_twpice,nlevel,ntime
     
    18842015       return
    18852016       end
     2017!=====================================================================
     2018
     2019       SUBROUTINE interp_sandu_vertical(play,nlev_sandu,plev_prof
     2020     :         ,t_prof,thl_prof,q_prof,u_prof,v_prof,w_prof
     2021     :         ,omega_prof,o3mmr_prof
     2022     :         ,t_mod,thl_mod,q_mod,u_mod,v_mod,w_mod
     2023     :         ,omega_mod,o3mmr_mod,mxcalc)
     2024
     2025       implicit none
     2026
     2027#include "dimensions.h"
     2028
     2029c-------------------------------------------------------------------------
     2030c Vertical interpolation of SANDUREF forcing data onto model levels
     2031c-------------------------------------------------------------------------
     2032
     2033       integer nlevmax
     2034       parameter (nlevmax=41)
     2035       integer nlev_sandu,mxcalc
     2036!       real play(llm), plev_prof(nlevmax)
     2037!       real t_prof(nlevmax),q_prof(nlevmax)
     2038!       real u_prof(nlevmax),v_prof(nlevmax), w_prof(nlevmax)
     2039!       real ht_prof(nlevmax),vt_prof(nlevmax)
     2040!       real hq_prof(nlevmax),vq_prof(nlevmax)
     2041
     2042       real play(llm), plev_prof(nlev_sandu)
     2043       real t_prof(nlev_sandu),thl_prof(nlev_sandu),q_prof(nlev_sandu)
     2044       real u_prof(nlev_sandu),v_prof(nlev_sandu), w_prof(nlev_sandu)
     2045       real omega_prof(nlev_sandu),o3mmr_prof(nlev_sandu)
     2046
     2047       real t_mod(llm),thl_mod(llm),q_mod(llm)
     2048       real u_mod(llm),v_mod(llm), w_mod(llm)
     2049       real omega_mod(llm),o3mmr_mod(llm)
     2050
     2051       integer l,k,k1,k2,kp
     2052       real aa,frac,frac1,frac2,fact
     2053
     2054       do l = 1, llm
     2055
     2056        if (play(l).ge.plev_prof(nlev_sandu)) then
     2057
     2058        mxcalc=l
     2059         k1=0
     2060         k2=0
     2061
     2062         if (play(l).le.plev_prof(1)) then
     2063
     2064         do k = 1, nlev_sandu-1
     2065          if (play(l).le.plev_prof(k)
     2066     :       .and. play(l).gt.plev_prof(k+1)) then
     2067            k1=k
     2068            k2=k+1
     2069          endif
     2070         enddo
     2071
     2072         if (k1.eq.0 .or. k2.eq.0) then
     2073          write(*,*) 'PB! k1, k2 = ',k1,k2
     2074          write(*,*) 'l,play(l) = ',l,play(l)/100
     2075         do k = 1, nlev_sandu-1
     2076          write(*,*) 'k,plev_prof(k) = ',k,plev_prof(k)/100
     2077         enddo
     2078         endif
     2079
     2080         frac = (plev_prof(k2)-play(l))/(plev_prof(k2)-plev_prof(k1))
     2081         t_mod(l)= t_prof(k2) - frac*(t_prof(k2)-t_prof(k1))
     2082         thl_mod(l)= thl_prof(k2) - frac*(thl_prof(k2)-thl_prof(k1))
     2083         q_mod(l)= q_prof(k2) - frac*(q_prof(k2)-q_prof(k1))
     2084         u_mod(l)= u_prof(k2) - frac*(u_prof(k2)-u_prof(k1))
     2085         v_mod(l)= v_prof(k2) - frac*(v_prof(k2)-v_prof(k1))
     2086         w_mod(l)= w_prof(k2) - frac*(w_prof(k2)-w_prof(k1))
     2087         omega_mod(l)=omega_prof(k2)-
     2088     :      frac*(omega_prof(k2)-omega_prof(k1))
     2089         o3mmr_mod(l)=o3mmr_prof(k2)-
     2090     :      frac*(o3mmr_prof(k2)-o3mmr_prof(k1))
     2091
     2092         else !play>plev_prof(1)
     2093
     2094         k1=1
     2095         k2=2
     2096         frac1 = (play(l)-plev_prof(k2))/(plev_prof(k1)-plev_prof(k2))
     2097         frac2 = (play(l)-plev_prof(k1))/(plev_prof(k1)-plev_prof(k2))
     2098         t_mod(l)= frac1*t_prof(k1) - frac2*t_prof(k2)
     2099         thl_mod(l)= frac1*thl_prof(k1) - frac2*thl_prof(k2)
     2100         q_mod(l)= frac1*q_prof(k1) - frac2*q_prof(k2)
     2101         u_mod(l)= frac1*u_prof(k1) - frac2*u_prof(k2)
     2102         v_mod(l)= frac1*v_prof(k1) - frac2*v_prof(k2)
     2103         w_mod(l)= frac1*w_prof(k1) - frac2*w_prof(k2)
     2104         omega_mod(l)= frac1*omega_prof(k1) - frac2*omega_prof(k2)
     2105         o3mmr_mod(l)= frac1*o3mmr_prof(k1) - frac2*o3mmr_prof(k2)
     2106
     2107         endif ! play.le.plev_prof(1)
     2108
     2109        else ! above max altitude of forcing file
     2110
     2111cjyg
     2112         fact=20.*(plev_prof(nlev_sandu)-play(l))/plev_prof(nlev_sandu) !jyg
     2113         fact = max(fact,0.)                                           !jyg
     2114         fact = exp(-fact)                                             !jyg
     2115         t_mod(l)= t_prof(nlev_sandu)                                   !jyg
     2116         thl_mod(l)= thl_prof(nlev_sandu)                                   !jyg
     2117         q_mod(l)= q_prof(nlev_sandu)*fact                              !jyg
     2118         u_mod(l)= u_prof(nlev_sandu)*fact                              !jyg
     2119         v_mod(l)= v_prof(nlev_sandu)*fact                              !jyg
     2120         w_mod(l)= w_prof(nlev_sandu)*fact                              !jyg
     2121         omega_mod(l)= omega_prof(nlev_sandu)*fact                      !jyg
     2122         o3mmr_mod(l)= o3mmr_prof(nlev_sandu)*fact                      !jyg
     2123
     2124        endif ! play
     2125
     2126       enddo ! l
     2127
     2128       do l = 1,llm
     2129!      print *,'t_mod(l),thl_mod(l),q_mod(l),u_mod(l),v_mod(l) ',
     2130!    $        l,t_mod(l),thl_mod(l),q_mod(l),u_mod(l),v_mod(l)
     2131       enddo
     2132
     2133          return
     2134          end
     2135!=====================================================================
     2136       SUBROUTINE interp_astex_vertical(play,nlev_astex,plev_prof
     2137     :         ,t_prof,thl_prof,qv_prof,ql_prof,qt_prof,u_prof,v_prof
     2138     :         ,w_prof,tke_prof,o3mmr_prof
     2139     :         ,t_mod,thl_mod,qv_mod,ql_mod,qt_mod,u_mod,v_mod,w_mod
     2140     :         ,tke_mod,o3mmr_mod,mxcalc)
     2141
     2142       implicit none
     2143
     2144#include "dimensions.h"
     2145
     2146c-------------------------------------------------------------------------
     2147c Vertical interpolation of Astex forcing data onto model levels
     2148c-------------------------------------------------------------------------
     2149
     2150       integer nlevmax
     2151       parameter (nlevmax=41)
     2152       integer nlev_astex,mxcalc
     2153!       real play(llm), plev_prof(nlevmax)
     2154!       real t_prof(nlevmax),qv_prof(nlevmax)
     2155!       real u_prof(nlevmax),v_prof(nlevmax), w_prof(nlevmax)
     2156!       real ht_prof(nlevmax),vt_prof(nlevmax)
     2157!       real hq_prof(nlevmax),vq_prof(nlevmax)
     2158
     2159       real play(llm), plev_prof(nlev_astex)
     2160       real t_prof(nlev_astex),thl_prof(nlev_astex),qv_prof(nlev_astex)
     2161       real u_prof(nlev_astex),v_prof(nlev_astex), w_prof(nlev_astex)
     2162       real o3mmr_prof(nlev_astex),ql_prof(nlev_astex)
     2163       real qt_prof(nlev_astex),tke_prof(nlev_astex)
     2164
     2165       real t_mod(llm),thl_mod(llm),qv_mod(llm)
     2166       real u_mod(llm),v_mod(llm), w_mod(llm),tke_mod(llm)
     2167       real o3mmr_mod(llm),ql_mod(llm),qt_mod(llm)
     2168
     2169       integer l,k,k1,k2,kp
     2170       real aa,frac,frac1,frac2,fact
     2171
     2172       do l = 1, llm
     2173
     2174        if (play(l).ge.plev_prof(nlev_astex)) then
     2175
     2176        mxcalc=l
     2177         k1=0
     2178         k2=0
     2179
     2180         if (play(l).le.plev_prof(1)) then
     2181
     2182         do k = 1, nlev_astex-1
     2183          if (play(l).le.plev_prof(k)
     2184     :       .and. play(l).gt.plev_prof(k+1)) then
     2185            k1=k
     2186            k2=k+1
     2187          endif
     2188         enddo
     2189
     2190         if (k1.eq.0 .or. k2.eq.0) then
     2191          write(*,*) 'PB! k1, k2 = ',k1,k2
     2192          write(*,*) 'l,play(l) = ',l,play(l)/100
     2193         do k = 1, nlev_astex-1
     2194          write(*,*) 'k,plev_prof(k) = ',k,plev_prof(k)/100
     2195         enddo
     2196         endif
     2197
     2198         frac = (plev_prof(k2)-play(l))/(plev_prof(k2)-plev_prof(k1))
     2199         t_mod(l)= t_prof(k2) - frac*(t_prof(k2)-t_prof(k1))
     2200         thl_mod(l)= thl_prof(k2) - frac*(thl_prof(k2)-thl_prof(k1))
     2201         qv_mod(l)= qv_prof(k2) - frac*(qv_prof(k2)-qv_prof(k1))
     2202         ql_mod(l)= ql_prof(k2) - frac*(ql_prof(k2)-ql_prof(k1))
     2203         qt_mod(l)= qt_prof(k2) - frac*(qt_prof(k2)-qt_prof(k1))
     2204         u_mod(l)= u_prof(k2) - frac*(u_prof(k2)-u_prof(k1))
     2205         v_mod(l)= v_prof(k2) - frac*(v_prof(k2)-v_prof(k1))
     2206         w_mod(l)= w_prof(k2) - frac*(w_prof(k2)-w_prof(k1))
     2207         tke_mod(l)= tke_prof(k2) - frac*(tke_prof(k2)-tke_prof(k1))
     2208         o3mmr_mod(l)=o3mmr_prof(k2)-
     2209     :      frac*(o3mmr_prof(k2)-o3mmr_prof(k1))
     2210
     2211         else !play>plev_prof(1)
     2212
     2213         k1=1
     2214         k2=2
     2215         frac1 = (play(l)-plev_prof(k2))/(plev_prof(k1)-plev_prof(k2))
     2216         frac2 = (play(l)-plev_prof(k1))/(plev_prof(k1)-plev_prof(k2))
     2217         t_mod(l)= frac1*t_prof(k1) - frac2*t_prof(k2)
     2218         thl_mod(l)= frac1*thl_prof(k1) - frac2*thl_prof(k2)
     2219         qv_mod(l)= frac1*qv_prof(k1) - frac2*qv_prof(k2)
     2220         ql_mod(l)= frac1*ql_prof(k1) - frac2*ql_prof(k2)
     2221         qt_mod(l)= frac1*qt_prof(k1) - frac2*qt_prof(k2)
     2222         u_mod(l)= frac1*u_prof(k1) - frac2*u_prof(k2)
     2223         v_mod(l)= frac1*v_prof(k1) - frac2*v_prof(k2)
     2224         w_mod(l)= frac1*w_prof(k1) - frac2*w_prof(k2)
     2225         tke_mod(l)= frac1*tke_prof(k1) - frac2*tke_prof(k2)
     2226         o3mmr_mod(l)= frac1*o3mmr_prof(k1) - frac2*o3mmr_prof(k2)
     2227
     2228         endif ! play.le.plev_prof(1)
     2229
     2230        else ! above max altitude of forcing file
     2231
     2232cjyg
     2233         fact=20.*(plev_prof(nlev_astex)-play(l))/plev_prof(nlev_astex) !jyg
     2234         fact = max(fact,0.)                                           !jyg
     2235         fact = exp(-fact)                                             !jyg
     2236         t_mod(l)= t_prof(nlev_astex)                                   !jyg
     2237         thl_mod(l)= thl_prof(nlev_astex)                                   !jyg
     2238         qv_mod(l)= qv_prof(nlev_astex)*fact                              !jyg
     2239         ql_mod(l)= ql_prof(nlev_astex)*fact                              !jyg
     2240         qt_mod(l)= qt_prof(nlev_astex)*fact                              !jyg
     2241         u_mod(l)= u_prof(nlev_astex)*fact                              !jyg
     2242         v_mod(l)= v_prof(nlev_astex)*fact                              !jyg
     2243         w_mod(l)= w_prof(nlev_astex)*fact                              !jyg
     2244         tke_mod(l)= tke_prof(nlev_astex)*fact                              !jyg
     2245         o3mmr_mod(l)= o3mmr_prof(nlev_astex)*fact                      !jyg
     2246
     2247        endif ! play
     2248
     2249       enddo ! l
     2250
     2251       do l = 1,llm
     2252!      print *,'t_mod(l),thl_mod(l),qv_mod(l),u_mod(l),v_mod(l) ',
     2253!    $        l,t_mod(l),thl_mod(l),qv_mod(l),u_mod(l),v_mod(l)
     2254       enddo
     2255
     2256          return
     2257          end
    18862258
    18872259!======================================================================
     
    20482420          end
    20492421
     2422!======================================================================
     2423        SUBROUTINE interp_sandu_time(day,day1,annee_ref
     2424     i             ,year_ini_sandu,day_ini_sandu,nt_sandu,dt_sandu
     2425     i             ,nlev_sandu,ts_sandu,ts_prof)
     2426        implicit none
     2427
     2428!---------------------------------------------------------------------------------------
     2429! Time interpolation of a 2D field to the timestep corresponding to day
     2430!
     2431! day: current julian day (e.g. 717538.2)
     2432! day1: first day of the simulation
     2433! nt_sandu: total nb of data in the forcing (e.g. 13 for Sanduref)
     2434! dt_sandu: total time interval (in sec) between 2 forcing data (e.g. 6h for Sanduref)
     2435!---------------------------------------------------------------------------------------
     2436! inputs:
     2437        integer annee_ref
     2438        integer nt_sandu,nlev_sandu
     2439        integer year_ini_sandu
     2440        real day, day1,day_ini_sandu,dt_sandu
     2441        real ts_sandu(nt_sandu)
     2442! outputs:
     2443        real ts_prof
     2444! local:
     2445        integer it_sandu1, it_sandu2,k
     2446        real timeit,time_sandu1,time_sandu2,frac
     2447! Check that initial day of the simulation consistent with SANDU period:
     2448       if (annee_ref.ne.2006 ) then
     2449        print*,'Pour SANDUREF, annee_ref doit etre 2006 '
     2450        print*,'Changer annee_ref dans run.def'
     2451        stop
     2452       endif
     2453!      if (annee_ref.eq.2006 .and. day1.lt.day_ini_sandu) then
     2454!       print*,'SANDUREF debute le 15 Juillet 2006 (jour julien=196)'
     2455!       print*,'Changer dayref dans run.def'
     2456!       stop
     2457!      endif
     2458
     2459! Determine timestep relative to the 1st day of TOGA-COARE:
     2460!       timeit=(day-day1)*86400.
     2461!       if (annee_ref.eq.1992) then
     2462!        timeit=(day-day_ini_sandu)*86400.
     2463!       else
     2464!        timeit=(day+61.-1.)*86400. ! 61 days between Nov01 and Dec31 1992
     2465!       endif
     2466      timeit=(day-day_ini_sandu)*86400
     2467
     2468! Determine the closest observation times:
     2469       it_sandu1=INT(timeit/dt_sandu)+1
     2470       it_sandu2=it_sandu1 + 1
     2471       time_sandu1=(it_sandu1-1)*dt_sandu
     2472       time_sandu2=(it_sandu2-1)*dt_sandu
     2473       print *,'timeit day day_ini_sandu',timeit,day,day_ini_sandu
     2474       print *,'it_sandu1,it_sandu2,time_sandu1,time_sandu2',
     2475     .          it_sandu1,it_sandu2,time_sandu1,time_sandu2
     2476
     2477       if (it_sandu1 .ge. nt_sandu) then
     2478        write(*,*) 'PB-stop: day, it_sandu1, it_sandu2, timeit: '
     2479     :        ,day,it_sandu1,it_sandu2,timeit/86400.
     2480        stop
     2481       endif
     2482
     2483! time interpolation:
     2484       frac=(time_sandu2-timeit)/(time_sandu2-time_sandu1)
     2485       frac=max(frac,0.0)
     2486
     2487       ts_prof = ts_sandu(it_sandu2)
     2488     :          -frac*(ts_sandu(it_sandu2)-ts_sandu(it_sandu1))
     2489
     2490         print*,
     2491     :'day,annee_ref,day_ini_sandu,timeit,it_sandu1,it_sandu2,SST:',
     2492     :day,annee_ref,day_ini_sandu,timeit/86400.,it_sandu1,
     2493     :it_sandu2,ts_prof
     2494
     2495        return
     2496        END
    20502497!=====================================================================
    20512498c-------------------------------------------------------------------------
     
    22092656          end
    22102657 
     2658!======================================================================
     2659        SUBROUTINE interp_astex_time(day,day1,annee_ref
     2660     i             ,year_ini_astex,day_ini_astex,nt_astex,dt_astex
     2661     i             ,nlev_astex,div_astex,ts_astex,ug_astex,vg_astex
     2662     i             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof
     2663     i             ,ufa_prof,vfa_prof)
     2664        implicit none
     2665
     2666!---------------------------------------------------------------------------------------
     2667! Time interpolation of a 2D field to the timestep corresponding to day
     2668!
     2669! day: current julian day (e.g. 717538.2)
     2670! day1: first day of the simulation
     2671! nt_astex: total nb of data in the forcing (e.g. 41 for Astex)
     2672! dt_astex: total time interval (in sec) between 2 forcing data (e.g. 1h for Astex)
     2673!---------------------------------------------------------------------------------------
     2674
     2675! inputs:
     2676        integer annee_ref
     2677        integer nt_astex,nlev_astex
     2678        integer year_ini_astex
     2679        real day, day1,day_ini_astex,dt_astex
     2680        real div_astex(nt_astex),ts_astex(nt_astex),ug_astex(nt_astex)
     2681        real vg_astex(nt_astex),ufa_astex(nt_astex),vfa_astex(nt_astex)
     2682! outputs:
     2683        real div_prof,ts_prof,ug_prof,vg_prof,ufa_prof,vfa_prof
     2684! local:
     2685        integer it_astex1, it_astex2,k
     2686        real timeit,time_astex1,time_astex2,frac
     2687
     2688! Check that initial day of the simulation consistent with ASTEX period:
     2689       if (annee_ref.ne.1992 ) then
     2690        print*,'Pour Astex, annee_ref doit etre 1992 '
     2691        print*,'Changer annee_ref dans run.def'
     2692        stop
     2693       endif
     2694       if (annee_ref.eq.1992 .and. day1.lt.day_ini_astex) then
     2695        print*,'Astex debute le 13 Juin 1992 (jour julien=165)'
     2696        print*,'Changer dayref dans run.def'
     2697        stop
     2698       endif
     2699
     2700! Determine timestep relative to the 1st day of TOGA-COARE:
     2701!       timeit=(day-day1)*86400.
     2702!       if (annee_ref.eq.1992) then
     2703!        timeit=(day-day_ini_astex)*86400.
     2704!       else
     2705!        timeit=(day+2.-1.)*86400. ! 2 days between Jun13 and Jun15 1992
     2706!       endif
     2707      timeit=(day-day_ini_astex)*86400
     2708
     2709! Determine the closest observation times:
     2710       it_astex1=INT(timeit/dt_astex)+1
     2711       it_astex2=it_astex1 + 1
     2712       time_astex1=(it_astex1-1)*dt_astex
     2713       time_astex2=(it_astex2-1)*dt_astex
     2714       print *,'timeit day day_ini_astex',timeit,day,day_ini_astex
     2715       print *,'it_astex1,it_astex2,time_astex1,time_astex2',
     2716     .          it_astex1,it_astex2,time_astex1,time_astex2
     2717
     2718       if (it_astex1 .ge. nt_astex) then
     2719        write(*,*) 'PB-stop: day, it_astex1, it_astex2, timeit: '
     2720     :        ,day,it_astex1,it_astex2,timeit/86400.
     2721        stop
     2722       endif
     2723
     2724! time interpolation:
     2725       frac=(time_astex2-timeit)/(time_astex2-time_astex1)
     2726       frac=max(frac,0.0)
     2727
     2728       div_prof = div_astex(it_astex2)
     2729     :          -frac*(div_astex(it_astex2)-div_astex(it_astex1))
     2730       ts_prof = ts_astex(it_astex2)
     2731     :          -frac*(ts_astex(it_astex2)-ts_astex(it_astex1))
     2732       ug_prof = ug_astex(it_astex2)
     2733     :          -frac*(ug_astex(it_astex2)-ug_astex(it_astex1))
     2734       vg_prof = vg_astex(it_astex2)
     2735     :          -frac*(vg_astex(it_astex2)-vg_astex(it_astex1))
     2736       ufa_prof = ufa_astex(it_astex2)
     2737     :          -frac*(ufa_astex(it_astex2)-ufa_astex(it_astex1))
     2738       vfa_prof = vfa_astex(it_astex2)
     2739     :          -frac*(vfa_astex(it_astex2)-vfa_astex(it_astex1))
     2740
     2741         print*,
     2742     :'day,annee_ref,day_ini_astex,timeit,it_astex1,it_astex2,SST:',
     2743     :day,annee_ref,day_ini_astex,timeit/86400.,it_astex1,
     2744     :it_astex2,div_prof,ts_prof,ug_prof,vg_prof,ufa_prof,vfa_prof
     2745
     2746        return
     2747        END
     2748
    22112749!======================================================================
    22122750        SUBROUTINE interp_toga_time(day,day1,annee_ref
     
    24793017        return
    24803018        end
     3019!======================================================================
     3020      subroutine readprofile_sandu(nlev_max,kmax,height,pprof,tprof,
     3021     .       thlprof,qprof,uprof,vprof,wprof,omega,o3mmr)
     3022!======================================================================
     3023      implicit none
     3024
     3025        integer nlev_max,kmax,kmax2
     3026        logical :: llesread = .true.
     3027
     3028        real height(nlev_max),pprof(nlev_max),tprof(nlev_max),
     3029     .  thlprof(nlev_max),
     3030     .  qprof(nlev_max),uprof(nlev_max),vprof(nlev_max),
     3031     .  wprof(nlev_max),omega(nlev_max),o3mmr(nlev_max)
     3032
     3033        integer, parameter :: ilesfile=1
     3034        integer :: ierr,irad,imax,jtot,k
     3035        logical :: lmoist,lcoriol,ltimedep
     3036        real :: xsize,ysize
     3037        real :: ustin,wsvsurf,timerad
     3038        character(80) :: chmess
     3039
     3040        if(.not.(llesread)) return
     3041
     3042       open (ilesfile,file='prof.inp.001',status='old',iostat=ierr)
     3043        if (ierr /= 0) stop 'ERROR:Prof.inp does not exist'
     3044        read (ilesfile,*) kmax
     3045        do k=1,kmax
     3046          read (ilesfile,*) height(k),pprof(k),  tprof(k),thlprof(k),
     3047     .                      qprof (k),uprof(k),  vprof(k),  wprof(k),
     3048     .                      omega (k),o3mmr(k)
     3049        enddo
     3050        close(ilesfile)
     3051
     3052        return
     3053        end
     3054
     3055!======================================================================
     3056      subroutine readprofile_astex(nlev_max,kmax,height,pprof,tprof,
     3057     .    thlprof,qvprof,qlprof,qtprof,uprof,vprof,wprof,tkeprof,o3mmr)
     3058!======================================================================
     3059      implicit none
     3060
     3061        integer nlev_max,kmax,kmax2
     3062        logical :: llesread = .true.
     3063
     3064        real height(nlev_max),pprof(nlev_max),tprof(nlev_max),
     3065     .  thlprof(nlev_max),qlprof(nlev_max),qtprof(nlev_max),
     3066     .  qvprof(nlev_max),uprof(nlev_max),vprof(nlev_max),
     3067     .  wprof(nlev_max),tkeprof(nlev_max),o3mmr(nlev_max)
     3068
     3069        integer, parameter :: ilesfile=1
     3070        integer :: ierr,irad,imax,jtot,k
     3071        logical :: lmoist,lcoriol,ltimedep
     3072        real :: xsize,ysize
     3073        real :: ustin,wsvsurf,timerad
     3074        character(80) :: chmess
     3075
     3076        if(.not.(llesread)) return
     3077
     3078       open (ilesfile,file='prof.inp.001',status='old',iostat=ierr)
     3079        if (ierr /= 0) stop 'ERROR:Prof.inp does not exist'
     3080        read (ilesfile,*) kmax
     3081        do k=1,kmax
     3082          read (ilesfile,*) height(k),pprof(k),  tprof(k),thlprof(k),
     3083     .                qvprof (k),qlprof (k),qtprof (k),
     3084     .                uprof(k),  vprof(k),  wprof(k),tkeprof(k),o3mmr(k)
     3085        enddo
     3086        close(ilesfile)
     3087
     3088        return
     3089        end
     3090
    24813091
    24823092
     
    25393149        return
    25403150        end
    2541 !===============================================================
    2542       function ismin(n,sx,incx)
     3151!=====================================================================
     3152      subroutine read_amma(fich_amma,nlevel,ntime
     3153     :     ,zz,pp,temp,qv,u,v,dw
     3154     :     ,dt,dq,sens,flat)
     3155
     3156!program reading forcings of the AMMA case study
     3157
    25433158
    25443159      implicit none
    2545       integer n,i,incx,ismin,ix
    2546       real sx((n-1)*incx+1),sxmin
    2547 
    2548       ix=1
    2549       ismin=1
    2550       sxmin=sx(1)
    2551       do i=1,n-1
    2552          ix=ix+incx
    2553          if(sx(ix).lt.sxmin) then
    2554              sxmin=sx(ix)
    2555              ismin=i+1
    2556          endif
    2557       enddo
    2558 
    2559       return
    2560       end
    2561 
    2562 !===============================================================
    2563       function ismax(n,sx,incx)
     3160
     3161#include "netcdf.inc"
     3162
     3163      integer ntime,nlevel
     3164      integer l,k
     3165      character*80 :: fich_amma
     3166      real*8 time(ntime)
     3167      real*8 zz(nlevel)
     3168
     3169      real*8 temp(nlevel),pp(nlevel)
     3170      real*8 qv(nlevel),u(nlevel)
     3171      real*8 v(nlevel)
     3172      real*8 dw(nlevel,ntime)
     3173      real*8 dt(nlevel,ntime)
     3174      real*8 dq(nlevel,ntime)   
     3175      real*8 flat(ntime),sens(ntime)
     3176
     3177      integer nid, ierr
     3178      integer nbvar3d
     3179      parameter(nbvar3d=30)
     3180      integer var3didin(nbvar3d)
     3181
     3182      ierr = NF_OPEN(fich_amma,NF_NOWRITE,nid)
     3183      if (ierr.NE.NF_NOERR) then
     3184         write(*,*) 'ERROR: Pb opening forcings nc file '
     3185         write(*,*) NF_STRERROR(ierr)
     3186         stop ""
     3187      endif
     3188
     3189
     3190       ierr=NF_INQ_VARID(nid,"zz",var3didin(1))
     3191         if(ierr/=NF_NOERR) then
     3192           write(*,*) NF_STRERROR(ierr)
     3193           stop 'lev'
     3194         endif
     3195
     3196
     3197      ierr=NF_INQ_VARID(nid,"temp",var3didin(2))
     3198         if(ierr/=NF_NOERR) then
     3199           write(*,*) NF_STRERROR(ierr)
     3200           stop 'temp'
     3201         endif
     3202
     3203      ierr=NF_INQ_VARID(nid,"qv",var3didin(3))
     3204         if(ierr/=NF_NOERR) then
     3205           write(*,*) NF_STRERROR(ierr)
     3206           stop 'qv'
     3207         endif
     3208
     3209      ierr=NF_INQ_VARID(nid,"u",var3didin(4))
     3210         if(ierr/=NF_NOERR) then
     3211           write(*,*) NF_STRERROR(ierr)
     3212           stop 'u'
     3213         endif
     3214
     3215      ierr=NF_INQ_VARID(nid,"v",var3didin(5))
     3216         if(ierr/=NF_NOERR) then
     3217           write(*,*) NF_STRERROR(ierr)
     3218           stop 'v'
     3219         endif
     3220
     3221      ierr=NF_INQ_VARID(nid,"dw",var3didin(6))
     3222         if(ierr/=NF_NOERR) then
     3223           write(*,*) NF_STRERROR(ierr)
     3224           stop 'dw'
     3225         endif
     3226
     3227      ierr=NF_INQ_VARID(nid,"dt",var3didin(7))
     3228         if(ierr/=NF_NOERR) then
     3229           write(*,*) NF_STRERROR(ierr)
     3230           stop 'dt'
     3231         endif
     3232
     3233      ierr=NF_INQ_VARID(nid,"dq",var3didin(8))
     3234         if(ierr/=NF_NOERR) then
     3235           write(*,*) NF_STRERROR(ierr)
     3236           stop 'dq'
     3237         endif
     3238     
     3239      ierr=NF_INQ_VARID(nid,"sens",var3didin(9))
     3240         if(ierr/=NF_NOERR) then
     3241           write(*,*) NF_STRERROR(ierr)
     3242           stop 'sens'
     3243         endif
     3244
     3245      ierr=NF_INQ_VARID(nid,"flat",var3didin(10))
     3246         if(ierr/=NF_NOERR) then
     3247           write(*,*) NF_STRERROR(ierr)
     3248           stop 'flat'
     3249         endif
     3250
     3251      ierr=NF_INQ_VARID(nid,"pp",var3didin(11))
     3252         if(ierr/=NF_NOERR) then
     3253           write(*,*) NF_STRERROR(ierr)
     3254           stop 'pp'
     3255      endif
     3256
     3257!dimensions lecture
     3258!      call catchaxis(nid,ntime,nlevel,time,z,ierr)
     3259 
     3260#ifdef NC_DOUBLE
     3261         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(1),zz)
     3262#else
     3263         ierr = NF_GET_VAR_REAL(nid,var3didin(1),zz)
     3264#endif
     3265         if(ierr/=NF_NOERR) then
     3266            write(*,*) NF_STRERROR(ierr)
     3267            stop "getvarup"
     3268         endif
     3269!          write(*,*)'lecture z ok',zz
     3270
     3271#ifdef NC_DOUBLE
     3272         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(2),temp)
     3273#else
     3274         ierr = NF_GET_VAR_REAL(nid,var3didin(2),temp)
     3275#endif
     3276         if(ierr/=NF_NOERR) then
     3277            write(*,*) NF_STRERROR(ierr)
     3278            stop "getvarup"
     3279         endif
     3280!          write(*,*)'lecture th ok',temp
     3281
     3282#ifdef NC_DOUBLE
     3283         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(3),qv)
     3284#else
     3285         ierr = NF_GET_VAR_REAL(nid,var3didin(3),qv)
     3286#endif
     3287         if(ierr/=NF_NOERR) then
     3288            write(*,*) NF_STRERROR(ierr)
     3289            stop "getvarup"
     3290         endif
     3291!          write(*,*)'lecture qv ok',qv
     3292 
     3293#ifdef NC_DOUBLE
     3294         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(4),u)
     3295#else
     3296         ierr = NF_GET_VAR_REAL(nid,var3didin(4),u)
     3297#endif
     3298         if(ierr/=NF_NOERR) then
     3299            write(*,*) NF_STRERROR(ierr)
     3300            stop "getvarup"
     3301         endif
     3302!          write(*,*)'lecture u ok',u
     3303
     3304#ifdef NC_DOUBLE
     3305         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(5),v)
     3306#else
     3307         ierr = NF_GET_VAR_REAL(nid,var3didin(5),v)
     3308#endif
     3309         if(ierr/=NF_NOERR) then
     3310            write(*,*) NF_STRERROR(ierr)
     3311            stop "getvarup"
     3312         endif
     3313!          write(*,*)'lecture v ok',v
     3314
     3315#ifdef NC_DOUBLE
     3316         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(6),dw)
     3317#else
     3318         ierr = NF_GET_VAR_REAL(nid,var3didin(6),dw)
     3319#endif
     3320         if(ierr/=NF_NOERR) then
     3321            write(*,*) NF_STRERROR(ierr)
     3322            stop "getvarup"
     3323         endif
     3324!          write(*,*)'lecture w ok',dw
     3325
     3326#ifdef NC_DOUBLE
     3327         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(7),dt)
     3328#else
     3329         ierr = NF_GET_VAR_REAL(nid,var3didin(7),dt)
     3330#endif
     3331         if(ierr/=NF_NOERR) then
     3332            write(*,*) NF_STRERROR(ierr)
     3333            stop "getvarup"
     3334         endif
     3335!          write(*,*)'lecture dt ok',dt
     3336
     3337#ifdef NC_DOUBLE
     3338         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(8),dq)
     3339#else
     3340         ierr = NF_GET_VAR_REAL(nid,var3didin(8),dq)
     3341#endif
     3342         if(ierr/=NF_NOERR) then
     3343            write(*,*) NF_STRERROR(ierr)
     3344            stop "getvarup"
     3345         endif
     3346!          write(*,*)'lecture dq ok',dq
     3347
     3348#ifdef NC_DOUBLE
     3349         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(9),sens)
     3350#else
     3351         ierr = NF_GET_VAR_REAL(nid,var3didin(9),sens)
     3352#endif
     3353         if(ierr/=NF_NOERR) then
     3354            write(*,*) NF_STRERROR(ierr)
     3355            stop "getvarup"
     3356         endif
     3357!          write(*,*)'lecture sens ok',sens
     3358
     3359#ifdef NC_DOUBLE
     3360         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(10),flat)
     3361#else
     3362         ierr = NF_GET_VAR_REAL(nid,var3didin(10),flat)
     3363#endif
     3364         if(ierr/=NF_NOERR) then
     3365            write(*,*) NF_STRERROR(ierr)
     3366            stop "getvarup"
     3367         endif
     3368!          write(*,*)'lecture flat ok',flat
     3369
     3370#ifdef NC_DOUBLE
     3371         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(11),pp)
     3372#else
     3373         ierr = NF_GET_VAR_REAL(nid,var3didin(11),pp)
     3374#endif
     3375         if(ierr/=NF_NOERR) then
     3376            write(*,*) NF_STRERROR(ierr)
     3377            stop "getvarup"
     3378         endif
     3379!          write(*,*)'lecture pp ok',pp
     3380
     3381         return
     3382         end subroutine read_amma
     3383!======================================================================
     3384        SUBROUTINE interp_amma_time(day,day1,annee_ref
     3385     i         ,year_ini_amma,day_ini_amma,nt_amma,dt_amma,nlev_amma
     3386     i         ,vitw_amma,ht_amma,hq_amma,lat_amma,sens_amma
     3387     o         ,vitw_prof,ht_prof,hq_prof,lat_prof,sens_prof)
     3388        implicit none
     3389
     3390!---------------------------------------------------------------------------------------
     3391! Time interpolation of a 2D field to the timestep corresponding to day
     3392!
     3393! day: current julian day (e.g. 717538.2)
     3394! day1: first day of the simulation
     3395! nt_amma: total nb of data in the forcing (e.g. 48 for AMMA)
     3396! dt_amma: total time interval (in sec) between 2 forcing data (e.g. 30min for AMMA)
     3397!---------------------------------------------------------------------------------------
     3398
     3399#include "compar1d.h"
     3400
     3401! inputs:
     3402        integer annee_ref
     3403        integer nt_amma,nlev_amma
     3404        integer year_ini_amma
     3405        real day, day1,day_ini_amma,dt_amma
     3406        real vitw_amma(nlev_amma,nt_amma)
     3407        real ht_amma(nlev_amma,nt_amma)
     3408        real hq_amma(nlev_amma,nt_amma)
     3409        real lat_amma(nt_amma)
     3410        real sens_amma(nt_amma)
     3411! outputs:
     3412        real vitw_prof(nlev_amma)
     3413        real ht_prof(nlev_amma)
     3414        real hq_prof(nlev_amma)
     3415        real lat_prof,sens_prof
     3416! local:
     3417        integer it_amma1, it_amma2,k
     3418        real timeit,time_amma1,time_amma2,frac
     3419
     3420
     3421        if (forcing_type.eq.6) then
     3422! Check that initial day of the simulation consistent with AMMA case:
     3423       if (annee_ref.ne.2006) then
     3424        print*,'Pour AMMA, annee_ref doit etre 2006'
     3425        print*,'Changer annee_ref dans run.def'
     3426        stop
     3427       endif
     3428       if (annee_ref.eq.2006 .and. day1.lt.day_ini_amma) then
     3429        print*,'AMMA a débuté le 10 juillet 2006',day1,day_ini_amma
     3430        print*,'Changer dayref dans run.def'
     3431        stop
     3432       endif
     3433       if (annee_ref.eq.2006 .and. day1.gt.day_ini_amma+1) then
     3434        print*,'AMMA a fini le 11 juillet'
     3435        print*,'Changer dayref ou nday dans run.def'
     3436        stop
     3437       endif
     3438       endif
     3439
     3440! Determine timestep relative to the 1st day of AMMA:
     3441!       timeit=(day-day1)*86400.
     3442!       if (annee_ref.eq.1992) then
     3443!        timeit=(day-day_ini_toga)*86400.
     3444!       else
     3445!        timeit=(day+61.-1.)*86400. ! 61 days between Nov01 and Dec31 1992
     3446!       endif
     3447      timeit=(day-day_ini_amma)*86400
     3448
     3449! Determine the closest observation times:
     3450!       it_amma1=INT(timeit/dt_amma)+1
     3451!       it_amma2=it_amma1 + 1
     3452!       time_amma1=(it_amma1-1)*dt_amma
     3453!       time_amma2=(it_amma2-1)*dt_amma
     3454
     3455       it_amma1=INT(timeit/dt_amma)+1
     3456       IF (it_amma1 .EQ. nt_amma) THEN
     3457       it_amma2=it_amma1
     3458       ELSE
     3459       it_amma2=it_amma1 + 1
     3460       ENDIF
     3461       time_amma1=(it_amma1-1)*dt_amma
     3462       time_amma2=(it_amma2-1)*dt_amma
     3463
     3464       if (it_amma1 .gt. nt_amma) then
     3465        write(*,*) 'PB-stop: day, it_amma1, it_amma2, timeit: '
     3466     :        ,day,day_ini_amma,it_amma1,it_amma2,timeit/86400.
     3467        stop
     3468       endif
     3469
     3470! time interpolation:
     3471       frac=(time_amma2-timeit)/(time_amma2-time_amma1)
     3472       frac=max(frac,0.0)
     3473
     3474       lat_prof = lat_amma(it_amma2)
     3475     :          -frac*(lat_amma(it_amma2)-lat_amma(it_amma1))
     3476       sens_prof = sens_amma(it_amma2)
     3477     :          -frac*(sens_amma(it_amma2)-sens_amma(it_amma1))
     3478
     3479       do k=1,nlev_amma
     3480        vitw_prof(k) = vitw_amma(k,it_amma2)
     3481     :          -frac*(vitw_amma(k,it_amma2)-vitw_amma(k,it_amma1))
     3482        ht_prof(k) = ht_amma(k,it_amma2)
     3483     :          -frac*(ht_amma(k,it_amma2)-ht_amma(k,it_amma1))
     3484        hq_prof(k) = hq_amma(k,it_amma2)
     3485     :          -frac*(hq_amma(k,it_amma2)-hq_amma(k,it_amma1))
     3486        enddo
     3487
     3488        return
     3489        END
     3490
     3491!=====================================================================
     3492      subroutine read_fire(fich_fire,nlevel,ntime
     3493     :     ,zz,thl,qt,u,v,tke
     3494     :     ,ug,vg,wls,dqtdx,dqtdy,dqtdt,thl_rad)
     3495
     3496!program reading forcings of the FIRE case study
     3497
    25643498
    25653499      implicit none
    2566       integer n,i,incx,ismax,ix
    2567       real sx((n-1)*incx+1),sxmax
    2568 
    2569       ix=1
    2570       ismax=1
    2571       sxmax=sx(1)
    2572       do i=1,n-1
    2573          ix=ix+incx
    2574          if(sx(ix).gt.sxmax) then
    2575              sxmax=sx(ix)
    2576              ismax=i+1
    2577          endif
    2578       enddo
    2579 
    2580       return
    2581       end
    2582 
     3500
     3501#include "netcdf.inc"
     3502
     3503      integer ntime,nlevel
     3504      integer l,k
     3505      character*80 :: fich_fire
     3506      real*8 time(ntime)
     3507      real*8 zz(nlevel)
     3508
     3509      real*8 thl(nlevel)
     3510      real*8 qt(nlevel),u(nlevel)
     3511      real*8 v(nlevel),tke(nlevel)
     3512      real*8 ug(nlevel,ntime),vg(nlevel,ntime),wls(nlevel,ntime)
     3513      real*8 dqtdx(nlevel,ntime),dqtdy(nlevel,ntime)
     3514      real*8 dqtdt(nlevel,ntime),thl_rad(nlevel,ntime) 
     3515
     3516      integer nid, ierr
     3517      integer nbvar3d
     3518      parameter(nbvar3d=30)
     3519      integer var3didin(nbvar3d)
     3520
     3521      ierr = NF_OPEN(fich_fire,NF_NOWRITE,nid)
     3522      if (ierr.NE.NF_NOERR) then
     3523         write(*,*) 'ERROR: Pb opening forcings nc file '
     3524         write(*,*) NF_STRERROR(ierr)
     3525         stop ""
     3526      endif
     3527
     3528
     3529       ierr=NF_INQ_VARID(nid,"zz",var3didin(1))
     3530         if(ierr/=NF_NOERR) then
     3531           write(*,*) NF_STRERROR(ierr)
     3532           stop 'lev'
     3533         endif
     3534
     3535
     3536      ierr=NF_INQ_VARID(nid,"thetal",var3didin(2))
     3537         if(ierr/=NF_NOERR) then
     3538           write(*,*) NF_STRERROR(ierr)
     3539           stop 'temp'
     3540         endif
     3541
     3542      ierr=NF_INQ_VARID(nid,"qt",var3didin(3))
     3543         if(ierr/=NF_NOERR) then
     3544           write(*,*) NF_STRERROR(ierr)
     3545           stop 'qv'
     3546         endif
     3547
     3548      ierr=NF_INQ_VARID(nid,"u",var3didin(4))
     3549         if(ierr/=NF_NOERR) then
     3550           write(*,*) NF_STRERROR(ierr)
     3551           stop 'u'
     3552         endif
     3553
     3554      ierr=NF_INQ_VARID(nid,"v",var3didin(5))
     3555         if(ierr/=NF_NOERR) then
     3556           write(*,*) NF_STRERROR(ierr)
     3557           stop 'v'
     3558         endif
     3559
     3560      ierr=NF_INQ_VARID(nid,"tke",var3didin(6))
     3561         if(ierr/=NF_NOERR) then
     3562           write(*,*) NF_STRERROR(ierr)
     3563           stop 'tke'
     3564         endif
     3565
     3566      ierr=NF_INQ_VARID(nid,"ugeo",var3didin(7))
     3567         if(ierr/=NF_NOERR) then
     3568           write(*,*) NF_STRERROR(ierr)
     3569           stop 'ug'
     3570         endif
     3571
     3572      ierr=NF_INQ_VARID(nid,"vgeo",var3didin(8))
     3573         if(ierr/=NF_NOERR) then
     3574           write(*,*) NF_STRERROR(ierr)
     3575           stop 'vg'
     3576         endif
     3577     
     3578      ierr=NF_INQ_VARID(nid,"wls",var3didin(9))
     3579         if(ierr/=NF_NOERR) then
     3580           write(*,*) NF_STRERROR(ierr)
     3581           stop 'wls'
     3582         endif
     3583
     3584      ierr=NF_INQ_VARID(nid,"dqtdx",var3didin(10))
     3585         if(ierr/=NF_NOERR) then
     3586           write(*,*) NF_STRERROR(ierr)
     3587           stop 'dqtdx'
     3588         endif
     3589
     3590      ierr=NF_INQ_VARID(nid,"dqtdy",var3didin(11))
     3591         if(ierr/=NF_NOERR) then
     3592           write(*,*) NF_STRERROR(ierr)
     3593           stop 'dqtdy'
     3594      endif
     3595
     3596      ierr=NF_INQ_VARID(nid,"dqtdt",var3didin(12))
     3597         if(ierr/=NF_NOERR) then
     3598           write(*,*) NF_STRERROR(ierr)
     3599           stop 'dqtdt'
     3600      endif
     3601
     3602      ierr=NF_INQ_VARID(nid,"thl_rad",var3didin(13))
     3603         if(ierr/=NF_NOERR) then
     3604           write(*,*) NF_STRERROR(ierr)
     3605           stop 'thl_rad'
     3606      endif
     3607!dimensions lecture
     3608!      call catchaxis(nid,ntime,nlevel,time,z,ierr)
     3609 
     3610#ifdef NC_DOUBLE
     3611         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(1),zz)
     3612#else
     3613         ierr = NF_GET_VAR_REAL(nid,var3didin(1),zz)
     3614#endif
     3615         if(ierr/=NF_NOERR) then
     3616            write(*,*) NF_STRERROR(ierr)
     3617            stop "getvarup"
     3618         endif
     3619!          write(*,*)'lecture z ok',zz
     3620
     3621#ifdef NC_DOUBLE
     3622         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(2),thl)
     3623#else
     3624         ierr = NF_GET_VAR_REAL(nid,var3didin(2),thl)
     3625#endif
     3626         if(ierr/=NF_NOERR) then
     3627            write(*,*) NF_STRERROR(ierr)
     3628            stop "getvarup"
     3629         endif
     3630!          write(*,*)'lecture thl ok',thl
     3631
     3632#ifdef NC_DOUBLE
     3633         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(3),qt)
     3634#else
     3635         ierr = NF_GET_VAR_REAL(nid,var3didin(3),qt)
     3636#endif
     3637         if(ierr/=NF_NOERR) then
     3638            write(*,*) NF_STRERROR(ierr)
     3639            stop "getvarup"
     3640         endif
     3641!          write(*,*)'lecture qt ok',qt
     3642 
     3643#ifdef NC_DOUBLE
     3644         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(4),u)
     3645#else
     3646         ierr = NF_GET_VAR_REAL(nid,var3didin(4),u)
     3647#endif
     3648         if(ierr/=NF_NOERR) then
     3649            write(*,*) NF_STRERROR(ierr)
     3650            stop "getvarup"
     3651         endif
     3652!          write(*,*)'lecture u ok',u
     3653
     3654#ifdef NC_DOUBLE
     3655         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(5),v)
     3656#else
     3657         ierr = NF_GET_VAR_REAL(nid,var3didin(5),v)
     3658#endif
     3659         if(ierr/=NF_NOERR) then
     3660            write(*,*) NF_STRERROR(ierr)
     3661            stop "getvarup"
     3662         endif
     3663!          write(*,*)'lecture v ok',v
     3664
     3665#ifdef NC_DOUBLE
     3666         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(6),tke)
     3667#else
     3668         ierr = NF_GET_VAR_REAL(nid,var3didin(6),tke)
     3669#endif
     3670         if(ierr/=NF_NOERR) then
     3671            write(*,*) NF_STRERROR(ierr)
     3672            stop "getvarup"
     3673         endif
     3674!          write(*,*)'lecture tke ok',tke
     3675
     3676#ifdef NC_DOUBLE
     3677         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(7),ug)
     3678#else
     3679         ierr = NF_GET_VAR_REAL(nid,var3didin(7),ug)
     3680#endif
     3681         if(ierr/=NF_NOERR) then
     3682            write(*,*) NF_STRERROR(ierr)
     3683            stop "getvarup"
     3684         endif
     3685!          write(*,*)'lecture ug ok',ug
     3686
     3687#ifdef NC_DOUBLE
     3688         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(8),vg)
     3689#else
     3690         ierr = NF_GET_VAR_REAL(nid,var3didin(8),vg)
     3691#endif
     3692         if(ierr/=NF_NOERR) then
     3693            write(*,*) NF_STRERROR(ierr)
     3694            stop "getvarup"
     3695         endif
     3696!          write(*,*)'lecture vg ok',vg
     3697
     3698#ifdef NC_DOUBLE
     3699         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(9),wls)
     3700#else
     3701         ierr = NF_GET_VAR_REAL(nid,var3didin(9),wls)
     3702#endif
     3703         if(ierr/=NF_NOERR) then
     3704            write(*,*) NF_STRERROR(ierr)
     3705            stop "getvarup"
     3706         endif
     3707!          write(*,*)'lecture wls ok',wls
     3708
     3709#ifdef NC_DOUBLE
     3710         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(10),dqtdx)
     3711#else
     3712         ierr = NF_GET_VAR_REAL(nid,var3didin(10),dqtdx)
     3713#endif
     3714         if(ierr/=NF_NOERR) then
     3715            write(*,*) NF_STRERROR(ierr)
     3716            stop "getvarup"
     3717         endif
     3718!          write(*,*)'lecture dqtdx ok',dqtdx
     3719
     3720#ifdef NC_DOUBLE
     3721         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(11),dqtdy)
     3722#else
     3723         ierr = NF_GET_VAR_REAL(nid,var3didin(11),dqtdy)
     3724#endif
     3725         if(ierr/=NF_NOERR) then
     3726            write(*,*) NF_STRERROR(ierr)
     3727            stop "getvarup"
     3728         endif
     3729!          write(*,*)'lecture dqtdy ok',dqtdy
     3730
     3731#ifdef NC_DOUBLE
     3732         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(12),dqtdt)
     3733#else
     3734         ierr = NF_GET_VAR_REAL(nid,var3didin(12),dqtdt)
     3735#endif
     3736         if(ierr/=NF_NOERR) then
     3737            write(*,*) NF_STRERROR(ierr)
     3738            stop "getvarup"
     3739         endif
     3740!          write(*,*)'lecture dqtdt ok',dqtdt
     3741
     3742#ifdef NC_DOUBLE
     3743         ierr = NF_GET_VAR_DOUBLE(nid,var3didin(13),thl_rad)
     3744#else
     3745         ierr = NF_GET_VAR_REAL(nid,var3didin(13),thl_rad)
     3746#endif
     3747         if(ierr/=NF_NOERR) then
     3748            write(*,*) NF_STRERROR(ierr)
     3749            stop "getvarup"
     3750         endif
     3751!          write(*,*)'lecture thl_rad ok',thl_rad
     3752
     3753         return
     3754         end subroutine read_fire
  • LMDZ5/branches/testing/libf/phy1d/1DUTILS.h_with_writelim

    r1707 r1795  
    125125       ok_flux_surf = .FALSE.
    126126       CALL getin('ok_flux_surf',ok_flux_surf)
     127
     128!Config  Key  = ok_old_disvert
     129!Config  Desc = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
     130!Config  Def  = false
     131!Config  Help = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
     132       ok_old_disvert = .FALSE.
     133       CALL getin('ok_old_disvert',ok_old_disvert)
    127134
    128135!Config  Key  = time_ini
     
    703710      RETURN
    704711      END
    705       subroutine scopy(n,sx,incx,sy,incy)
    706 !
    707       IMPLICIT NONE
    708 !
    709       integer n,incx,incy,ix,iy,i
    710       real sx((n-1)*incx+1),sy((n-1)*incy+1)
    711 !
    712       iy=1
    713       ix=1
    714       do 10 i=1,n
    715          sy(iy)=sx(ix)
    716          ix=ix+incx
    717          iy=iy+incy
    718 10    continue
    719 !
    720       return
    721       end
    722712      subroutine wrgradsfi(if,nl,field,name,titlevar)
    723713      implicit none
     
    10791069 
    10801070!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1081       SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
     1071      SUBROUTINE disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
    10821072 
    10831073!    Auteur :  P. Le Van .
     
    26622652        return
    26632653        end
    2664 !===============================================================
    2665       function ismin(n,sx,incx)
    2666 
    2667       implicit none
    2668       integer n,i,incx,ismin,ix
    2669       real sx((n-1)*incx+1),sxmin
    2670 
    2671       ix=1
    2672       ismin=1
    2673       sxmin=sx(1)
    2674       do i=1,n-1
    2675          ix=ix+incx
    2676          if(sx(ix).lt.sxmin) then
    2677              sxmin=sx(ix)
    2678              ismin=i+1
    2679          endif
    2680       enddo
    2681 
    2682       return
    2683       end
    2684 
    2685 !===============================================================
    2686       function ismax(n,sx,incx)
    2687 
    2688       implicit none
    2689       integer n,i,incx,ismax,ix
    2690       real sx((n-1)*incx+1),sxmax
    2691 
    2692       ix=1
    2693       ismax=1
    2694       sxmax=sx(1)
    2695       do i=1,n-1
    2696          ix=ix+incx
    2697          if(sx(ix).gt.sxmax) then
    2698              sxmax=sx(ix)
    2699              ismax=i+1
    2700          endif
    2701       enddo
    2702 
    2703       return
    2704       end
    2705 
     2654
  • LMDZ5/branches/testing/libf/phy1d/1DUTILS.h_with_writelim_old

    r1707 r1795  
    125125       ok_flux_surf = .FALSE.
    126126       CALL getin('ok_flux_surf',ok_flux_surf)
     127
     128!Config  Key  = ok_old_disvert
     129!Config  Desc = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
     130!Config  Def  = false
     131!Config  Help = utilisation de l ancien programme disvert0 (dans 1DUTILS.h)
     132       ok_old_disvert = .FALSE.
     133       CALL getin('ok_old_disvert',ok_old_disvert)
    127134
    128135!Config  Key  = time_ini
     
    703710      RETURN
    704711      END
    705       subroutine scopy(n,sx,incx,sy,incy)
    706 !
    707       IMPLICIT NONE
    708 !
    709       integer n,incx,incy,ix,iy,i
    710       real sx((n-1)*incx+1),sy((n-1)*incy+1)
    711 !
    712       iy=1
    713       ix=1
    714       do 10 i=1,n
    715          sy(iy)=sx(ix)
    716          ix=ix+incx
    717          iy=iy+incy
    718 10    continue
    719 !
    720       return
    721       end
    722712      subroutine wrgradsfi(if,nl,field,name,titlevar)
    723713      implicit none
     
    10791069 
    10801070!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1081       SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
     1071      SUBROUTINE disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
    10821072 
    10831073!    Auteur :  P. Le Van .
     
    26042594        end
    26052595
    2606 !===============================================================
    2607       function ismin(n,sx,incx)
    2608 
    2609       implicit none
    2610       integer n,i,incx,ismin,ix
    2611       real sx((n-1)*incx+1),sxmin
    2612 
    2613       ix=1
    2614       ismin=1
    2615       sxmin=sx(1)
    2616       do i=1,n-1
    2617          ix=ix+incx
    2618          if(sx(ix).lt.sxmin) then
    2619              sxmin=sx(ix)
    2620              ismin=i+1
    2621          endif
    2622       enddo
    2623 
    2624       return
    2625       end
    2626 
    2627 !===============================================================
    2628       function ismax(n,sx,incx)
    2629 
    2630       implicit none
    2631       integer n,i,incx,ismax,ix
    2632       real sx((n-1)*incx+1),sxmax
    2633 
    2634       ix=1
    2635       ismax=1
    2636       sxmax=sx(1)
    2637       do i=1,n-1
    2638          ix=ix+incx
    2639          if(sx(ix).gt.sxmax) then
    2640              sxmax=sx(ix)
    2641              ismax=i+1
    2642          endif
    2643       enddo
    2644 
    2645       return
    2646       end
    2647 
     2596
  • LMDZ5/branches/testing/libf/phy1d/1D_decl_cases.h

    r1665 r1795  
    8181        real ht_proftwp(nlev_twpi),vt_proftwp(nlev_twpi)
    8282        real hq_proftwp(nlev_twpi),vq_proftwp(nlev_twpi)
     83
     84
     85!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     86!Declarations specifiques au cas AMMA
     87        character*80 :: fich_amma
     88! Option du cas AMMA ou on impose la discretisation verticale (Ap,Bp)
     89        logical  :: fixe_disvert=.true.
     90        integer nlev_amma, nt_amma
     91!       parameter (nlev_amma=29, nt_amma=48)  ! Fleur, juillet 2012
     92        parameter (nlev_amma=36, nt_amma=48)  ! Romain, octobre 2012
     93!       parameter (nlev_amma=26, nt_amma=48)  ! Test MPL feverier 2013
     94        integer year_ini_amma, day_ini_amma, mth_ini_amma
     95        real heure_ini_amma
     96        real day_ju_ini_amma   ! Julian day of amma first day
     97        parameter (year_ini_amma=2006)
     98        parameter (mth_ini_amma=7)
     99        parameter (day_ini_amma=10)  ! 10 = 10Juil2006
     100        parameter (heure_ini_amma=0.) !0h en secondes
     101        real dt_amma
     102        parameter (dt_amma=1800.)
     103
     104!profils initiaux:
     105        real plev_amma(nlev_amma)
     106        real tv_amma(nlev_amma),rho_amma(nlev_amma)
     107        real thv_amma(nlev_amma)
     108       
     109        real z_amma(nlev_amma)
     110        real th_amma(nlev_amma),q_amma(nlev_amma)
     111        real u_amma(nlev_amma)
     112        real v_amma(nlev_amma)
     113
     114        real thvsurf_amma,tvsurf_amma,rhosurf_amma,thsurf
     115
     116        real th_ammai(nlev_amma),q_ammai(nlev_amma)
     117        real u_ammai(nlev_amma)
     118        real v_ammai(nlev_amma)
     119        real vitw_ammai(nlev_amma)
     120        real ht_ammai(nlev_amma)
     121        real hq_ammai(nlev_amma)
     122        real vt_ammai(nlev_amma)
     123        real vq_ammai(nlev_amma)
     124       
     125!forcings
     126        real ht_amma(nlev_amma,nt_amma)
     127        real hq_amma(nlev_amma,nt_amma)
     128        real vitw_amma(nlev_amma,nt_amma)
     129        real lat_amma(nt_amma),sens_amma(nt_amma)
     130
     131!champs interpoles
     132        real plev_profamma(nlev_amma),vitw_profamma(nlev_amma)
     133        real ht_profamma(nlev_amma)
     134        real hq_profamma(nlev_amma)
     135        real lat_profamma,sens_profamma
     136        real vt_profamma(nlev_amma)
     137        real vq_profamma(nlev_amma)
     138        real th_profamma(nlev_amma)
     139        real q_profamma(nlev_amma)
     140        real u_profamma(nlev_amma)
     141        real v_profamma(nlev_amma)
     142
     143!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     144!Declarations specifiques au cas FIRE
     145        character*80 :: fich_fire
     146        integer nlev_fire, nt_fire
     147        parameter (nlev_fire=120, nt_fire=1) 
     148        integer year_ini_fire, day_ini_fire, mth_ini_fire
     149        real heure_ini_fire
     150        real day_ju_ini_fire   ! Julian day of fire first day
     151        parameter (year_ini_fire=1987)
     152        parameter (mth_ini_fire=7)
     153        parameter (day_ini_fire=14)  ! 14 = 14Juil1987
     154        parameter (heure_ini_fire=0.) !0h en secondes
     155
     156!profils initiaux:
     157        real z_fire(nlev_fire)
     158        real thl_fire(nlev_fire),qt_fire(nlev_fire)
     159        real u_fire(nlev_fire), v_fire(nlev_fire)
     160        real tke_fire(nlev_fire)
     161       
     162!forcings
     163        real ugeo_fire(nlev_fire),vgeo_fire(nlev_fire)
     164        real wls_fire(nlev_fire),dqtdx_fire(nlev_fire)
     165        real dqtdy_fire(nlev_fire)
     166        real dqtdt_fire(nlev_fire),thl_rad_fire(nlev_fire)
     167         
     168        real ugeo_mod(llm),vgeo_mod(llm),wls_mod(llm)
     169        real dqtdx_mod(llm),dqtdy_mod(llm),dqtdt_mod(llm)
     170        real thl_rad_mod(llm)
    83171!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    84172! Declarations specifiques au cas GCSSold
     
    127215        real sens_prof,flat_prof,fact
    128216!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    129 
     217! declarations specifiques au cas Sandu
     218        character*80 :: fich_sandu
     219!        integer nlev_prof
     220!        parameter (nlev_prof = 41)
     221        integer nlev_sandu, nt_sandu
     222        parameter (nlev_sandu=87, nt_sandu=13)
     223        integer year_ini_sandu, day_ini_sandu, mth_ini_sandu
     224        real day_ju_ini_sandu                                ! Julian day of sandu case first day
     225        parameter (year_ini_sandu=2006)
     226        parameter (mth_ini_sandu=7)
     227        parameter (day_ini_sandu=15)  ! 196 = 15 juillet 2006
     228        real dt_sandu, tau_sandu
     229        logical  :: trouve_700=.true.
     230        parameter (dt_sandu=6.*3600.)   ! forcages donnes ttes les 6 heures par ifa_sandu.txt
     231!       parameter (tau_sandu=3600.)  ! temps de relaxation u,v,thetal,qt vers profil init et au dessus 700hPa
     232!!
     233        integer it_sandu1, it_sandu2
     234        real time_sandu1,time_sandu2
     235
     236        real ts_sandu(nt_sandu)
     237! profs comme "profil sandu"
     238        real plev_profs(nlev_sandu)
     239        real t_profs(nlev_sandu),thl_profs(nlev_sandu)
     240        real q_profs(nlev_sandu)
     241        real u_profs(nlev_sandu),v_profs(nlev_sandu),w_profs(nlev_sandu)
     242        real omega_profs(nlev_sandu),o3mmr_profs(nlev_sandu)
     243
     244        real thl_mod(llm),omega_mod(llm),o3mmr_mod(llm),tke_mod(llm)
     245! pour relaxer u,v,thl et qt vers les profils initiaux au dessus de 700hPa
     246        real relax_u(llm),relax_v(llm),relax_thl(llm),relax_q(llm,2)
     247!vertical advection computation
     248        real d_t_z(llm), d_q_z(llm)
     249        real d_t_dyn_z(llm), d_q_dyn_z(llm)
     250        real zz(llm)
     251        real zfact
     252!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     253! Declarations specifiques au cas Astex
     254        character*80 :: fich_astex
     255        integer nlev_astex, nt_astex
     256        parameter (nlev_astex=34, nt_astex=49)
     257        integer year_ini_astex, day_ini_astex, mth_ini_astex
     258        real day_ju_ini_astex                                ! Julian day of astex case first day
     259        parameter (year_ini_astex=1992)
     260        parameter (mth_ini_astex=6)
     261        parameter (day_ini_astex=13)  ! 165 = 13 juin 1992
     262        real dt_astex, tau_astex
     263        parameter (dt_astex=3600.)    ! forcages donnes ttes les heures par ifa_astex.txt
     264        integer it_astex1, it_astex2
     265        real time_astex1,time_astex2
     266        real ts_astex(nt_astex),div_astex(nt_astex),ug_astex(nt_astex)
     267        real vg_astex(nt_astex),ufa_astex(nt_astex),vfa_astex(nt_astex)
     268        real div_prof,ug_prof,vg_prof,ufa_prof,vfa_prof
     269! profa comme "profil astex"
     270        real plev_profa(nlev_astex)
     271        real t_profa(nlev_astex),thl_profa(nlev_astex)
     272        real qv_profa(nlev_astex),ql_profa(nlev_astex)
     273        real qt_profa(nlev_astex),o3mmr_profa(nlev_astex)
     274        real u_profa(nlev_astex),v_profa(nlev_astex),w_profa(nlev_astex)
     275        real tke_profa(nlev_astex)
     276!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     277
  • LMDZ5/branches/testing/libf/phy1d/1D_interp_cases.h

    r1665 r1795  
    181181
    182182      endif ! forcing_twpice
     183
     184!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     185!---------------------------------------------------------------------
     186! Interpolation forcing AMMA
     187!---------------------------------------------------------------------
     188
     189       if (forcing_amma) then
     190
     191        print*,
     192     : '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_amma=',
     193     :    daytime,day1,(daytime-day1)*86400.,
     194     :    (daytime-day1)*86400/dt_amma
     195
     196! time interpolation using TOGA interpolation routine
     197        CALL interp_amma_time(daytime,day1,annee_ref
     198     i       ,year_ini_amma,day_ju_ini_amma,nt_amma,dt_amma,nlev_amma
     199     i       ,vitw_amma,ht_amma,hq_amma,lat_amma,sens_amma
     200     o       ,vitw_profamma,ht_profamma,hq_profamma,lat_profamma
     201     :       ,sens_profamma)
     202
     203      print*,'apres interpolation temporelle AMMA'
     204
     205      do k=1,nlev_amma
     206         th_profamma(k)=0.
     207         q_profamma(k)=0.
     208         u_profamma(k)=0.
     209         v_profamma(k)=0.
     210         vt_profamma(k)=0.
     211         vq_profamma(k)=0.
     212       enddo
     213! vertical interpolation using TOGA interpolation routine:
     214!      write(*,*)'avant interp vert', t_proftwp
     215      CALL interp_toga_vertical(play,nlev_amma,plev_amma
     216     :         ,th_profamma,q_profamma,u_profamma,v_profamma
     217     :         ,vitw_profamma
     218     :         ,ht_profamma,vt_profamma,hq_profamma,vq_profamma
     219     :         ,t_mod,q_mod,u_mod,v_mod,w_mod
     220     :         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
     221       write(*,*) 'Profil initial forcing AMMA interpole'
     222
     223
     224!calcul de l'advection verticale a partir du omega
     225cCalcul des gradients verticaux
     226cinitialisation
     227      do l=1,llm
     228      d_t_z(l)=0.
     229      d_q_z(l)=0.
     230      enddo
     231
     232      DO l=2,llm-1
     233       d_t_z(l)=(temp(l+1)-temp(l-1))
     234     &          /(play(l+1)-play(l-1))
     235       d_q_z(l)=(q(l+1,1)-q(l-1,1))
     236     &          /(play(l+1)-play(l-1))
     237      ENDDO
     238      d_t_z(1)=d_t_z(2)
     239      d_q_z(1)=d_q_z(2)
     240      d_t_z(llm)=d_t_z(llm-1)
     241      d_q_z(llm)=d_q_z(llm-1)
     242
     243
     244      do l = 1, llm
     245       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
     246       omega(l) = w_mod(l)*(-rg*rho(l))
     247       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     248       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
     249!calcul de l'advection totale
     250!        d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)-omega(l)*d_t_z(l)
     251!attention: on impose dth
     252        d_th_adv(l) = alpha*omega(l)/rcpd+
     253     &         ht_mod(l)*(play(l)/pzero)**rkappa-omega(l)*d_t_z(l)
     254!        d_th_adv(l) = 0.
     255!        print*,'temp vert adv',l,ht_mod(l),vt_mod(l),-d_t_dyn_z(l)
     256        d_q_adv(l,1) = hq_mod(l)-omega(l)*d_q_z(l)
     257!        d_q_adv(l,1) = 0.
     258!        print*,'q vert adv',l,hq_mod(l),vq_mod(l),-d_q_dyn_z(l)
     259   
     260       dt_cooling(l) = 0.0
     261      enddo
     262
     263
     264!     ok_flux_surf=.false.
     265      fsens=-1.*sens_profamma
     266      flat=-1.*lat_profamma
     267
     268      endif ! forcing_amma
     269
    183270!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    184271!---------------------------------------------------------------------
     
    254341      endif ! forcing_armcu
    255342!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    256 
     343!---------------------------------------------------------------------
     344! Interpolation forcing in time and onto model levels
     345!---------------------------------------------------------------------
     346      if (forcing_sandu) then
     347
     348        print*,
     349     : '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_sandu=',
     350     :    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_sandu
     351
     352! time interpolation:
     353! ATTENTION, cet appel ne convient pas pour TOGA !!
     354! revoir 1DUTILS.h et les arguments
     355      CALL interp_sandu_time(daytime,day1,annee_ref
     356     i             ,year_ini_sandu,day_ju_ini_sandu,nt_sandu,dt_sandu
     357     i             ,nlev_sandu
     358     i             ,ts_sandu,ts_prof)
     359
     360        if (type_ts_forcing.eq.1) ts_cur = ts_prof ! SST used in read_tsurf1d
     361
     362! vertical interpolation:
     363      CALL interp_sandu_vertical(play,nlev_sandu,plev_profs
     364     :         ,t_profs,thl_profs,q_profs,u_profs,v_profs,w_profs
     365     :         ,omega_profs,o3mmr_profs
     366     :         ,t_mod,thl_mod,q_mod,u_mod,v_mod,w_mod
     367     :         ,omega_mod,o3mmr_mod,mxcalc)
     368!calcul de l'advection verticale
     369cCalcul des gradients verticaux
     370cinitialisation
     371      d_t_z(:)=0.
     372      d_q_z(:)=0.
     373      d_t_dyn_z(:)=0.
     374      d_q_dyn_z(:)=0.
     375! schema centre
     376!     DO l=2,llm-1
     377!      d_t_z(l)=(temp(l+1)-temp(l-1))
     378!    &          /(play(l+1)-play(l-1))
     379!      d_q_z(l)=(q(l+1,1)-q(l-1,1))
     380!    &          /(play(l+1)-play(l-1))
     381! schema amont
     382      DO l=2,llm-1
     383       d_t_z(l)=(temp(l+1)-temp(l))/(play(l+1)-play(l))
     384       d_q_z(l)=(q(l+1,1)-q(l,1))/(play(l+1)-play(l))
     385!     print *,'l temp2 temp0 play2 play0 omega_mod',
     386!    & temp(l+1),temp(l-1),play(l+1),play(l-1),omega_mod(l)
     387      ENDDO
     388      d_t_z(1)=d_t_z(2)
     389      d_q_z(1)=d_q_z(2)
     390      d_t_z(llm)=d_t_z(llm-1)
     391      d_q_z(llm)=d_q_z(llm-1)
     392
     393!  calcul de l advection verticale
     394! Confusion w (m/s) et omega (Pa/s) !!
     395      d_t_dyn_z(:)=omega_mod(:)*d_t_z(:)
     396      d_q_dyn_z(:)=omega_mod(:)*d_q_z(:)
     397!     do l=1,llm
     398!      print *,'d_t_dyn omega_mod d_t_z d_q_dyn d_q_z',
     399!    :l,d_t_dyn_z(l),omega_mod(l),d_t_z(l),d_q_dyn_z(l),d_q_z(l)
     400!     enddo
     401
     402
     403! large-scale forcing : pour le cas Sandu ces forcages sont la SST
     404! et une divergence constante -> profil de omega
     405      tsurf = ts_prof
     406      write(*,*) 'SST suivante: ',tsurf
     407      do l = 1, llm
     408       omega(l) = omega_mod(l)
     409       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     410
     411       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
     412!
     413!      d_th_adv(l) = 0.0
     414!      d_q_adv(l,1) = 0.0
     415!CR:test advection=0
     416!calcul de l'advection verticale
     417        d_th_adv(l) = alpha*omega(l)/rcpd-d_t_dyn_z(l)
     418!        print*,'temp adv',l,-d_t_dyn_z(l)
     419        d_q_adv(l,1) = -d_q_dyn_z(l)
     420!        print*,'q adv',l,-d_q_dyn_z(l)
     421       dt_cooling(l) = 0.0
     422      enddo
     423      endif ! forcing_sandu
     424!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     425!---------------------------------------------------------------------
     426! Interpolation forcing in time and onto model levels
     427!---------------------------------------------------------------------
     428      if (forcing_astex) then
     429
     430        print*,
     431     : '#### ITAP,day,day1,(day-day1)*86400,(day-day1)*86400/dt_astex=',
     432     :    day,day1,(day-day1)*86400.,(day-day1)*86400/dt_astex
     433
     434! time interpolation:
     435! ATTENTION, cet appel ne convient pas pour TOGA !!
     436! revoir 1DUTILS.h et les arguments
     437      CALL interp_astex_time(daytime,day1,annee_ref
     438     i             ,year_ini_astex,day_ju_ini_astex,nt_astex,dt_astex
     439     i             ,nlev_astex,div_astex,ts_astex,ug_astex,vg_astex
     440     i             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof
     441     i             ,ufa_prof,vfa_prof)
     442
     443        if (type_ts_forcing.eq.1) ts_cur = ts_prof ! SST used in read_tsurf1d
     444
     445! vertical interpolation:
     446      CALL interp_astex_vertical(play,nlev_astex,plev_profa
     447     :         ,t_profa,thl_profa,qv_profa,ql_profa,qt_profa
     448     :         ,u_profa,v_profa,w_profa,tke_profa,o3mmr_profa
     449     :         ,t_mod,thl_mod,qv_mod,ql_mod,qt_mod,u_mod,v_mod,w_mod
     450     :         ,tke_mod,o3mmr_mod,mxcalc)
     451!calcul de l'advection verticale
     452!Calcul des gradients verticaux
     453!initialisation
     454      d_t_z(:)=0.
     455      d_q_z(:)=0.
     456      d_t_dyn_z(:)=0.
     457      d_q_dyn_z(:)=0.
     458! schema centre
     459!     DO l=2,llm-1
     460!      d_t_z(l)=(temp(l+1)-temp(l-1))
     461!    &          /(play(l+1)-play(l-1))
     462!      d_q_z(l)=(q(l+1,1)-q(l-1,1))
     463!    &          /(play(l+1)-play(l-1))
     464! schema amont
     465      DO l=2,llm-1
     466       d_t_z(l)=(temp(l+1)-temp(l))/(play(l+1)-play(l))
     467       d_q_z(l)=(q(l+1,1)-q(l,1))/(play(l+1)-play(l))
     468!     print *,'l temp2 temp0 play2 play0 omega_mod',
     469!    & temp(l+1),temp(l-1),play(l+1),play(l-1),omega_mod(l)
     470      ENDDO
     471      d_t_z(1)=d_t_z(2)
     472      d_q_z(1)=d_q_z(2)
     473      d_t_z(llm)=d_t_z(llm-1)
     474      d_q_z(llm)=d_q_z(llm-1)
     475
     476!  calcul de l advection verticale
     477! Confusion w (m/s) et omega (Pa/s) !!
     478      d_t_dyn_z(:)=w_mod(:)*d_t_z(:)
     479      d_q_dyn_z(:)=w_mod(:)*d_q_z(:)
     480!     do l=1,llm
     481!      print *,'d_t_dyn omega_mod d_t_z d_q_dyn d_q_z',
     482!    :l,d_t_dyn_z(l),omega_mod(l),d_t_z(l),d_q_dyn_z(l),d_q_z(l)
     483!     enddo
     484
     485
     486! large-scale forcing : pour le cas Astex ces forcages sont la SST
     487! la divergence,ug,vg,ufa,vfa
     488      tsurf = ts_prof
     489      write(*,*) 'SST suivante: ',tsurf
     490      do l = 1, llm
     491       omega(l) = w_mod(l)
     492       omega2(l)= omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     493
     494       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
     495!
     496!      d_th_adv(l) = 0.0
     497!      d_q_adv(l,1) = 0.0
     498!CR:test advection=0
     499!calcul de l'advection verticale
     500        d_th_adv(l) = alpha*omega(l)/rcpd-d_t_dyn_z(l)
     501!        print*,'temp adv',l,-d_t_dyn_z(l)
     502        d_q_adv(l,1) = -d_q_dyn_z(l)
     503!        print*,'q adv',l,-d_q_dyn_z(l)
     504       dt_cooling(l) = 0.0
     505      enddo
     506      endif ! forcing_astex
     507!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     508
  • LMDZ5/branches/testing/libf/phy1d/1D_read_forc_cases.h

    r1665 r1795  
    44!----------------------------------------------------------------------
    55
    6       if (forcing_les .or. forcing_radconv .or. forcing_GCSSold ) then
    7 
     6      if (forcing_les .or. forcing_radconv
     7     :    .or. forcing_GCSSold .or. forcing_fire) then
     8
     9      if (forcing_fire) then
     10!----------------------------------------------------------------------
     11!read fire forcings from fire.nc
     12!----------------------------------------------------------------------
     13      fich_fire='fire.nc'
     14      call read_fire(fich_fire,nlev_fire,nt_fire
     15     :     ,height,tttprof,qtprof,uprof,vprof,e12prof
     16     :     ,ugprof,vgprof,wfls,dqtdxls
     17     :     ,dqtdyls,dqtdtls,thlpcar)
     18      write(*,*) 'Forcing FIRE lu'
     19      kmax=120            ! nombre de niveaux dans les profils et forcages
     20      else
    821!----------------------------------------------------------------------
    922! Read profiles from files: prof.inp.001 and lscale.inp.001
     
    1629     .           wfls,dqtdxls,dqtdyls,dqtdtls,
    1730     .           thlpcar)
     31      endif
    1832
    1933! compute altitudes of play levels.
     
    3549        frac = (height(kmax)-zlay(l))/(height (kmax)-height(kmax-1))
    3650        ttt =tttprof(kmax)-frac*(tttprof(kmax)-tttprof(kmax-1))
    37         if (forcing_GCSSold .AND. tp_ini_GCSSold) then ! pot. temp. in initial profile
     51       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
    3852          temp(l) = ttt*(play(l)/pzero)**rkappa
    3953          teta(l) = ttt
    40         else
     54       else
    4155          temp(l) = ttt
    4256          teta(l) = ttt*(pzero/play(l))**rkappa
    43         endif
     57       endif
    4458          print *,' temp,teta ',l,temp(l),teta(l)
    4559        q(l,1)  = qtprof(kmax)-frac*( qtprof(kmax)- qtprof(kmax-1))
     
    5872          if(zlay(l)>height(k-1).and.zlay(l)<height(k)) then
    5973            ttt =tttprof(k)-frac*(tttprof(k)-tttprof(k-1))
    60         if (forcing_GCSSold .AND. tp_ini_GCSSold) then ! pot. temp. in initial profile
     74       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
    6175          temp(l) = ttt*(play(l)/pzero)**rkappa
    6276          teta(l) = ttt
    63         else
     77       else
    6478          temp(l) = ttt
    6579          teta(l) = ttt*(pzero/play(l))**rkappa
    66         endif
     80       endif
    6781          print *,' temp,teta ',l,temp(l),teta(l)
    6882            q(l,1)  = qtprof(k)-frac*( qtprof(k)- qtprof(k-1))
     
    7791          elseif(zlay(l)<height(1)) then ! profils uniformes pour z<height(1)
    7892            ttt =tttprof(1)
    79         if (forcing_GCSSold .AND. tp_ini_GCSSold) then ! pot. temp. in initial profile
     93       if ((forcing_GCSSold .AND. tp_ini_GCSSold) .OR. forcing_fire)then ! pot. temp. in initial profile
    8094          temp(l) = ttt*(play(l)/pzero)**rkappa
    8195          teta(l) = ttt
    82         else
     96       else
    8397          temp(l) = ttt
    8498          teta(l) = ttt*(pzero/play(l))**rkappa
    85         endif
     99       endif
    86100            q(l,1)  = qtprof(1)
    87101            u(l)    =  uprof(1)
     
    112126      enddo
    113127
    114       endif ! forcing_les .or. forcing_GCSSold
     128      endif ! forcing_les .or. forcing_GCSSold .or. forcing_fire
    115129!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    116130!---------------------------------------------------------------------
     
    263277       
    264278      endif !forcing_twpice
     279
     280!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     281!---------------------------------------------------------------------
     282! Forcing from AMMA experiment (Couvreux et al. 2010) :
     283!---------------------------------------------------------------------
     284
     285      if (forcing_amma) then
     286!read AMMA forcings
     287      fich_amma='amma.nc'
     288      call read_amma(fich_amma,nlev_amma,nt_amma
     289     :     ,z_amma,plev_amma,th_amma,q_amma,u_amma,v_amma,vitw_amma
     290     :     ,ht_amma,hq_amma,sens_amma,lat_amma)
     291
     292      write(*,*) 'Forcing AMMA lu'
     293
     294!champs initiaux:
     295      do k=1,nlev_amma
     296         th_ammai(k)=th_amma(k)
     297         q_ammai(k)=q_amma(k)
     298         u_ammai(k)=u_amma(k)
     299         v_ammai(k)=v_amma(k)
     300         vitw_ammai(k)=vitw_amma(k,12)
     301         ht_ammai(k)=ht_amma(k,12)
     302         hq_ammai(k)=hq_amma(k,12)
     303         vt_ammai(k)=0.
     304         vq_ammai(k)=0.
     305      enddo   
     306      omega(:)=0.     
     307      omega2(:)=0.
     308      rho(:)=0.
     309! vertical interpolation using TOGA interpolation routine:
     310!      write(*,*)'avant interp vert', t_proftwp
     311      CALL interp_toga_vertical(play,nlev_amma,plev_amma
     312     :         ,th_ammai,q_ammai,u_ammai,v_ammai,vitw_ammai
     313     :         ,ht_ammai,vt_ammai,hq_ammai,vq_ammai
     314     :         ,t_mod,q_mod,u_mod,v_mod,w_mod
     315     :         ,ht_mod,vt_mod,hq_mod,vq_mod,mxcalc)
     316!       write(*,*) 'Profil initial forcing TWP-ICE interpole',t_mod
     317
     318! initial and boundary conditions :
     319!      tsurf = ts_proftwp
     320      write(*,*) 'SST initiale mxcalc: ',tsurf,mxcalc
     321      do l = 1, llm
     322! Ligne du dessous à decommenter si on lit theta au lieu de temp
     323!      temp(l) = t_mod(l)*(play(l)/pzero)**rkappa
     324       temp(l) = t_mod(l)
     325       q(l,1) = q_mod(l)
     326       q(l,2) = 0.0
     327!      print *,'read_forc: l,temp,q=',l,temp(l),q(l,1)
     328       u(l) = u_mod(l)
     329       v(l) = v_mod(l)
     330       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
     331       omega(l) = w_mod(l)*(-rg*rho(l))
     332       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     333
     334       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
     335!on applique le forcage total au premier pas de temps
     336!attention: signe different de toga
     337       d_th_adv(l) = alpha*omega(l)/rcpd+ht_mod(l)
     338!forcage en th
     339!       d_th_adv(l) = ht_mod(l)
     340       d_q_adv(l,1) = hq_mod(l)
     341       d_q_adv(l,2) = 0.0
     342       dt_cooling(l)=0.
     343      enddo     
     344       write(*,*) 'Profil initial forcing AMMA interpole temp39',
     345     &           temp(39)
     346     
     347
     348!     ok_flux_surf=.false.
     349      fsens=-1.*sens_amma(12)
     350      flat=-1.*lat_amma(12)
     351       
     352      endif !forcing_amma
     353
     354
    265355!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    266356!---------------------------------------------------------------------
     
    366456      endif ! forcing_armcu
    367457!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    368 
     458!---------------------------------------------------------------------
     459! Forcing from transition case of Irina Sandu                 
     460!---------------------------------------------------------------------
     461
     462      if (forcing_sandu) then
     463       write(*,*) 'Avant lecture Forcing SANDU'
     464
     465! read sanduref forcing :
     466      fich_sandu = './ifa_sanduref.txt'
     467      CALL read_sandu(fich_sandu,nlev_sandu,nt_sandu,ts_sandu)
     468
     469       write(*,*) 'Forcing SANDU lu'
     470
     471!----------------------------------------------------------------------
     472! Read profiles from file: prof.inp.001
     473!----------------------------------------------------------------------
     474
     475      call readprofile_sandu(nlev_max,kmax,height,plev_profs,t_profs,
     476     .           thl_profs,q_profs,u_profs,v_profs,
     477     .           w_profs,omega_profs,o3mmr_profs)
     478
     479! time interpolation for initial conditions:
     480      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
     481! ATTENTION, cet appel ne convient pas pour le cas SANDU !!
     482! revoir 1DUTILS.h et les arguments
     483
     484      print *,'Avant interp_sandu_time'
     485      print *,'daytime=',daytime
     486      print *,'day1=',day1
     487      print *,'annee_ref=',annee_ref
     488      print *,'year_ini_sandu=',year_ini_sandu
     489      print *,'day_ju_ini_sandu=',day_ju_ini_sandu
     490      print *,'nt_sandu=',nt_sandu
     491      print *,'dt_sandu=',dt_sandu
     492      print *,'nlev_sandu=',nlev_sandu
     493      CALL interp_sandu_time(daytime,day1,annee_ref
     494     i             ,year_ini_sandu,day_ju_ini_sandu,nt_sandu,dt_sandu
     495     i             ,nlev_sandu
     496     i             ,ts_sandu,ts_prof)
     497
     498! vertical interpolation:
     499      print *,'Avant interp_vertical: nlev_sandu=',nlev_sandu
     500      CALL interp_sandu_vertical(play,nlev_sandu,plev_profs
     501     :         ,t_profs,thl_profs,q_profs,u_profs,v_profs,w_profs
     502     :         ,omega_profs,o3mmr_profs
     503     :         ,t_mod,thl_mod,q_mod,u_mod,v_mod,w_mod
     504     :         ,omega_mod,o3mmr_mod,mxcalc)
     505       write(*,*) 'Profil initial forcing SANDU interpole'
     506
     507! initial and boundary conditions :
     508      tsurf = ts_prof
     509      write(*,*) 'SST initiale: ',tsurf
     510      do l = 1, llm
     511       temp(l) = t_mod(l)
     512       tetal(l)=thl_mod(l)
     513       q(l,1) = q_mod(l)
     514       q(l,2) = 0.0
     515       u(l) = u_mod(l)
     516       v(l) = v_mod(l)
     517       w(l) = w_mod(l)
     518       omega(l) = omega_mod(l)
     519       omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     520!?       rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
     521!?       omega2(l)=-rho(l)*omega(l)
     522       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
     523!      d_th_adv(l) = alpha*omega(l)/rcpd+vt_mod(l)
     524!      d_q_adv(l,1) = vq_mod(l)
     525       d_th_adv(l) = alpha*omega(l)/rcpd
     526       d_q_adv(l,1) = 0.0
     527       d_q_adv(l,2) = 0.0
     528      enddo
     529
     530      endif ! forcing_sandu
     531!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     532!---------------------------------------------------------------------
     533! Forcing from Astex case
     534!---------------------------------------------------------------------
     535
     536      if (forcing_astex) then
     537       write(*,*) 'Avant lecture Forcing Astex'
     538
     539! read astex forcing :
     540      fich_astex = './ifa_astex.txt'
     541      CALL read_astex(fich_astex,nlev_astex,nt_astex,div_astex,ts_astex,
     542     :  ug_astex,vg_astex,ufa_astex,vfa_astex)
     543
     544       write(*,*) 'Forcing Astex lu'
     545
     546!----------------------------------------------------------------------
     547! Read profiles from file: prof.inp.001
     548!----------------------------------------------------------------------
     549
     550      call readprofile_astex(nlev_max,kmax,height,plev_profa,t_profa,
     551     .           thl_profa,qv_profa,ql_profa,qt_profa,u_profa,v_profa,
     552     .           w_profa,tke_profa,o3mmr_profa)
     553
     554! time interpolation for initial conditions:
     555      write(*,*) 'AVT 1ere INTERPOLATION: day,day1 = ',day,day1
     556! ATTENTION, cet appel ne convient pas pour le cas SANDU !!
     557! revoir 1DUTILS.h et les arguments
     558
     559      print *,'Avant interp_astex_time'
     560      print *,'daytime=',daytime
     561      print *,'day1=',day1
     562      print *,'annee_ref=',annee_ref
     563      print *,'year_ini_astex=',year_ini_astex
     564      print *,'day_ju_ini_astex=',day_ju_ini_astex
     565      print *,'nt_astex=',nt_astex
     566      print *,'dt_astex=',dt_astex
     567      print *,'nlev_astex=',nlev_astex
     568      CALL interp_astex_time(daytime,day1,annee_ref
     569     i             ,year_ini_astex,day_ju_ini_astex,nt_astex,dt_astex
     570     i             ,nlev_astex,div_astex,ts_astex,ug_astex,vg_astex
     571     i             ,ufa_astex,vfa_astex,div_prof,ts_prof,ug_prof,vg_prof
     572     i             ,ufa_prof,vfa_prof)
     573
     574! vertical interpolation:
     575      print *,'Avant interp_vertical: nlev_astex=',nlev_astex
     576      CALL interp_astex_vertical(play,nlev_astex,plev_profa
     577     :         ,t_profa,thl_profa,qv_profa,ql_profa,qt_profa
     578     :         ,u_profa,v_profa,w_profa,tke_profa,o3mmr_profa
     579     :         ,t_mod,thl_mod,qv_mod,ql_mod,qt_mod,u_mod,v_mod,w_mod
     580     :         ,tke_mod,o3mmr_mod,mxcalc)
     581       write(*,*) 'Profil initial forcing Astex interpole'
     582
     583! initial and boundary conditions :
     584      tsurf = ts_prof
     585      write(*,*) 'SST initiale: ',tsurf
     586      do l = 1, llm
     587       temp(l) = t_mod(l)
     588       tetal(l)=thl_mod(l)
     589       q(l,1) = qv_mod(l)
     590       q(l,2) = ql_mod(l)
     591       u(l) = u_mod(l)
     592       v(l) = v_mod(l)
     593       w(l) = w_mod(l)
     594       omega(l) = w_mod(l)
     595!      omega2(l)=omega(l)/rg*airefi ! flxmass_w calcule comme ds physiq
     596!      rho(l)  = play(l)/(rd*temp(l)*(1.+(rv/rd-1.)*q(l,1)))
     597!      omega2(l)=-rho(l)*omega(l)
     598       alpha = rd*temp(l)*(1.+(rv/rd-1.)*q(l,1))/play(l)
     599!      d_th_adv(l) = alpha*omega(l)/rcpd+vt_mod(l)
     600!      d_q_adv(l,1) = vq_mod(l)
     601       d_th_adv(l) = alpha*omega(l)/rcpd
     602       d_q_adv(l,1) = 0.0
     603       d_q_adv(l,2) = 0.0
     604      enddo
     605
     606      endif ! forcing_astex
     607
  • LMDZ5/branches/testing/libf/phy1d/compar1d.h

    r1665 r1795  
    2525
    2626      logical :: restart
     27      logical :: ok_old_disvert
    2728
    2829      common/com_par1d/forcing_type,nat_surf,tsurf,rugos,               &
    2930     & qsol,qsurf,psurf,zsurf,albedo,time,time_ini,xlat,xlon,airefi,    &
    3031     & wtsurf,wqsurf,restart_runoff,xagesno,qsolinp,zpicinp,            &
    31      & restart
     32     & restart,ok_old_disvert
    3233
    3334!$OMP THREADPRIVATE(/com_par1d/)
  • LMDZ5/branches/testing/libf/phy1d/lmdz1d.F

    r1750 r1795  
    66      use dimphy
    77      use surface_data, only : type_ocean,ok_veget
    8       use pbl_surface_mod, only : pbl_surface_init, pbl_surface_final
     8      use pbl_surface_mod, only : ftsoil, pbl_surface_init,
     9     $                            pbl_surface_final
    910      use fonte_neige_mod, only : fonte_neige_init, fonte_neige_final
    1011
    1112      use infotrac ! new
    1213      use control_mod
     14      USE indice_sol_mod
    1315
    1416      implicit none
     
    2022#include "clesphys.h"
    2123#include "dimsoil.h"
    22 #include "indicesol.h"
     24!#include "indicesol.h"
    2325
    2426#include "comvert.h"
    2527#include "compar1d.h"
    2628#include "flux_arp.h"
     29#include "tsoilnudge.h"
    2730#include "fcg_gcssold.h"
    2831!!!#include "fbforcing.h"
     
    8689
    8790        integer :: kmax = llm
    88         integer nlev_max
    89         parameter (nlev_max = 100)
     91        integer nlev_max,llm700
     92        parameter (nlev_max = 1000)
    9093        real timestep, frac, timeit
    9194        real height(nlev_max),tttprof(nlev_max),qtprof(nlev_max),
     
    98101c        integer :: forcing_type
    99102        logical :: forcing_les     = .false.
    100         logical :: forcing_armcu  = .false.
     103        logical :: forcing_armcu   = .false.
    101104        logical :: forcing_rico    = .false.
    102105        logical :: forcing_radconv = .false.
    103106        logical :: forcing_toga    = .false.
    104107        logical :: forcing_twpice  = .false.
     108        logical :: forcing_amma    = .false.
    105109        logical :: forcing_GCM2SCM = .false.
    106110        logical :: forcing_GCSSold = .false.
     111        logical :: forcing_sandu   = .false.
     112        logical :: forcing_astex   = .false.
     113        logical :: forcing_fire    = .false.
    107114        integer :: type_ts_forcing ! 0 = SST constant; 1 = SST read from a file
    108115!                                                            (cf read_tsurf1d.F)
    109116
    110117!vertical advection computation
    111         real d_t_z(llm), d_q_z(llm)
    112         real d_t_dyn_z(llm), d_q_dyn_z(llm)
    113         real zz(llm)
    114         real zfact
     118!       real d_t_z(llm), d_q_z(llm)
     119!       real d_t_dyn_z(llm), d_q_dyn_z(llm)
     120!       real zz(llm)
     121!       real zfact
    115122
    116123!flag forcings
     
    129136      real :: pzero=1.e5
    130137      real :: play (llm),zlay (llm),sig_s(llm),plev(llm+1)
    131       real :: playd(llm),zlayd(llm)
     138      real :: playd(llm),zlayd(llm),ap_amma(llm+1),bp_amma(llm+1),poub
    132139
    133140!---------------------------------------------------------------------
     
    137144      integer :: iq
    138145      real :: phi(llm)
    139       real :: teta(llm),temp(llm),u(llm),v(llm)
     146      real :: teta(llm),tetal(llm),temp(llm),u(llm),v(llm),w(llm)
     147      real :: rlat_rad(1),rlon_rad(1)
    140148      real :: omega(llm+1),omega2(llm),rho(llm+1)
    141149      real :: ug(llm),vg(llm),fcoriolis
     150      real :: sfdt, cfdt
    142151      real :: du_phys(llm),dv_phys(llm),dt_phys(llm)
    143152      real :: du_dyn(llm),dv_dyn(llm),dt_dyn(llm)
     
    194203!  Fichiers et d'autres variables
    195204!---------------------------------------------------------------------
    196       real ttt
     205      real ttt,bow,q1
    197206      integer :: ierr,k,l,i,it=1,mxcalc
    198207      integer jjmp1
     
    250259!             initial profiles from RICO files
    251260!             LS convergence imposed from RICO files
     261!forcing_type = 6 ==> forcing_amma = .true.
     262!             initial profiles from AMMA nc file
     263!             LS convergence, omega and surface fluxes imposed from AMMA file 
    252264!forcing_type = 40 ==> forcing_GCSSold = .true.
    253265!             initial profile from GCSS file
    254266!             LS convergence imposed from GCSS file
     267!forcing_type = 59 ==> forcing_sandu = .true.
     268!             initial profiles from sanduref file: see prof.inp.001
     269!             SST varying with time and divergence constante: see ifa_sanduref.txt file
     270!             Radiation has to be computed interactively
     271!forcing_type = 60 ==> forcing_astex = .true.
     272!             initial profiles from file: see prof.inp.001
     273!             SST,divergence,ug,vg,ufa,vfa varying with time : see ifa_astex.txt file
     274!             Radiation has to be computed interactively
    255275!forcing_type = 61 ==> forcing_armcu = .true.
    256 !             initial profile from arm_cu file
    257 !             LS convergence imposed from arm_cu file
     276!             initial profiles from file: see prof.inp.001
     277!             sensible and latent heat flux imposed: see ifa_arm_cu_1.txt
     278!             large scale advective forcing & radiative tendencies applied below 1000m: see ifa_arm_cu_2.txt
     279!             use geostrophic wind ug=10m/s vg=0m/s. Duration of the case 53100s
     280!             Radiation to be switched off
    258281!
    259282      if (forcing_type .eq.0) THEN
     
    269292      elseif (forcing_type .eq.5) THEN
    270293       forcing_rico = .true.
     294      elseif (forcing_type .eq.6) THEN
     295       forcing_amma = .true.
    271296      elseif (forcing_type .eq.40) THEN
    272297       forcing_GCSSold = .true.
     298      elseif (forcing_type .eq.59) THEN
     299       forcing_sandu   = .true.
     300      elseif (forcing_type .eq.60) THEN
     301       forcing_astex   = .true.
    273302      elseif (forcing_type .eq.61) THEN
    274303       forcing_armcu = .true.
     
    276305      else
    277306       write (*,*) 'ERROR : unknown forcing_type ', forcing_type
    278        stop 'Forcing_type should be 0,1,2,3 or 40'
     307       stop 'Forcing_type should be 0,1,2,3,4,5,6 or 40,59,60,61'
    279308      ENDIF
    280309      print*,"forcing type=",forcing_type
     
    286315
    287316        type_ts_forcing = 0
    288         if (forcing_toga) type_ts_forcing = 1
     317        if (forcing_toga .or. forcing_sandu .or. forcing_astex)
     318     :    type_ts_forcing = 1
    289319
    290320!---------------------------------------------------------------------
     
    325355c Special case for arm_cu which lasts less than one day : 53100s !! (MPL 20111026)
    326356      IF(forcing_type .EQ. 61) fnday=53100./86400.
     357c Special case for amma which lasts less than one day : 64800s !! (MPL 20120216)
     358      IF(forcing_type .EQ. 6) fnday=64800./86400.
    327359      annee_ref = anneeref
    328360      mois = 1
     
    334366      day_ini = day
    335367      day_end = day_ini + nday
     368
     369      IF (forcing_type .eq.2) THEN
    336370! Convert the initial date of Toga-Coare to Julian day
    337371      call ymds2ju
    338372     $ (year_ini_toga,mth_ini_toga,day_ini_toga,heure,day_ju_ini_toga)
    339373
     374      ELSEIF (forcing_type .eq.4) THEN
    340375! Convert the initial date of TWPICE to Julian day
    341376      call ymds2ju
    342377     $ (year_ini_twpi,mth_ini_twpi,day_ini_twpi,heure_ini_twpi
    343378     $ ,day_ju_ini_twpi)
    344 
    345 ! Convert the initial date of Arm_cu to Julian day
     379      ELSEIF (forcing_type .eq.6) THEN
     380! Convert the initial date of AMMA to Julian day
     381      call ymds2ju
     382     $ (year_ini_amma,mth_ini_amma,day_ini_amma,heure_ini_amma
     383     $ ,day_ju_ini_amma)
     384
     385      ELSEIF (forcing_type .eq.59) THEN
     386! Convert the initial date of Sandu case to Julian day
     387      call ymds2ju
     388     $   (year_ini_sandu,mth_ini_sandu,day_ini_sandu,
     389     $    time_ini*3600.,day_ju_ini_sandu)
     390
     391      ELSEIF (forcing_type .eq.60) THEN
     392! Convert the initial date of Astex case to Julian day
     393      call ymds2ju
     394     $   (year_ini_astex,mth_ini_astex,day_ini_astex,
     395     $    time_ini*3600.,day_ju_ini_astex)
     396
     397      ELSEIF (forcing_type .eq.61) THEN
     398
     399! Convert the initial date of Arm_cu case to Julian day
    346400      call ymds2ju
    347401     $ (year_ini_armcu,mth_ini_armcu,day_ini_armcu,heure_ini_armcu
    348402     $ ,day_ju_ini_armcu)
     403      ENDIF
    349404
    350405      daytime = day + time_ini/24. ! 1st day and initial time of the simulation
     
    418473!!      preff= 1.01325e5
    419474      preff = psurf
    420       call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
     475      IF (ok_old_disvert) THEN
     476        call disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
     477        print *,'On utilise disvert0'
     478      ELSE
     479        call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,
     480     :                 scaleheight)
     481        print *,'On utilise disvert'
     482c       Nouvelle version disvert permettant d imposer ap,bp (modif L.Guez) MPL 18092012
     483c       Dans ce cas, on lit ap,bp dans le fichier hybrid.txt
     484      ENDIF
    421485      sig_s=presnivs/preff
    422486      plev =ap+bp*psurf
     
    424488ccc      zlay=-rd*300.*log(play/psurf)/rg ! moved after reading profiles
    425489
     490      IF (forcing_type .eq. 59) THEN
     491! pour forcing_sandu, on cherche l'indice le plus proche de 700hpa#3000m
    426492      write(*,*) '***********************'
    427493      do l = 1, llm
    428494       write(*,*) 'l,play(l),presnivs(l): ',l,play(l),presnivs(l)
     495       if (trouve_700 .and. play(l).le.70000) then
     496         llm700=l
     497         print *,'llm700,play=',llm700,play(l)/100.
     498         trouve_700= .false.
     499       endif
    429500      enddo
    430501      write(*,*) '***********************'
     502      ENDIF
    431503
    432504c
     
    460532! rday: defini dans suphel.F (86400.)
    461533! day_ini: lu dans run.def (dayref)
    462 ! rlat,rlon lus dans lmdz1d.def
     534! rlat_rad,rlon-rad: transformes en radian de rlat,rlon lus dans lmdz1d.def (en degres)
    463535! airefi,zcufi,zcvfi initialises au debut de ce programme
    464536! rday,ra,rg,rd,rcpd declares dans YOMCST.h et calcules dans suphel.F
     
    470542      zcufi=airefi
    471543      zcvfi=airefi
     544!
     545      rlat_rad(:)=rlat(:)*rpi/180.
     546      rlon_rad(:)=rlon(:)*rpi/180.
    472547
    473548      call iniphysiq(ngrid,llm,rday,day_ini,timestep,
    474      .     rlat,rlon,airefi,zcufi,zcvfi,ra,rg,rd,rcpd,1)
     549     .     rlat_rad,rlon_rad,airefi,zcufi,zcvfi,ra,rg,rd,rcpd,(/1/))
    475550      print*,'apres iniphysiq'
    476551
     
    501576        agesno  = xagesno
    502577        tsoil(:,:,:)=tsurf
     578!------ AMMA 2e run avec modele sol et rayonnement actif (MPL 23052012)
     579!       tsoil(1,1,1)=299.18
     580!       tsoil(1,2,1)=300.08
     581!       tsoil(1,3,1)=301.88
     582!       tsoil(1,4,1)=305.48
     583!       tsoil(1,5,1)=308.00
     584!       tsoil(1,6,1)=308.00
     585!       tsoil(1,7,1)=308.00
     586!       tsoil(1,8,1)=308.00
     587!       tsoil(1,9,1)=308.00
     588!       tsoil(1,10,1)=308.00
     589!       tsoil(1,11,1)=308.00
     590!-----------------------------------------------------------------------
    503591        call pbl_surface_init(qsol, fder, snsrf, qsurfsrf,
    504592     &                                    evap, frugs, agesno, tsoil)
     
    734822       endif
    735823
    736        if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice) then
     824       if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice
     825     :    .or.forcing_amma) then
    737826         fcoriolis=0.0 ; ug=0. ; vg=0.
    738827       endif
     
    748837     : -fcoriolis*(u(1:mxcalc)-ug(1:mxcalc))
    749838
     839!!!!!!!!!!!!!!!!!!!!!!!!
     840! Geostrophic wind
     841!!!!!!!!!!!!!!!!!!!!!!!!
     842       sfdt = sin(0.5*fcoriolis*timestep)
     843       cfdt = cos(0.5*fcoriolis*timestep)
     844!
     845        du_age(1:mxcalc)= -2.*sfdt/timestep*
     846     :          (sfdt*(u(1:mxcalc)-ug(1:mxcalc)) -
     847     :           cfdt*(v(1:mxcalc)-vg(1:mxcalc))  )
     848!!     : fcoriolis*(v(1:mxcalc)-vg(1:mxcalc))
     849!
     850       dv_age(1:mxcalc)= -2.*sfdt/timestep*
     851     :          (cfdt*(u(1:mxcalc)-ug(1:mxcalc)) +
     852     :           sfdt*(v(1:mxcalc)-vg(1:mxcalc))  )
     853!!     : -fcoriolis*(u(1:mxcalc)-ug(1:mxcalc))
     854!
     855!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     856!         call  writefield_phy('dv_age' ,dv_age,llm)
     857!         call  writefield_phy('du_age' ,du_age,llm)
     858!         call  writefield_phy('du_phys' ,du_phys,llm)
     859!         call  writefield_phy('u_tend' ,u,llm)
     860!         call  writefield_phy('u_g' ,ug,llm)
     861!
     862!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     863!! Increment state variables
     864!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    750865        u(1:mxcalc)=u(1:mxcalc) + timestep*(
    751866     :              du_phys(1:mxcalc)
     
    773888
    774889        teta=temp*(pzero/play)**rkappa
     890!
     891!---------------------------------------------------------------------
     892!   Nudge soil temperature if requested
     893!---------------------------------------------------------------------
     894
     895      IF (nudge_tsoil) THEN
     896       ftsoil(1,isoil_nudge,:) = ftsoil(1,isoil_nudge,:)
     897     .  -timestep/tau_soil_nudge*(ftsoil(1,isoil_nudge,:)-Tsoil_nudge)
     898      ENDIF
    775899
    776900!---------------------------------------------------------------------
  • LMDZ5/branches/testing/libf/phy1d/ocean_forced_mod.F90

    r1665 r1795  
    3131    USE limit_read_mod
    3232    USE mod_grid_phy_lmdz
    33     INCLUDE "indicesol.h"
     33    USE indice_sol_mod
     34!    INCLUDE "indicesol.h"
    3435    INCLUDE "YOMCST.h"
    3536
     
    145146    USE limit_read_mod
    146147    USE fonte_neige_mod,  ONLY : fonte_neige
    147 
    148     INCLUDE "indicesol.h"
     148    USE indice_sol_mod
     149
     150!    INCLUDE "indicesol.h"
    149151    INCLUDE "dimsoil.h"
    150152    INCLUDE "YOMCST.h"
  • LMDZ5/branches/testing/libf/phy1d/surf_land_bucket_mod.F90

    r1665 r1795  
    2626    USE mod_grid_phy_lmdz
    2727    USE mod_phys_lmdz_para
     28    USE indice_sol_mod
    2829!****************************************************************************************
    2930! Bucket calculations for surface.
    3031!
    3132    INCLUDE "clesphys.h"
    32     INCLUDE "indicesol.h"
     33!    INCLUDE "indicesol.h"
    3334    INCLUDE "dimsoil.h"
    3435    INCLUDE "YOMCST.h"
Note: See TracChangeset for help on using the changeset viewer.