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

Last change on this file since 5300 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

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