Ignore:
Timestamp:
Jul 16, 2013, 11:22:04 AM (11 years ago)
Author:
Ehouarn Millour
Message:

Transformation de l'include indicesol.h en un module indice_sol_mod et modification des appels dans tous les fichiers concernés.
Aucun changement des résultats ni des sorties du modèle vs 1784.
UG

...................................................

Replacement of the indicesol.h include by a module named indice_sol_mod. Modification of the calls in every affected files.
Results and outputs of simulations are unchanged in comparison with rev 1784.
UG

Location:
LMDZ5/trunk/libf/phy1d
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phy1d/lmdz1d.F

    r1780 r1785  
    22
    33      USE ioipsl, only: ju2ymds, ymds2ju, ioconf_calendar
    4       use phys_state_var_mod
    5       use comgeomphy
    6       use dimphy
    7       use surface_data, only : type_ocean,ok_veget
    8       use pbl_surface_mod, only : ftsoil, pbl_surface_init,
    9      $                            pbl_surface_final
    10       use fonte_neige_mod, only : fonte_neige_init, fonte_neige_final
    11 
    12       use infotrac ! new
    13       use control_mod
     4      USE phys_state_var_mod
     5      USE comgeomphy
     6      USE dimphy
     7      USE surface_data, only : type_ocean,ok_veget
     8      USE pbl_surface_mod, only : pbl_surface_init, pbl_surface_final
     9      USE fonte_neige_mod, only : fonte_neige_init, fonte_neige_final
     10
     11      USE infotrac ! new
     12      USE control_mod
     13      USE indice_sol_mod
    1414
    1515      implicit none
     
    2121#include "clesphys.h"
    2222#include "dimsoil.h"
    23 #include "indicesol.h"
     23!#include "indicesol.h"
    2424
    2525#include "comvert.h"
    2626#include "compar1d.h"
    2727#include "flux_arp.h"
    28 #include "tsoilnudge.h"
    2928#include "fcg_gcssold.h"
    3029!!!#include "fbforcing.h"
     
    8887
    8988        integer :: kmax = llm
    90         integer nlev_max,llm700
    91         parameter (nlev_max = 1000)
     89        integer nlev_max
     90        parameter (nlev_max = 100)
    9291        real timestep, frac, timeit
    9392        real height(nlev_max),tttprof(nlev_max),qtprof(nlev_max),
     
    10099c        integer :: forcing_type
    101100        logical :: forcing_les     = .false.
    102         logical :: forcing_armcu   = .false.
     101        logical :: forcing_armcu  = .false.
    103102        logical :: forcing_rico    = .false.
    104103        logical :: forcing_radconv = .false.
    105104        logical :: forcing_toga    = .false.
    106105        logical :: forcing_twpice  = .false.
    107         logical :: forcing_amma    = .false.
    108106        logical :: forcing_GCM2SCM = .false.
    109107        logical :: forcing_GCSSold = .false.
    110         logical :: forcing_sandu   = .false.
    111         logical :: forcing_astex   = .false.
    112         logical :: forcing_fire    = .false.
    113108        integer :: type_ts_forcing ! 0 = SST constant; 1 = SST read from a file
    114109!                                                            (cf read_tsurf1d.F)
    115110
    116111!vertical advection computation
    117 !       real d_t_z(llm), d_q_z(llm)
    118 !       real d_t_dyn_z(llm), d_q_dyn_z(llm)
    119 !       real zz(llm)
    120 !       real zfact
     112        real d_t_z(llm), d_q_z(llm)
     113        real d_t_dyn_z(llm), d_q_dyn_z(llm)
     114        real zz(llm)
     115        real zfact
    121116
    122117!flag forcings
     
    135130      real :: pzero=1.e5
    136131      real :: play (llm),zlay (llm),sig_s(llm),plev(llm+1)
    137       real :: playd(llm),zlayd(llm),ap_amma(llm+1),bp_amma(llm+1),poub
     132      real :: playd(llm),zlayd(llm)
    138133
    139134!---------------------------------------------------------------------
     
    143138      integer :: iq
    144139      real :: phi(llm)
    145       real :: teta(llm),tetal(llm),temp(llm),u(llm),v(llm),w(llm)
    146140      real :: rlat_rad(1),rlon_rad(1)
     141      real :: teta(llm),temp(llm),u(llm),v(llm)
    147142      real :: omega(llm+1),omega2(llm),rho(llm+1)
    148143      real :: ug(llm),vg(llm),fcoriolis
     
    202197!  Fichiers et d'autres variables
    203198!---------------------------------------------------------------------
    204       real ttt,bow,q1
     199      real ttt
    205200      integer :: ierr,k,l,i,it=1,mxcalc
    206201      integer jjmp1
     
    258253!             initial profiles from RICO files
    259254!             LS convergence imposed from RICO files
    260 !forcing_type = 6 ==> forcing_amma = .true.
    261 !             initial profiles from AMMA nc file
    262 !             LS convergence, omega and surface fluxes imposed from AMMA file 
    263255!forcing_type = 40 ==> forcing_GCSSold = .true.
    264256!             initial profile from GCSS file
    265257!             LS convergence imposed from GCSS file
    266 !forcing_type = 59 ==> forcing_sandu = .true.
    267 !             initial profiles from sanduref file: see prof.inp.001
    268 !             SST varying with time and divergence constante: see ifa_sanduref.txt file
    269 !             Radiation has to be computed interactively
    270 !forcing_type = 60 ==> forcing_astex = .true.
    271 !             initial profiles from file: see prof.inp.001
    272 !             SST,divergence,ug,vg,ufa,vfa varying with time : see ifa_astex.txt file
    273 !             Radiation has to be computed interactively
    274258!forcing_type = 61 ==> forcing_armcu = .true.
    275 !             initial profiles from file: see prof.inp.001
    276 !             sensible and latent heat flux imposed: see ifa_arm_cu_1.txt
    277 !             large scale advective forcing & radiative tendencies applied below 1000m: see ifa_arm_cu_2.txt
    278 !             use geostrophic wind ug=10m/s vg=0m/s. Duration of the case 53100s
    279 !             Radiation to be switched off
     259!             initial profile from arm_cu file
     260!             LS convergence imposed from arm_cu file
    280261!
    281262      if (forcing_type .eq.0) THEN
     
    291272      elseif (forcing_type .eq.5) THEN
    292273       forcing_rico = .true.
    293       elseif (forcing_type .eq.6) THEN
    294        forcing_amma = .true.
    295274      elseif (forcing_type .eq.40) THEN
    296275       forcing_GCSSold = .true.
    297       elseif (forcing_type .eq.59) THEN
    298        forcing_sandu   = .true.
    299       elseif (forcing_type .eq.60) THEN
    300        forcing_astex   = .true.
    301276      elseif (forcing_type .eq.61) THEN
    302277       forcing_armcu = .true.
     
    304279      else
    305280       write (*,*) 'ERROR : unknown forcing_type ', forcing_type
    306        stop 'Forcing_type should be 0,1,2,3,4,5,6 or 40,59,60,61'
     281       stop 'Forcing_type should be 0,1,2,3 or 40'
    307282      ENDIF
    308283      print*,"forcing type=",forcing_type
     
    314289
    315290        type_ts_forcing = 0
    316         if (forcing_toga .or. forcing_sandu .or. forcing_astex)
    317      :    type_ts_forcing = 1
     291        if (forcing_toga) type_ts_forcing = 1
    318292
    319293!---------------------------------------------------------------------
     
    354328c Special case for arm_cu which lasts less than one day : 53100s !! (MPL 20111026)
    355329      IF(forcing_type .EQ. 61) fnday=53100./86400.
    356 c Special case for amma which lasts less than one day : 64800s !! (MPL 20120216)
    357       IF(forcing_type .EQ. 6) fnday=64800./86400.
    358330      annee_ref = anneeref
    359331      mois = 1
     
    365337      day_ini = day
    366338      day_end = day_ini + nday
    367 
    368       IF (forcing_type .eq.2) THEN
    369339! Convert the initial date of Toga-Coare to Julian day
    370340      call ymds2ju
    371341     $ (year_ini_toga,mth_ini_toga,day_ini_toga,heure,day_ju_ini_toga)
    372342
    373       ELSEIF (forcing_type .eq.4) THEN
    374343! Convert the initial date of TWPICE to Julian day
    375344      call ymds2ju
    376345     $ (year_ini_twpi,mth_ini_twpi,day_ini_twpi,heure_ini_twpi
    377346     $ ,day_ju_ini_twpi)
    378       ELSEIF (forcing_type .eq.6) THEN
    379 ! Convert the initial date of AMMA to Julian day
    380       call ymds2ju
    381      $ (year_ini_amma,mth_ini_amma,day_ini_amma,heure_ini_amma
    382      $ ,day_ju_ini_amma)
    383 
    384       ELSEIF (forcing_type .eq.59) THEN
    385 ! Convert the initial date of Sandu case to Julian day
    386       call ymds2ju
    387      $   (year_ini_sandu,mth_ini_sandu,day_ini_sandu,
    388      $    time_ini*3600.,day_ju_ini_sandu)
    389 
    390       ELSEIF (forcing_type .eq.60) THEN
    391 ! Convert the initial date of Astex case to Julian day
    392       call ymds2ju
    393      $   (year_ini_astex,mth_ini_astex,day_ini_astex,
    394      $    time_ini*3600.,day_ju_ini_astex)
    395 
    396       ELSEIF (forcing_type .eq.61) THEN
    397 
    398 ! Convert the initial date of Arm_cu case to Julian day
     347
     348! Convert the initial date of Arm_cu to Julian day
    399349      call ymds2ju
    400350     $ (year_ini_armcu,mth_ini_armcu,day_ini_armcu,heure_ini_armcu
    401351     $ ,day_ju_ini_armcu)
    402       ENDIF
    403352
    404353      daytime = day + time_ini/24. ! 1st day and initial time of the simulation
     
    487436ccc      zlay=-rd*300.*log(play/psurf)/rg ! moved after reading profiles
    488437
    489       IF (forcing_type .eq. 59) THEN
    490 ! pour forcing_sandu, on cherche l'indice le plus proche de 700hpa#3000m
    491438      write(*,*) '***********************'
    492439      do l = 1, llm
    493440       write(*,*) 'l,play(l),presnivs(l): ',l,play(l),presnivs(l)
    494        if (trouve_700 .and. play(l).le.70000) then
    495          llm700=l
    496          print *,'llm700,play=',llm700,play(l)/100.
    497          trouve_700= .false.
    498        endif
    499441      enddo
    500442      write(*,*) '***********************'
    501       ENDIF
    502443
    503444c
     
    575516        agesno  = xagesno
    576517        tsoil(:,:,:)=tsurf
    577 !------ AMMA 2e run avec modele sol et rayonnement actif (MPL 23052012)
    578 !       tsoil(1,1,1)=299.18
    579 !       tsoil(1,2,1)=300.08
    580 !       tsoil(1,3,1)=301.88
    581 !       tsoil(1,4,1)=305.48
    582 !       tsoil(1,5,1)=308.00
    583 !       tsoil(1,6,1)=308.00
    584 !       tsoil(1,7,1)=308.00
    585 !       tsoil(1,8,1)=308.00
    586 !       tsoil(1,9,1)=308.00
    587 !       tsoil(1,10,1)=308.00
    588 !       tsoil(1,11,1)=308.00
    589 !-----------------------------------------------------------------------
    590518        call pbl_surface_init(qsol, fder, snsrf, qsurfsrf,
    591519     &                                    evap, frugs, agesno, tsoil)
     
    821749       endif
    822750
    823        if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice
    824      :    .or.forcing_amma) then
     751       if (forcing_toga .or. forcing_GCSSold .or. forcing_twpice) then
    825752         fcoriolis=0.0 ; ug=0. ; vg=0.
    826753       endif
     
    887814
    888815        teta=temp*(pzero/play)**rkappa
    889 !
    890 !---------------------------------------------------------------------
    891 !   Nudge soil temperature if requested
    892 !---------------------------------------------------------------------
    893 
    894       IF (nudge_tsoil) THEN
    895        ftsoil(1,isoil_nudge,:) = ftsoil(1,isoil_nudge,:)
    896      .  -timestep/tau_soil_nudge*(ftsoil(1,isoil_nudge,:)-Tsoil_nudge)
    897       ENDIF
    898816
    899817!---------------------------------------------------------------------
  • LMDZ5/trunk/libf/phy1d/ocean_forced_mod.F90

    r1607 r1785  
    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/trunk/libf/phy1d/pbl_surface_mod.F90

    r1780 r1785  
    2323  USE coef_diff_turb_mod,  ONLY : coef_diff_turb
    2424  USE control_mod
     25  USE indice_sol_mod
    2526
    2627
     
    5758! for the index of the different surfaces and tests the choice of type of ocean.
    5859
    59     INCLUDE "indicesol.h"
    6060    INCLUDE "dimsoil.h"
    6161    INCLUDE "iniprint.h"
     
    250250    IMPLICIT NONE
    251251
    252     INCLUDE "indicesol.h"
    253252    INCLUDE "dimsoil.h"
    254253    INCLUDE "YOMCST.h"
     
    13191318       evap_rst, rugos_rst, agesno_rst, ftsoil_rst)
    13201319
    1321     INCLUDE "indicesol.h"
    13221320    INCLUDE "dimsoil.h"
    13231321
     
    13691367    ! Give default values where new fraction has appread
    13701368
    1371     INCLUDE "indicesol.h"
    13721369    INCLUDE "dimsoil.h"
    13731370    INCLUDE "clesphys.h"
  • LMDZ5/trunk/libf/phy1d/surf_land_bucket_mod.F90

    r1607 r1785  
    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.