source: LMDZ6/branches/Amaury_dev/libf/dyn3d/tetaleveli1j.F90 @ 5103

Last change on this file since 5103 was 5103, checked in by abarral, 8 weeks ago

Handle CPP_INLANDSIS in lmdz_cppkeys_wrapper.F90
Remove obsolete key wrgrads_thermcell, _ADV_HALO, _ADV_HALLO, isminmax
Remove redundant uses of CPPKEY_INCA (thanks acozic)
Remove obsolete misc/write_field.F90
Remove unused ioipsl_* wrappers
Remove calls to WriteField_u with wrong signature
Convert .F -> .[fF]90
(lint) uppercase fortran operators
[note: 1d and iso still broken - working on it]

  • 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: 3.9 KB
Line 
1!================================================================
2!================================================================
3SUBROUTINE tetaleveli1j(ilon, ilev, lnew, pgcm, pres, Qgcm, Qpres)
4  !================================================================
5  !================================================================
6
7  ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
8  IMPLICIT none
9
10  include "dimensions.h"
11
12  !================================================================
13  !
14  ! Interpoler des champs 3-D u, v et g du modele a un niveau de
15  ! pression donnee (pres)
16  !
17  ! INPUT:  ilon ----- nombre de points
18  !     ilev ----- nombre de couches
19  !     lnew ----- true si on doit reinitialiser les poids
20  !     pgcm ----- pressions modeles
21  !     pres ----- pression vers laquelle on interpolle
22  !     Qgcm ----- champ GCM
23  !     Qpres ---- champ interpolle au niveau pres
24  !
25  !================================================================
26  !
27  !   arguments :
28  !   -----------
29
30  INTEGER :: ilon, ilev
31  logical :: lnew
32
33  REAL :: pgcm(ilon, ilev)
34  REAL :: Qgcm(ilon, ilev)
35  real :: pres
36  REAL :: Qpres(ilon)
37
38  !   local :
39  !   -------
40
41  !IM 211004
42  ! INTEGER lt(klon), lb(klon)
43  ! REAL ptop, pbot, aist(klon), aisb(klon)
44  !
45  include "paramet.h"
46  !
47  INTEGER :: lt(ip1jm), lb(ip1jm)
48  REAL :: ptop, pbot, aist(ip1jm), aisb(ip1jm)
49  !MI 211004
50  save lt, lb, ptop, pbot, aist, aisb
51
52  INTEGER :: i, k
53  !
54  ! PRINT*,'tetalevel pres=',pres
55  !=====================================================================
56  if (lnew) then
57    !   on réinitialise les réindicages et les poids
58    !=====================================================================
59
60
61    ! Chercher les 2 couches les plus proches du niveau a obtenir
62    !
63    ! Eventuellement, faire l'extrapolation a partir des deux couches
64    ! les plus basses ou les deux couches les plus hautes:
65    DO i = 1, ilon
66      !IM      IF ( ABS(pres-pgcm(i,ilev) ) .LT.
67      IF (ABS(pres - pgcm(i, ilev)) > &
68              ABS(pres - pgcm(i, 1))) THEN
69        lt(i) = ilev     ! 2
70        lb(i) = ilev - 1   ! 1
71      ELSE
72        lt(i) = 2
73        lb(i) = 1
74      ENDIF
75      !IM   PRINT*,'i, ABS(pres-pgcm),ABS(pres-pgcm)',
76      !IM  .i, ABS(pres-pgcm(i,ilev)),ABS(pres-pgcm(i,1))
77    END DO
78    DO k = 1, ilev - 1
79      DO i = 1, ilon
80        pbot = pgcm(i, k)
81        ptop = pgcm(i, k + 1)
82        !IM         IF (ptop.LE.pres .AND. pbot.GE.pres) THEN
83        IF (ptop>=pres .AND. pbot<=pres) THEN
84          lt(i) = k + 1
85          lb(i) = k
86        ENDIF
87      END DO
88    END DO
89    !
90    ! Interpolation lineaire:
91    !
92    DO i = 1, ilon
93      ! interpolation en logarithme de pression:
94      !
95      ! ...   Modif . P. Le Van    ( 20/01/98) ....
96      !   Modif Frédéric Hourdin (3/01/02)
97
98      IF(pgcm(i, lb(i))==0.OR. &
99              pgcm(i, lt(i))==0.) THEN
100        !
101        PRINT*, 'i,lb,lt,2pgcm,pres', i, lb(i), &
102                lt(i), pgcm(i, lb(i)), pgcm(i, lt(i)), pres
103        !
104      ENDIF
105      !
106      aist(i) = LOG(pgcm(i, lb(i)) / pres) &
107              / LOG(pgcm(i, lb(i)) / pgcm(i, lt(i)))
108      aisb(i) = LOG(pres / pgcm(i, lt(i))) &
109              / LOG(pgcm(i, lb(i)) / pgcm(i, lt(i)))
110    enddo
111
112  endif ! lnew
113
114  !======================================================================
115  !    inteprollation
116  !======================================================================
117
118  do i = 1, ilon
119    Qpres(i) = Qgcm(i, lb(i)) * aisb(i) + Qgcm(i, lt(i)) * aist(i)
120    !IM      PRINT*,'i,Qgcm,Qpres',i,Qgcm(i,lb(i)),aisb(i),
121    !IM  $   Qgcm(i,lt(i)),aist(i),Qpres(i)
122  enddo
123  !
124  ! Je mets les vents a zero quand je rencontre une montagne
125  do i = 1, ilon
126    !IM      if (pgcm(i,1).LT.pres) THEN
127    if (pgcm(i, 1)>pres) THEN
128      ! Qpres(i)=1e33
129      Qpres(i) = 1e+20
130      !IM         PRINT*,'i,pgcm(i,1),pres =',i,pgcm(i,1),pres
131    endif
132  enddo
133
134  !
135  RETURN
136END SUBROUTINE tetaleveli1j
Note: See TracBrowser for help on using the repository browser.