Changeset 1921


Ignore:
Timestamp:
Dec 20, 2013, 10:04:40 AM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r1909:1920 into testing branch

Location:
LMDZ5/branches/testing
Files:
15 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

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

    r1910 r1921  
    105105!             initial profile from GCSS file
    106106!             LS convergence imposed from GCSS file
     107!         = 50 ==> forcing_fire = .true.
    107108!         = 59 ==> forcing_sandu = .true.
    108109!             initial profiles from sanduref file: see prof.inp.001
  • LMDZ5/branches/testing/libf/phy1d/lmdz1d.F

    r1910 r1921  
    266266!             initial profile from GCSS file
    267267!             LS convergence imposed from GCSS file
     268!forcing_type = 50 ==> forcing_fire = .true.
     269!             forcing from fire.nc
    268270!forcing_type = 59 ==> forcing_sandu = .true.
    269271!             initial profiles from sanduref file: see prof.inp.001
     
    297299      elseif (forcing_type .eq.40) THEN
    298300       forcing_GCSSold = .true.
     301      elseif (forcing_type .eq.50) THEN
     302       forcing_fire = .true.
    299303      elseif (forcing_type .eq.59) THEN
    300304       forcing_sandu   = .true.
     
    818822
    819823       fcoriolis=2.*sin(rpi*xlat/180.)*romega
    820        if (forcing_radconv) then
     824       if (forcing_radconv .or. forcing_fire) then
    821825         fcoriolis=0.0
    822826         dt_cooling=0.0
  • LMDZ5/branches/testing/libf/phylmd/calcul_STDlev.h

    r1910 r1921  
    66        missing_val=nf90_fill_real
    77!
    8 !IM freq_moyNMC = frequences auxquelles on moyenne les champs accumules
    9 !IM               sur les niveaux de pression standard du NMC
    10       DO n=1, nout
    11        freq_moyNMC(n)=freq_outNMC(n)/freq_calNMC(n)
    12       ENDDO
    13 !
    14         CALL ini_undefSTD(itap,freq_outNMC)
     8        CALL ini_undefSTD(itap,itapm1)
    159!
    1610!IM on interpole les champs sur les niveaux STD de pression
     
    135129!IM on somme les valeurs toutes les freq_calNMC secondes
    136130!
    137        CALL undefSTD(itap,freq_calNMC, read_climoz)
    138 !
    139 !IM on moyenne a la fin du mois ou du jour (toutes les freq_outNMC secondes)
    140 !
    141        CALL moy_undefSTD(itap,freq_outNMC,freq_moyNMC)
     131       CALL undefSTD(itap, read_climoz)
     132!
     133!IM on moyenne a la fin du mois, du jour ou toutes les 6h
     134!
     135       CALL moy_undefSTD(itap,itapm1)
    142136!
    143137       CALL plevel(klon,klev,.true.,pplay,50000., &
  • LMDZ5/branches/testing/libf/phylmd/calcul_divers.h

    r1910 r1921  
    22! $Header$
    33!
    4 
    5 !     Initialisations diverses au "debut" du mois
    6       IF(debut) THEN
    7          nday_rain(:)=0.
    8 
     4! Initialisations diverses au tout debut
     5      IF(itap.EQ.1) THEN
     6         itapm1=0
    97!        surface terre
    10          paire_ter(:)=0.
    118         DO i=1, klon
    129            IF(pctsrf(i,is_ter).GT.0.) THEN
     
    1613      ENDIF
    1714
    18 !IM   Calcul une fois par jour : total_rain, nday_rain
    19       IF(MOD(itap,INT(un_jour/dtime)).EQ.0) THEN
     15! Initialisation debut de mois
     16      IF(itap.EQ.itapm1+1) THEN
     17        nday_rain(:)=0.
     18!       print*,'initialisation mois suivants day_rain itap',itap
     19      ENDIF
     20
     21! Calcul fin de journee : total_rain, nday_rain
     22      IF(MOD(itap,NINT(un_jour/dtime)).EQ.0) THEN
     23!        print*,'calcul nday_rain itap ',itap
    2024         DO i = 1, klon
    2125            total_rain(i)=rain_fall(i)+snow_fall(i) 
     
    2327         ENDDO
    2428      ENDIF
     29
     30! Initialisation fin de mois
     31      IF(MOD(itap-itapm1,NINT(mth_len*un_jour/dtime)).EQ.0) THEN
     32        itapm1=itapm1+NINT(mth_len*un_jour/dtime)
     33!       print*,'initialisation itapm1 ',itapm1
     34      ENDIF
  • LMDZ5/branches/testing/libf/phylmd/conf_phys_m.F90

    r1910 r1921  
    13361336!Config Desc = freq_outNMC(2) = frequence de sortie fichiers histdayNMC
    13371337!Config Desc = freq_outNMC(3) = frequence de sortie fichiers histhfNMC
    1338 !Config Def  = 2592000., 86400., 21600.
    1339 !Config Help =
    1340 !
    1341   freq_outNMC_omp(1) = mth_len*86400.
    1342   freq_outNMC_omp(2) = 86400.
    1343   freq_outNMC_omp(3) = 21600.
     1338!Config Def  = 2592000., 86400., 21600. (1mois, 1jour, 6h)
     1339!Config Help =
     1340!
     1341  freq_outNMC_omp(1) = mth_len
     1342  freq_outNMC_omp(2) = 1.
     1343  freq_outNMC_omp(3) = 1./4.
    13441344  call getin('freq_outNMC',freq_outNMC_omp)
    13451345!
  • LMDZ5/branches/testing/libf/phylmd/indice_sol_mod.F90

    r1910 r1921  
    44                              ! terre ! ocean ! glacier continental ! glace de mer
    55
    6             INTEGER, PARAMETER :: is_ave=nbsrf+1 ! glacier continental
     6            INTEGER, PARAMETER :: is_ave=nbsrf+1 ! valeur moyenne sur l'ensemble des surfaces
    77            REAL, PARAMETER :: epsfra=1.0E-05
    88
  • LMDZ5/branches/testing/libf/phylmd/ini_undefSTD.F

    r1910 r1921  
    33!
    44
    5       SUBROUTINE ini_undefSTD(itap,
    6      $           freq_outNMC)
     5      SUBROUTINE ini_undefSTD(itap,itapm1)
    76      USE dimphy
    87      USE phys_state_var_mod ! Variables sauvegardees de la physique
     8      USE phys_cal_mod, only : mth_len
    99      IMPLICIT none
     10      include "clesphys.h"
    1011c
    1112c====================================================================
     
    3637c variables Input/Output
    3738c     INTEGER nlevSTD, klevSTD, itap
    38       INTEGER itap
     39      INTEGER itap, itapm1
    3940c     PARAMETER(klevSTD=17)
    4041c     REAL dtime
     
    4445      INTEGER i, k, n
    4546c     PARAMETER(nout=3) !nout=1 day/nout=2 mth/nout=3 NMC
    46       REAL freq_outNMC(nout)
     47c     REAL freq_outNMC(nout)
     48      REAL un_jour
     49      PARAMETER(un_jour=86400.)
    4750c
    4851c variables Output
     
    5255      DO n=1, nout
    5356c
    54 c initialisation variables en debut de la journee ou du mois
     57c initialisation variables en debut du mois, de la journee ou des 6h
    5558c
    56        IF(MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.1.) THEN
     59       IF(n.EQ.1.AND.itap-itapm1.EQ.1.OR.
     60     &n.GT.1.AND.MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.1) THEN
     61c       print*,'ini_undefSTD n itap',n,itap
    5762        DO k=1, nlevSTD
    5863         DO i=1, klon
     
    7883         ENDDO !i
    7984        ENDDO !k
    80 c
    81        ENDIF !MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.1.
    82 c
     85       ENDIF !
    8386      ENDDO !n
    84 c
    8587      RETURN
    8688      END 
  • LMDZ5/branches/testing/libf/phylmd/moy_undefSTD.F

    r1910 r1921  
    22! $Id$
    33!
    4       SUBROUTINE moy_undefSTD(itap,freq_outNMC,freq_moyNMC)
     4      SUBROUTINE moy_undefSTD(itap,itapm1)
    55      USE netcdf
    66      USE dimphy
    7       USE phys_state_var_mod ! Variables sauvegardees de la physique
     7      USE phys_state_var_mod
     8      USE phys_cal_mod, only : mth_len
    89      IMPLICIT none
     10      include "clesphys.h"
    911c
    1012c====================================================================
     
    3335c     INTEGER nlevSTD, klevSTD, itap
    3436c     PARAMETER(klevSTD=17)
    35       INTEGER itap
     37      INTEGER itap, itapm1
    3638c
    3739c variables locales
     
    4042      INTEGER i, k, n
    4143c     REAL dtime, freq_outNMC(nout), freq_moyNMC(nout)
    42       REAL freq_outNMC(nout), freq_moyNMC(nout)
     44c     REAL freq_outNMC(nout), freq_calNMC(nout)
     45      REAL freq_moyNMC(nout)
    4346c
    4447c variables Output
     
    4649c     REAL tsumSTD(klon,klevSTD,nout)
    4750c
     51      REAL un_jour
     52      PARAMETER(un_jour=86400.)
    4853      REAL missing_val
    4954c
     
    5156c
    5257      DO n=1, nout
     58       IF(freq_outNMC(n).LT.0) THEN
     59         freq_moyNMC(n)=(mth_len*un_jour)/freq_calNMC(n)
     60c        print*,'moy_undefSTD n freq_out freq_moy =',
     61c    $n,freq_moyNMC(n)
     62       ELSE
     63         freq_moyNMC(n)=freq_outNMC(n)/freq_calNMC(n)
     64       ENDIF         
    5365c
    54 c calcul 1 fois par jour
     66c calcul 1 fois pas mois, 1 fois par jour ou toutes les 6h
    5567c
    56        IF(MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.0) THEN
     68       IF(n.EQ.1.AND.itap.EQ.itapm1.OR.
     69     $n.GT.1.AND.MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.0) THEN
     70c
     71c       print*,'moy_undefSTD n itap itapm1',n,itap,itapm1
    5772c
    5873        DO k=1, nlevSTD
     
    6176           tsumSTD(i,k,n)=tsumSTD(i,k,n)/
    6277     $     (freq_moyNMC(n)-tnondef(i,k,n))
    63 cIM BEG
    6478          usumSTD(i,k,n)=usumSTD(i,k,n)/
    6579     $     (freq_moyNMC(n)-tnondef(i,k,n))
     
    96110          O3daysumSTD(i,k,n)=O3daysumSTD(i,k,n)/
    97111     $     (freq_moyNMC(n)-tnondef(i,k,n))
    98 cIM END
    99112          ELSE
    100113           tsumSTD(i,k,n)=missing_val
  • LMDZ5/branches/testing/libf/phylmd/pbl_surface_mod.F90

    r1910 r1921  
    333333    REAL, DIMENSION(klon, klev),  INTENT(OUT)       :: d_u        ! change in u speed
    334334    REAL, DIMENSION(klon, klev),  INTENT(OUT)       :: d_v        ! change in v speed
    335     REAL, DIMENSION(klon, klev,nbsrf+1),  INTENT(OUT)       :: zcoefh     ! coef for turbulent diffusion of T and Q, mean for each grid point
    336     REAL, DIMENSION(klon, klev,nbsrf+1),  INTENT(OUT)       :: zcoefm     ! coef for turbulent diffusion of U and V (?), mean for each grid point
     335
     336    REAL, INTENT(OUT):: zcoefh(:, :, :) ! (klon, klev, nbsrf + 1)
     337    ! coef for turbulent diffusion of T and Q, mean for each grid point
     338
     339    REAL, INTENT(OUT):: zcoefm(:, :, :) ! (klon, klev, nbsrf + 1)
     340    ! coef for turbulent diffusion of U and V (?), mean for each grid point
    337341
    338342! Output only for diagnostics
  • LMDZ5/branches/testing/libf/phylmd/phys_output_ctrlout_mod.F90

    r1910 r1921  
    500500
    501501  TYPE(ctrl_out), SAVE, DIMENSION(7) :: o_uSTDlevs     = (/                    &
    502       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u850', "Zonal wind 1hPa", "m/s",     &
    503       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    504       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u700', "Zonal wind 2hPa", "m/s",     &
    505       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    506       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u500', "Zonal wind 3hPa", "m/s",     &
    507       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    508       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u200', "Zonal wind 4hPa", "m/s",     &
    509       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    510       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u100', "Zonal wind 5hPa", "m/s",     &
    511       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    512       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u50', "Zonal wind 6hPa", "m/s",     &
    513       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    514       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u10', "Zonal wind 7hPa", "m/s",     &
     502      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u850', "Zonal wind 850hPa", "m/s",     &
     503      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     504      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u700', "Zonal wind 700hPa", "m/s",     &
     505      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     506      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u500', "Zonal wind 500hPa", "m/s",     &
     507      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     508      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u200', "Zonal wind 200hPa", "m/s",     &
     509      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     510      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u100', "Zonal wind 100hPa", "m/s",     &
     511      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     512      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u50', "Zonal wind 50hPa", "m/s",     &
     513      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     514      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'u10', "Zonal wind 10hPa", "m/s",     &
    515515      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)) /)
    516516
    517517  TYPE(ctrl_out), SAVE, DIMENSION(7) :: o_vSTDlevs     = (/                     &
    518       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v850', "Meridional wind 1hPa", "m/s", &
     518      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v850', "Meridional wind 850hPa", "m/s", &
    519519      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)),  &
    520       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v700', "Meridional wind 2hPa", "m/s", &
     520      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v700', "Meridional wind 700hPa", "m/s", &
    521521      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)),  &
    522       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v500', "Meridional wind 3hPa", "m/s", &
     522      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v500', "Meridional wind 500hPa", "m/s", &
    523523      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)),  &
    524       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v200', "Meridional wind 4hPa", "m/s", &
     524      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v200', "Meridional wind 200hPa", "m/s", &
    525525      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)),  &
    526       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v100', "Meridional wind 5hPa", "m/s", &
     526      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v100', "Meridional wind 100hPa", "m/s", &
    527527      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)),  &
    528       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v50', "Meridional wind 6hPa", "m/s",  &
     528      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v50', "Meridional wind 50hPa", "m/s",  &
    529529      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)),  &
    530       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v10', "Meridional wind 7hPa", "m/s",  &
     530      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'v10', "Meridional wind 10hPa", "m/s",  &
    531531      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)) /)
    532532
     
    534534      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w850', "Vertical wind 1hPa", "Pa/s", &
    535535      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    536       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w700', "Vertical wind 2hPa", "Pa/s", &
    537       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    538       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w500', "Vertical wind 3hPa", "Pa/s", &
    539       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    540       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w200', "Vertical wind 4hPa", "Pa/s", &
    541       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    542       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w100', "Vertical wind 5hPa", "Pa/s", &
    543       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    544       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w50', "Vertical wind 6hPa", "Pa/s",  &
    545       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    546       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w10', "Vertical wind 7hPa", "Pa/s",  &
     536      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w700', "Vertical wind 700hPa", "Pa/s", &
     537      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     538      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w500', "Vertical wind 500hPa", "Pa/s", &
     539      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     540      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w200', "Vertical wind 200hPa", "Pa/s", &
     541      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     542      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w100', "Vertical wind 100hPa", "Pa/s", &
     543      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     544      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w50', "Vertical wind 50hPa", "Pa/s",  &
     545      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     546      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'w10', "Vertical wind 10hPa", "Pa/s",  &
    547547      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)) /)
    548548
     
    550550      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t850', "Temperature 1hPa", "K",      &
    551551      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    552       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t700', "Temperature 2hPa", "K",      &
    553       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    554       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t500', "Temperature 3hPa", "K",      &
    555       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    556       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t200', "Temperature 4hPa", "K",      &
    557       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    558       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t100', "Temperature 5hPa", "K",      &
    559       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    560       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t50',  "Temperature 6hPa", "K",      &
    561       (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    562       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t10',  "Temperature 7hPa", "K",      &
     552      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t700', "Temperature 700hPa", "K",      &
     553      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     554      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t500', "Temperature 500hPa", "K",      &
     555      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     556      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t200', "Temperature 200hPa", "K",      &
     557      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     558      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t100', "Temperature 100hPa", "K",      &
     559      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     560      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t50',  "Temperature 50hPa", "K",      &
     561      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
     562      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'t10',  "Temperature 10hPa", "K",      &
    563563      (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)) /)
    564564
     
    566566      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q850', "Specific humidity 1hPa", &
    567567      "kg/kg", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    568       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q700', "Specific humidity 2hPa", &
     568      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q700', "Specific humidity 700hPa", &
    569569      "kg/kg", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    570       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q500', "Specific humidity 3hPa", &
     570      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q500', "Specific humidity 500hPa", &
    571571      "kg/kg", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    572       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q200', "Specific humidity 4hPa", &
     572      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q200', "Specific humidity 200hPa", &
    573573      "kg/kg", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    574       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q100', "Specific humidity 5hPa", &
     574      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q100', "Specific humidity 100hPa", &
    575575      "kg/kg", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    576       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q50', "Specific humidity 6hPa",  &
     576      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q50', "Specific humidity 50hPa",  &
    577577      "kg/kg", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    578       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q10', "Specific humidity 7hPa", &
     578      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'q10', "Specific humidity 10hPa", &
    579579      "kg/kg", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)) /)
    580580
     
    582582      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z850', "Geopotential height 1hPa",        &
    583583      "m", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    584       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z700', "Geopotential height 2hPa",        &
     584      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z700', "Geopotential height 700hPa",        &
    585585      "m", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    586       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z500', "Geopotential height 3hPa",        &
     586      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z500', "Geopotential height 500hPa",        &
    587587      "m", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    588       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z200', "Geopotential height 4hPa",        &
     588      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z200', "Geopotential height 200hPa",        &
    589589      "m", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    590       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z100', "Geopotential height 5hPa",        &
     590      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z100', "Geopotential height 100hPa",        &
    591591      "m", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    592       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z50', "Geopotential height 6hPa",         &
     592      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z50', "Geopotential height 50hPa",         &
    593593      "m", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)), &
    594       ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z10', "Geopotential height 7hPa",         &
     594      ctrl_out((/ 1, 7, 7, 10, 10, 10, 11, 11, 11 /),'z10', "Geopotential height 10hPa",         &
    595595      "m", (/ 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)', 'inst(X)' /)) /)
    596596
  • LMDZ5/branches/testing/libf/phylmd/phys_output_mod.F90

    r1910 r1921  
    77  USE aero_mod, only : naero_spc,name_aero
    88  USE phys_output_write_mod, ONLY : phys_output_write
     9  REAL, DIMENSION(nfiles),SAVE :: ecrit_files
    910
    1011! Abderrahmane 12 2007
     
    4445    USE surface_data, ONLY : ok_snow
    4546    USE phys_output_ctrlout_mod
     47    USE mod_grid_phy_lmdz, only: klon_glo
    4648
    4749#ifdef CPP_XIOS
     
    105107    CHARACTER(LEN=6)                      :: type_ocean
    106108    CHARACTER(LEN=3)                      :: ctetaSTD(nbteta)
    107     REAL, DIMENSION(nfiles)               :: ecrit_files
    108109    INTEGER, DIMENSION(iim*jjmp1)         ::  ndex2d
    109110    INTEGER, DIMENSION(iim*jjmp1*klev)    :: ndex3d
     
    207208    ecrit_files(5) = ecrit_LES
    208209    ecrit_files(6) = ecrit_ins
    209     ecrit_files(7) = freq_outNMC(1)/86400.
    210     ecrit_files(8) = freq_outNMC(2)/86400.
    211     ecrit_files(9) = freq_outNMC(3)/86400.
     210    ecrit_files(7) = freq_outNMC(1)
     211    ecrit_files(8) = freq_outNMC(2)
     212    ecrit_files(9) = freq_outNMC(3)
    212213
    213214    !! Lectures des parametres de sorties dans physiq.def
     
    248249    ! ug Réglage du calendrier xios
    249250    !Temps julian => an, mois, jour, heure
    250     CALL ymds2ju(annee_ref, 1, day_ref, 0.0, zjulian)
     251    IF (klon_glo==1) THEN                                       
     252        CALL ymds2ju(annee_ref, 1, day_ref, hour, zjulian)
     253    ELSE
     254        CALL ymds2ju(annee_ref, 1, day_ref, 0.0, zjulian)
     255    END IF
    251256    CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
    252257    CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure)
     
    278283          ! ...)*86400.
    279284          ecrit_files(iff)=ecrit_files(iff)*86400.
     285      ELSE IF (chtimestep(iff).eq.'-1') then
     286          PRINT*,'ecrit_files(',iff,') < 0 so IOIPSL work on different'
     287          PRINT*,'months length'
     288          ecrit_files(iff)=-1.
    280289      else
    281290       CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
     
    304313
    305314          idayref = day_ref
    306 !          CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)       
    307 ! correction pour l heure initiale                               !jyg
    308 !                                                                !jyg
    309           CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian)         !jyg
    310 ! correction pour l heure initiale                               !jyg
    311 !                                                                !jyg
    312 !!!      CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)       !jyg
    313 ! correction pour l heure initiale                               !jyg
    314 !                                                                !jyg
    315 !      CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian)         !jyg
    316 
     315! A noter pour
     316! l heure initiale - dans les fichiers histoire hist* - on met comme
     317! heure de debut soit la vraie heure (pour le 1D) soit 0h (pour le 3D)
     318! afin d avoir une seule sortie mensuelle par mois lorsque l on tourne
     319! par annee (IM).
     320!
     321     IF (klon_glo==1) THEN                                     
     322         CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian)     !jyg
     323     ELSE
     324         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
     325     END IF                                                     
    317326!!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
    318327!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    482491    WRITE(lunout,*)'swaero_diag=',swaero_diag
    483492    WRITE(lunout,*)'Fin phys_output_mod.F90'
     493
    484494  end SUBROUTINE phys_output_open
    485495
  • LMDZ5/branches/testing/libf/phylmd/phys_output_write_mod.F90

    r1910 r1921  
    1818       pplay, lmax_th, aerosol_couple,         &
    1919       ok_ade, ok_aie, ivap, new_aod, ok_sync, &
    20        ptconv, read_climoz, clevSTD, freq_moyNMC, ptconvth, &
     20       ptconv, read_climoz, clevSTD, ptconvth, &
    2121       d_t, qx, d_qx, zmasse, flag_aerosol_strat)
    2222
     
    230230    USE wxios, only: wxios_update_calendar, wxios_closedef
    231231#endif
     232    USE phys_cal_mod, only : mth_len
    232233
    233234    IMPLICIT NONE
     
    269270    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
    270271    REAL, PARAMETER :: missing_val=nf90_fill_real
     272    REAL, PARAMETER :: un_jour=86400.
    271273
    272274    ! On calcul le nouveau tau:
     
    11941196                DO i=1, klon
    11951197                   IF(tnondef(i,k,iff-6).NE.missing_val) THEN
     1198                      IF(freq_outNMC(iff-6).LT.0) THEN
     1199                         freq_moyNMC(iff-6)=(mth_len*un_jour)/freq_calNMC(iff-6)
     1200                      ELSE
     1201                         freq_moyNMC(iff-6)=freq_outNMC(iff-6)/freq_calNMC(iff-6)
     1202                      ENDIF
    11961203                      zx_tmp_fi3d(i,k) = (100.*tnondef(i,k,iff-6))/freq_moyNMC(iff-6)
    11971204                   ELSE
  • LMDZ5/branches/testing/libf/phylmd/physiq.F90

    r1910 r1921  
    493493  REAL un_jour
    494494  PARAMETER(un_jour=86400.)
     495  INTEGER itapm1 !pas de temps de la physique du(es) mois precedents
     496  SAVE itapm1    !mis a jour le dernier pas de temps du mois en cours
     497  !$OMP THREADPRIVATE(itapm1)
    495498  !======================================================================
    496499  !
     
    12541257     !$OMP BARRIER
    12551258
     1259    freq_outNMC(1) = ecrit_files(7)
     1260    freq_outNMC(2) = ecrit_files(8)
     1261    freq_outNMC(3) = ecrit_files(9)
     1262    WRITE(lunout,*)'OK freq_outNMC(1)=',freq_outNMC(1)
     1263    WRITE(lunout,*)'OK freq_outNMC(2)=',freq_outNMC(2)
     1264    WRITE(lunout,*)'OK freq_outNMC(3)=',freq_outNMC(3)
    12561265
    12571266     include "ini_histday_seri.h"
     
    17301739          zxtsol,    zxfluxlat, zt2m,    qsat2m,  &
    17311740          d_t_vdf,   d_q_vdf,   d_u_vdf, d_v_vdf, d_t_diss, &
    1732           coefh,     coefm,     slab_wfbils,                 &
     1741          coefh(1:klon,1:klev,1:nbsrf+1),     coefm(1:klon,1:klev,1:nbsrf+1), &
     1742          slab_wfbils,                 &
    17331743          qsol,      zq2m,      s_pblh,  s_lcl, &
    17341744          s_capCL,   s_oliqCL,  s_cteiCL,s_pblT, &
     
    28092819          paprs, &
    28102820          pplay, &
    2811           coefh(:,:,is_ave), &
     2821          coefh(1:klon,1:klev,is_ave), &
    28122822          pphi, &
    28132823          t_seri, &
     
    33403350       paprs,    pplay,     pmfu,     pmfd, &
    33413351       pen_u,    pde_u,     pen_d,    pde_d, &
    3342        cdragh,   coefh(:,:,is_ave),   fm_therm, entr_therm, &
     3352       cdragh,   coefh(1:klon,1:klev,is_ave),   fm_therm, entr_therm, &
    33433353       u1,       v1,        ftsol,    pctsrf, &
    33443354       zustar,   zu10m,     zv10m, &
     
    33683378          t,pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &
    33693379          fm_therm,entr_therm, &
    3370           cdragh,coefh(:,:,is_ave),u1,v1,ftsol,pctsrf, &
     3380          cdragh,coefh(1:klon,1:klev,is_ave),u1,v1,ftsol,pctsrf, &
    33713381          frac_impa, frac_nucl, &
    33723382          pphis,airephy,dtime,itap, &
     
    34313441  !   SORTIES
    34323442  !=======================================================================
    3433 
     3443  !
     3444  !IM initialisation + calculs divers diag AMIP2
     3445  !
     3446  include "calcul_divers.h"
     3447  !
    34343448  !IM Interpolation sur les niveaux de pression du NMC
    34353449  !   -------------------------------------------------
     
    34483462     ENDDO
    34493463  ENDDO
    3450   !
    3451   !IM initialisation + calculs divers diag AMIP2
    3452   !
    3453   include "calcul_divers.h"
    34543464  !
    34553465  IF (type_trac == 'inca') THEN
     
    36493659       pplay, lmax_th, aerosol_couple,                 &
    36503660       ok_ade, ok_aie, ivap, new_aod, ok_sync,         &
    3651        ptconv, read_climoz, clevSTD, freq_moyNMC,      &
     3661       ptconv, read_climoz, clevSTD,                   &
    36523662       ptconvth, d_t, qx, d_qx, zmasse,                &
    36533663       flag_aerosol_strat)
  • LMDZ5/branches/testing/libf/phylmd/undefSTD.F

    r1910 r1921  
    22! $Id$
    33!
    4       SUBROUTINE undefSTD(itap,freq_calNMC, read_climoz)
     4      SUBROUTINE undefSTD(itap, read_climoz)
    55      USE netcdf
    66      USE dimphy
    77      USE phys_state_var_mod ! Variables sauvegardees de la physique
    88      IMPLICIT none
     9      include "clesphys.h"
    910c
    1011c====================================================================
     
    4243c     PARAMETER(nout=3) !nout=1 : day; =2 : mth; =3 : NMC
    4344      INTEGER i, k, n
    44       REAL freq_calNMC(nout)
     45c     REAL freq_calNMC(nout)
    4546      INTEGER read_climoz
    4647c
Note: See TracChangeset for help on using the changeset viewer.