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