source: LMDZ4/trunk/libf/dyn3d/exner_hyb.F @ 1418

Last change on this file since 1418 was 1403, checked in by Laurent Fairhead, 14 years ago

Merged LMDZ4V5.0-dev branch changes r1292:r1399 to trunk.

Validation:
Validation consisted in compiling the HEAD revision of the trunk,
LMDZ4V5.0-dev branch and the merged sources and running different
configurations on local and SX8 machines comparing results.

Local machine: bench configuration, 32x24x11, gfortran

  • IPSLCM5A configuration (comparison between trunk and merged sources):
    • numerical convergence on dynamical fields over 3 days
    • start files are equivalent (except for RN and PB fields)
    • daily history files equivalent
  • MH07 configuration, new physics package (comparison between LMDZ4V5.0-dev branch and merged sources):
    • numerical convergence on dynamical fields over 3 days
    • start files are equivalent (except for RN and PB fields)
    • daily history files equivalent

SX8 machine (brodie), 96x95x39 on 4 processors:

  • IPSLCM5A configuration:
    • start files are equivalent (except for RN and PB fields)
    • monthly history files equivalent
  • MH07 configuration:
    • start files are equivalent (except for RN and PB fields)
    • monthly history files equivalent

Changes to the makegcm and create_make_gcm scripts to take into account
main programs in F90 files


Fusion de la branche LMDZ4V5.0-dev (r1292:r1399) au tronc principal

Validation:
La validation a consisté à compiler la HEAD de le trunk et de la banche
LMDZ4V5.0-dev et les sources fusionnées et de faire tourner le modéle selon
différentes configurations en local et sur SX8 et de comparer les résultats

En local: 32x24x11, config bench/gfortran

  • pour une config IPSLCM5A (comparaison tronc/fusion):
    • convergence numérique sur les champs dynamiques après 3 jours
    • restart et restartphy égaux (à part sur RN et Pb)
    • fichiers histoire égaux
  • pour une config nlle physique (MH07) (comparaison LMDZ4v5.0-dev/fusion):
    • convergence numérique sur les champs dynamiques après 3 jours
    • restart et restartphy égaux
    • fichiers histoire équivalents

Sur brodie, 96x95x39 sur 4 proc:

  • pour une config IPSLCM5A:
    • restart et restartphy égaux (à part sur RN et PB)
    • pas de différence dans les fichiers histmth.nc
  • pour une config MH07
    • restart et restartphy égaux (à part sur RN et PB)
    • pas de différence dans les fichiers histmth.nc

Changement sur makegcm et create_make-gcm pour pouvoir prendre en compte des
programmes principaux en *F90

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.1 KB
Line 
1!
2! $Id $
3!
4      SUBROUTINE  exner_hyb ( ngrid, ps, p,alpha,beta, pks, pk, pkf )
5c
6c     Auteurs :  P.Le Van  , Fr. Hourdin  .
7c    ..........
8c
9c    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
10c    .... alpha,beta, pks,pk,pkf   sont des argum.de sortie au sous-prog ...
11c
12c   ************************************************************************
13c    Calcule la fonction d'Exner pk = Cp * p ** kappa , aux milieux des
14c    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
15c    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
16c   ************************************************************************
17c  .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
18c    la pression et la fonction d'Exner  au  sol  .
19c
20c                                 -------- z                                   
21c    A partir des relations  ( 1 ) p*dz(pk) = kappa *pk*dz(p)      et
22c                            ( 2 ) pk(l) = alpha(l)+ beta(l)*pk(l-1)
23c    ( voir note de Fr.Hourdin )  ,
24c
25c    on determine successivement , du haut vers le bas des couches, les
26c    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
27c    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches, 
28c     pk(ij,l)  donne  par la relation (2),  pour l = 2 a l = llm .
29c
30c
31      IMPLICIT NONE
32c
33#include "dimensions.h"
34#include "paramet.h"
35#include "comconst.h"
36#include "comgeom.h"
37#include "comvert.h"
38#include "serre.h"
39
40      INTEGER  ngrid
41      REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
42      REAL ps(ngrid),pks(ngrid), alpha(ngrid,llm),beta(ngrid,llm)
43
44c    .... variables locales   ...
45
46      INTEGER l, ij
47      REAL unpl2k,dellta
48
49      REAL ppn(iim),pps(iim)
50      REAL xpn, xps
51      REAL SSUM
52c
53
54      if (llm.eq.1) then
55        ! Specific behaviour for Shallow Water (1 vertical layer) case
56     
57        ! Sanity checks
58        if (kappa.ne.1) then
59          call abort_gcm("exner_hyb",
60     &    "kappa!=1 , but running in Shallow Water mode!!",42)
61        endif
62        if (cpp.ne.r) then
63        call abort_gcm("exner_hyb",
64     &    "cpp!=r , but running in Shallow Water mode!!",42)
65        endif
66       
67        ! Compute pks(:),pk(:),pkf(:)
68       
69        DO   ij  = 1, ngrid
70          pks(ij) = (cpp/preff) * ps(ij)
71          pk(ij,1) = .5*pks(ij)
72        ENDDO
73       
74        CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
75        CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
76       
77        ! our work is done, exit routine
78        return
79      endif ! of if (llm.eq.1)
80
81     
82      unpl2k    = 1.+ 2.* kappa
83c
84      DO   ij  = 1, ngrid
85        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
86      ENDDO
87
88      DO  ij   = 1, iim
89        ppn(ij) = aire(   ij   ) * pks(  ij     )
90        pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
91      ENDDO
92      xpn      = SSUM(iim,ppn,1) /apoln
93      xps      = SSUM(iim,pps,1) /apols
94
95      DO ij   = 1, iip1
96        pks(   ij     )  =  xpn
97        pks( ij+ip1jm )  =  xps
98      ENDDO
99c
100c
101c    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
102c
103      DO     ij      = 1, ngrid
104       alpha(ij,llm) = 0.
105       beta (ij,llm) = 1./ unpl2k
106      ENDDO
107c
108c     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
109c
110      DO l = llm -1 , 2 , -1
111c
112        DO ij = 1, ngrid
113        dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
114        alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
115        beta (ij,l)  =   p(ij,l  ) / dellta   
116        ENDDO
117c
118      ENDDO
119c
120c  ***********************************************************************
121c     .....  Calcul de pk pour la couche 1 , pres du sol  ....
122c
123      DO   ij   = 1, ngrid
124       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  /
125     *    (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
126      ENDDO
127c
128c    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
129c
130      DO l = 2, llm
131        DO   ij   = 1, ngrid
132         pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
133        ENDDO
134      ENDDO
135c
136c
137      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
138      CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
139     
140
141      RETURN
142      END
Note: See TracBrowser for help on using the repository browser.