Ignore:
Timestamp:
Apr 14, 2010, 11:41:19 AM (14 years ago)
Author:
musat
Message:

Add 3 output files for standard pressure levels AR5 exercice and flags
to manage their computation and output frequencies
histhfNMC.nc with 3 standard pressure levels
histdayNMC.nc with 8 (or may have 17) standard pressure levels
histmthNMC.nc with 17 standard pressure levels
Add 3 flags in the physiq.def file: freq_calNMC(3), freq_outNMC(3) and lev_histdayNMC
freq_calNMC(3) : computation frequency of variables on standard pressure levels

and by default has fallowing values (in fact physics' time step dtime)

freq_calNMC(1)=900.
freq_calNMC(2)=900.
freq_calNMC(3)=900.
freq_outNMC(3) : output frequency of variables on standard pressure levels

with following default values

freq_out(1) = 2592000. (30 days)
freq_out(2) = 86400. (1 day)
freq_out(3) = 21600. (6 hours)
lev_histdayNMC is 8 by default but may be switched to 17 (if we need more levels for a particular run)
IM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/phylmd/ini_undefSTD.F

    r776 r1352  
    33!
    44
    5       SUBROUTINE ini_undefSTD(nlevSTD,itap,
    6      $           dtime,ecrit_day,ecrit_mth,
    7      $           tnondef,tsumSTD)
     5      SUBROUTINE ini_undefSTD(itap,
     6     $           freq_outNMC)
    87      USE dimphy
     8      USE phys_state_var_mod ! Variables sauvegardees de la physique
    99      IMPLICIT none
    1010c
     
    2727c nout=3 !var. mensuelle "NMC" moyennee toutes les 6heures
    2828c
    29 c
    30 c NB: mettre "inst(X)" dans le write_histXXX.h !
     29c NB: mettre "inst(X)" dans le write_hist*NMC.h !
    3130c====================================================================
    3231c
     
    3635cym #include "dimphy.h"
    3736c variables Input/Output
    38       INTEGER nlevSTD, klevSTD, itap
    39       PARAMETER(klevSTD=17)
    40       REAL dtime
    41       REAL ecrit_day,ecrit_mth
     37c     INTEGER nlevSTD, klevSTD, itap
     38      INTEGER itap
     39c     PARAMETER(klevSTD=17)
     40c     REAL dtime
    4241c
    4342c variables locales
    44       INTEGER i, k, nout
    45       PARAMETER(nout=3) !nout=1 day/nout=2 mth/nout=3 NMC
     43c     INTEGER i, k, nout, n
     44      INTEGER i, k, n
     45c     PARAMETER(nout=3) !nout=1 day/nout=2 mth/nout=3 NMC
     46      REAL freq_outNMC(nout)
    4647c
    4748c variables Output
    48       REAL tnondef(klon,klevSTD,nout)
    49       REAL tsumSTD(klon,klevSTD,nout)
     49c     REAL tnondef(klon,klevSTD,nout)
     50c     REAL tsumSTD(klon,klevSTD,nout)
    5051c
    51 c initialisation variables journalieres en debut de journee
     52      DO n=1, nout
    5253c
    53       IF(MOD(itap,NINT(ecrit_day/dtime)).EQ.1.) THEN
    54        DO k=1, nlevSTD
    55         DO i=1, klon
    56          tnondef(i,k,1)=0.
    57          tsumSTD(i,k,1)=0.
    58         ENDDO !i
    59        ENDDO !k
    60       ENDIF
     54c initialisation variables en debut de la journee ou du mois
    6155c
    62 c initialisation variables mensuelles (calculees a chaque pas de temps)
    63 c en debut de mois : nout=2
     56       IF(MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.1.) THEN
    6457c
    65       IF(MOD(itap,NINT(ecrit_mth/dtime)).EQ.1.) THEN
     58c       print*,'n freq_ini=',n,itap,freq_outNMC(n)/dtime
    6659c
    67        DO k=1, nlevSTD
    68         DO i=1, klon
    69          tnondef(i,k,2)=0.
    70          tsumSTD(i,k,2)=0.
    71         ENDDO !i
    72        ENDDO !k
     60        DO k=1, nlevSTD
     61         DO i=1, klon
     62          tnondef(i,k,n)=0.
     63          tsumSTD(i,k,n)=0.
     64          usumSTD(i,k,n)=0.
     65          vsumSTD(i,k,n)=0.
     66          wsumSTD(i,k,n)=0.
     67          phisumSTD(i,k,n)=0.
     68          qsumSTD(i,k,n)=0.
     69          rhsumSTD(i,k,n)=0.
     70          uvsumSTD(i,k,n)=0.
     71          vqsumSTD(i,k,n)=0.
     72          vTsumSTD(i,k,n)=0.
     73          wqsumSTD(i,k,n)=0.
     74          vphisumSTD(i,k,n)=0.
     75          wTsumSTD(i,k,n)=0.
     76          u2sumSTD(i,k,n)=0.
     77          v2sumSTD(i,k,n)=0.
     78          T2sumSTD(i,k,n)=0.
     79         ENDDO !i
     80        ENDDO !k
    7381c
    74 c initialisation variables mensuelles - runs type Amip - (calculees toutes les 6h)
    75 c en debut de mois : nout = 3
     82c          if(n.EQ.1.AND.i.EQ.4513.AND.k.EQ.17) THEN
     83           if(n.EQ.1.AND.i.EQ.1128.AND.k.EQ.17) THEN
     84            print*,'itap rlon rlat tlevSTD=',itap,rlon(i),rlat(i),
     85     $tlevSTD(i,k)
     86           endif
    7687c
    77        DO k=1, nlevSTD
    78         DO i=1, klon
    79          tnondef(i,k,3)=0.
    80          tsumSTD(i,k,3)=0.
    81         ENDDO !i
    82        ENDDO !k
     88       ENDIF !MOD(itap,NINT(freq_outNMC(n)/dtime)).EQ.1.
    8389c
    84       ENDIF
     90      ENDDO !n
    8591c
    8692      RETURN
Note: See TracChangeset for help on using the changeset viewer.