source: LMDZ6/trunk/libf/dyn3dmem/exner_milieu_loc_m.f90 @ 5278

Last change on this file since 5278 was 5272, checked in by abarral, 2 days ago

Turn paramet.h into a module

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.6 KB
RevLine 
[2021]1module exner_milieu_loc_m
[1632]2
[2021]3  IMPLICIT NONE
[1632]4
[2021]5contains
[1632]6
[2021]7  SUBROUTINE  exner_milieu_loc ( ngrid, ps, p, pks, pk, pkf )
8    !
9    !     Auteurs :  F. Forget , Y. Wanherdrick
10    ! P.Le Van  , Fr. Hourdin  .
11    !    ..........
12    !
13    !    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
14    !    ....  pks,pk,pkf   sont des argum.de sortie au sous-prog ...
15    !
16    !   ************************************************************************
17    !    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
18    !    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
19    !    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
20    !   ************************************************************************
21    !  .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
22    !    la pression et la fonction d'Exner  au  sol  .
23    !
24    !     WARNING : CECI est une version speciale de exner_hyb originale
25    !               Utilise dans la version martienne pour pouvoir
26    !               tourner avec des coordonnees verticales complexe
27    !              => Il ne verifie PAS la condition la proportionalite en
28    !              energie totale/ interne / potentielle (F.Forget 2001)
29    !    ( voir note de Fr.Hourdin )  ,
30    !
31    USE parallel_lmdz
32    USE mod_filtreg_p
[2597]33    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
[2600]34    USE comvert_mod, ONLY: preff
35   
[5271]36    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5272]37USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
38          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
[5271]39IMPLICIT NONE
[2021]40    !
[5271]41
[5272]42
[2021]43    include "comgeom.h"
[1632]44
[2021]45    INTEGER  ngrid
46    REAL p(ijb_u:ije_u,llmp1),pk(ijb_u:ije_u,llm)
47    REAL, optional:: pkf(ijb_u:ije_u,llm)
48    REAL ps(ijb_u:ije_u),pks(ijb_u:ije_u)
[1632]49
[2021]50    !    .... variables locales   ...
51
52    INTEGER l, ij
53    REAL dum1
54
55    INTEGER ije,ijb,jje,jjb
56    logical,save :: firstcall=.true.
57    !$OMP THREADPRIVATE(firstcall)
58    character(len=*),parameter :: modname="exner_milieu_loc"
59
60    ! Sanity check
61    if (firstcall) then
62       ! sanity checks for Shallow Water case (1 vertical layer)
63       if (llm.eq.1) then
[1632]64          if (kappa.ne.1) then
[2021]65             call abort_gcm(modname, &
66                  "kappa!=1 , but running in Shallow Water mode!!",42)
[1632]67          endif
68          if (cpp.ne.r) then
[2021]69             call abort_gcm(modname, &
70                  "cpp!=r , but running in Shallow Water mode!!",42)
[1632]71          endif
[2021]72       endif ! of if (llm.eq.1)
[1632]73
[2021]74       firstcall=.false.
75    endif ! of if (firstcall)
[1632]76
[2021]77    !$OMP BARRIER
[1632]78
[2021]79    ! Specific behaviour for Shallow Water (1 vertical layer) case:
80    if (llm.eq.1) then
81
82       ! Compute pks(:),pk(:),pkf(:)
83       ijb=ij_begin
84       ije=ij_end
85       !$OMP DO SCHEDULE(STATIC)
86       DO ij=ijb, ije
87          pks(ij) = (cpp/preff) * ps(ij)
[1632]88          pk(ij,1) = .5*pks(ij)
[2021]89          if (present(pkf)) pkf(ij,1)=pk(ij,1)
90       ENDDO
91       !$OMP ENDDO
[1632]92
[2021]93       !$OMP BARRIER
94       if (present(pkf)) then
95          jjb=jj_begin
96          jje=jj_end
97          CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
98               2, 1, .TRUE., 1 )
99       end if
[1632]100
[2021]101       ! our work is done, exit routine
102       return
103    endif ! of if (llm.eq.1)
[1632]104
[2021]105    ! General case:
[1632]106
[2021]107    !     -------------
108    !     Calcul de pks
109    !     -------------
[1632]110
[2021]111    ijb=ij_begin
112    ije=ij_end
[1632]113
[2021]114    !$OMP DO SCHEDULE(STATIC)
115    DO   ij  = ijb, ije
116       pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
117    ENDDO
118    !$OMP ENDDO
119    ! Synchro OPENMP ici
[1632]120
[2021]121    !$OMP BARRIER
122    !
123    !
124    !    .... Calcul de pk  pour la couche l
125    !    --------------------------------------------
126    !
127    dum1 = cpp * (2*preff)**(-kappa)
128    DO l = 1, llm-1
129       !$OMP DO SCHEDULE(STATIC)
130       DO   ij   = ijb, ije
131          pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
132       ENDDO
133       !$OMP ENDDO NOWAIT
134    ENDDO
[1632]135
[2021]136    !    .... Calcul de pk  pour la couche l = llm ..
137    !    (on met la meme distance (en log pression)  entre Pk(llm)
138    !    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
[1632]139
[2021]140    !$OMP DO SCHEDULE(STATIC)
141    DO   ij   = ijb, ije
142       pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
143    ENDDO
144    !$OMP ENDDO NOWAIT       
[1632]145
[2021]146    if (present(pkf)) then
147       !    calcul de pkf
[1632]148
[2021]149       DO l = 1, llm
150          !$OMP DO SCHEDULE(STATIC)
151          DO   ij   = ijb, ije
152             pkf(ij,l)=pk(ij,l)
153          ENDDO
154          !$OMP ENDDO NOWAIT
155       ENDDO
156
157       !$OMP BARRIER
158
159       jjb=jj_begin
160       jje=jj_end
161       CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
162            2, 1, .TRUE., 1 )
163    end if
164
165  END SUBROUTINE exner_milieu_loc
166
167end module exner_milieu_loc_m
Note: See TracBrowser for help on using the repository browser.