source: LMDZ6/trunk/libf/dyn3d/caladvtrac.f90 @ 5273

Last change on this file since 5273 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.3 KB
Line 
1!
2! $Id: caladvtrac.f90 5272 2024-10-24 15:53:15Z abarral $
3!
4!
5!
6      SUBROUTINE caladvtrac(q,pbaru,pbarv , &
7              p ,masse, dq ,  teta, &
8              flxw, pk)
9  !
10  USE infotrac, ONLY : nqtot
11  USE control_mod, ONLY : iapp_tracvl,planet_type
12  USE comconst_mod, ONLY: dtvr
13
14  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
15USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
16          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
17IMPLICIT NONE
18  !
19  ! Auteurs:   F.Hourdin , P.Le Van, F.Forget, F.Codron
20  !
21  ! F.Codron (10/99) : ajout humidite specifique pour eau vapeur
22  !=======================================================================
23  !
24  !   Shema de  Van Leer
25  !
26  !=======================================================================
27
28
29
30
31
32  !   Arguments:
33  !   ----------
34  REAL :: pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm),masse(ip1jmp1,llm)
35  REAL :: p( ip1jmp1,llmp1),q( ip1jmp1,llm,nqtot)
36  real :: dq(ip1jmp1,llm,nqtot)
37  REAL :: teta( ip1jmp1,llm),pk( ip1jmp1,llm)
38  REAL               :: flxw(ip1jmp1,llm)
39
40  !  ..................................................................
41  !
42  !  .. dq n'est utilise et dimensionne que pour l'eau  vapeur et liqu.
43  !
44  !  ..................................................................
45  !
46  !   Local:
47  !   ------
48
49  EXTERNAL  advtrac,minmaxq, qminimum
50  INTEGER :: ij,l, iq, iapptrac
51  REAL :: finmasse(ip1jmp1,llm), dtvrtrac
52
53  !c
54  !
55  ! Earth-specific stuff for the first 2 tracers (water)
56  if (planet_type.eq."earth") then
57  ! initialisation
58  ! CRisi: il faut gérer tous les traceurs si on veut pouvoir faire des
59  ! isotopes
60     ! dq(:,:,1:2)=q(:,:,1:2)
61    dq(:,:,1:nqtot)=q(:,:,1:nqtot)
62
63  !  test des valeurs minmax
64  !c        CALL minmaxq(q(1,1,1),1.e33,-1.e33,'Eau vapeur (a) ')
65  !c        CALL minmaxq(q(1,1,2),1.e33,-1.e33,'Eau liquide(a) ')
66  endif ! of if (planet_type.eq."earth")
67  !   advection
68
69    CALL advtrac( pbaru,pbarv, &
70          p,  masse,q,iapptrac, teta, &
71          flxw, pk)
72
73  !
74
75  IF( iapptrac.EQ.iapp_tracvl ) THEN
76    if (planet_type.eq."earth") then
77  ! Earth-specific treatment for the first 2 tracers (water)
78  !
79  !c          CALL minmaxq(q(1,1,1),1.e33,-1.e33,'Eau vapeur     ')
80  !c          CALL minmaxq(q(1,1,2),1.e33,-1.e33,'Eau liquide    ')
81
82  !c     ....  Calcul  de deltap  qu'on stocke dans finmasse   ...
83  !
84      DO l = 1, llm
85       DO ij = 1, ip1jmp1
86         finmasse(ij,l) =  p(ij,l) - p(ij,l+1)
87       ENDDO
88      ENDDO
89
90      ! !write(*,*) 'caladvtrac 87'
91      CALL qminimum( q, nqtot, finmasse )
92      ! !write(*,*) 'caladvtrac 89'
93
94      CALL SCOPY   ( ip1jmp1*llm, masse, 1, finmasse,       1 )
95      CALL filtreg ( finmasse ,  jjp1,  llm, -2, 2, .TRUE., 1 )
96  !
97  !   *****  Calcul de dq pour l'eau , pour le passer a la physique ******
98  !   ********************************************************************
99  !
100      dtvrtrac = iapp_tracvl * dtvr
101  !
102       DO iq = 1 , nqtot
103        DO l = 1 , llm
104         DO ij = 1,ip1jmp1
105         dq(ij,l,iq) = ( q(ij,l,iq) - dq(ij,l,iq) ) * finmasse(ij,l) &
106               /  dtvrtrac
107         ENDDO
108        ENDDO
109       ENDDO
110  !
111    endif ! of if (planet_type.eq."earth")
112  ELSE
113    if (planet_type.eq."earth") then
114  ! Earth-specific treatment for the first 2 tracers (water)
115      dq(:,:,1:nqtot)=0.
116    endif ! of if (planet_type.eq."earth")
117  ENDIF ! of IF( iapptrac.EQ.iapp_tracvl )
118
119END SUBROUTINE caladvtrac
120
121
Note: See TracBrowser for help on using the repository browser.