source: LMDZ6/trunk/libf/phylmd/stratocu_if.f90 @ 5834

Last change on this file since 5834 was 5834, checked in by rkazeroni, 2 months ago

For GPU porting of stratocu_if routine:

  • Put routine into module (speeds up source-to-source transformation)
  • Add "horizontal" comment to specify possible names of horizontal variables
  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.2 KB
Line 
1!$gpum horizontal klon
2MODULE stratocu_if_mod
3  PRIVATE
4
5  PUBLIC stratocu_if
6
7  CONTAINS
8
9  SUBROUTINE stratocu_if(klon,klev,pctsrf,paprs, pplay,t &
10,seuil_inversion,weak_inversion,dthmin)
11
12  USE indice_sol_mod
13
14USE yomcst_mod_h
15IMPLICIT NONE
16
17!======================================================================
18! J'introduit un peu de diffusion sauf dans les endroits
19! ou une forte inversion est presente
20! On peut dire qu'il represente la convection peu profonde
21!
22! Arguments:
23! klon-----input-I- nombre de points a traiter
24! paprs----input-R- pression a chaque intercouche (en Pa)
25! pplay----input-R- pression au milieu de chaque couche (en Pa)
26! t--------input-R- temperature (K)
27!
28! weak_inversion-----logical
29!======================================================================
30!
31! Arguments:
32!
33    INTEGER, INTENT(IN)                       :: klon,klev
34    REAL, DIMENSION(klon, klev+1), INTENT(IN) ::  paprs
35    REAL, DIMENSION(klon, klev), INTENT(IN)   ::  pplay
36    REAL, DIMENSION(klon, 4), INTENT(IN)   ::  pctsrf
37    REAL, DIMENSION(klon, klev), INTENT(IN)   :: t
38
39    REAL, DIMENSION(klon), INTENT(OUT)  :: weak_inversion
40!
41! Quelques constantes et options:
42!
43    REAL seuil_inversion ! au-dela l'inversion est consideree trop faible
44!    PARAMETER (seuil=-0.1)
45
46!
47! Variables locales:
48!
49    INTEGER i, k, invb(klon)
50    REAL zl2(klon)
51    REAL dthmin(klon), zdthdp
52
53
54
55!
56! Chercher la zone d'inversion forte
57!
58
59    DO i = 1, klon
60       invb(i) = klev
61       dthmin(i)=0.0
62    ENDDO
63    DO k = 2, klev/2-1
64       DO i = 1, klon
65          zdthdp = (t(i,k)-t(i,k+1))/(pplay(i,k)-pplay(i,k+1)) &
66               - RD * 0.5*(t(i,k)+t(i,k+1))/RCPD/paprs(i,k+1)
67          zdthdp = zdthdp * 100.0
68          IF (pplay(i,k).GT.0.8*paprs(i,1) .AND. &
69               zdthdp.LT.dthmin(i) ) THEN
70             dthmin(i) = zdthdp
71             invb(i) = k
72          ENDIF
73       ENDDO
74    ENDDO
75
76
77!
78! Introduire une diffusion:
79!
80    DO i = 1, klon
81       IF ( (pctsrf(i,is_oce) < 0.5) .OR. &
82          (invb(i) == klev) .OR. (dthmin(i) > seuil_inversion) ) THEN
83          weak_inversion(i)=1.
84       ELSE
85          weak_inversion(i)=0.
86       ENDIF
87    ENDDO
88
89  END SUBROUTINE stratocu_if
90
91END MODULE stratocu_if_mod
Note: See TracBrowser for help on using the repository browser.