LMDZ
tracinca_mod.F90
Go to the documentation of this file.
1 !$Id $
2 !
4 !
5 ! This module prepares and calls the INCA main subroutines.
6 !
7  IMPLICIT NONE
8 
9  CHARACTER(len=4),SAVE :: config_inca
10 !$OMP THREADPRIVATE(config_inca)
11  ! config_inca='none' => without INCA
12  ! config_inca='chem' => INCA with chemistry
13  ! config_inca='aero' => INCA with aerosols
14 CONTAINS
15 
16  SUBROUTINE tracinca_init(aerosol,lessivage)
17  ! This subroutine initialize some control varaibles.
18 
19  USE infotrac_phy, ONLY: nbtr
20  USE ioipsl_getin_p_mod, ONLY: getin_p
21  IMPLICIT NONE
22 
23  ! Output variables
24  LOGICAL,DIMENSION(nbtr), INTENT(OUT) :: aerosol
25  LOGICAL,INTENT(OUT) :: lessivage
26 
27 
28  ! Initialization
29  lessivage =.false.
30  aerosol(:) = .false.
31 
32  END SUBROUTINE tracinca_init
33 
34  SUBROUTINE tracinca( &
35  nstep, julien, gmtime, lafin, &
36  pdtphys, t_seri, paprs, pplay, &
37  pmfu, upwd, ftsol, pctsrf, pphis, &
38  pphi, albsol, sh, rh, &
39  cldfra, rneb, diafra, cldliq, &
40  itop_con, ibas_con, pmflxr, pmflxs, &
41  prfl, psfl, aerosol_couple, flxmass_w, &
42  tau_aero, piz_aero, cg_aero, ccm, &
43  rfname, &
44  tr_seri, source)
45 
46 !========================================================
47 ! -- CHIMIE INCA --
48 !========================================================
49 
50  USE dimphy
51  USE infotrac_phy, ONLY: nbtr
52  USE vampir
53  USE indice_sol_mod
54  USE geometry_mod, ONLY: cell_area
56  USE aero_mod, ONLY : naero_grp
57  IMPLICIT NONE
58 
59 !==========================================================================
60 ! -- DESCRIPTION DES ARGUMENTS --
61 !==========================================================================
62 
63 
64 ! EN ENTREE ...
65 !
66 !Configuration grille,temps:
67  INTEGER,INTENT(IN) :: nstep ! Appel physique
68  INTEGER,INTENT(IN) :: julien ! Jour julien
69  REAL,INTENT(IN) :: gmtime
70  REAL,INTENT(IN) :: pdtphys ! Pas d'integration pour la physique (seconde)
71  LOGICAL,INTENT(IN) :: lafin ! le flag de la fin de la physique
72 
73 
74 !Physique:
75 !--------
76  REAL,DIMENSION(klon,klev),INTENT(IN) :: t_seri ! Temperature
77  REAL,DIMENSION(klon,klev),INTENT(IN) :: sh ! humidite specifique
78  REAL,DIMENSION(klon,klev),INTENT(IN) :: rh ! humidite relative
79  REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs ! pression pour chaque inter-couche (en Pa)
80  REAL,DIMENSION(klon,klev),INTENT(IN) :: pplay ! pression pour le mileu de chaque couche (en Pa)
81  REAL,DIMENSION(klon,klev),INTENT(IN) :: pphi ! geopotentiel
82  REAL,DIMENSION(klon),INTENT(IN) :: pphis
83  REAL,DIMENSION(klon,klev),INTENT(IN) :: cldliq ! eau liquide nuageuse
84  REAL,DIMENSION(klon,klev),INTENT(IN) :: cldfra ! fraction nuageuse (tous les nuages)
85  REAL,DIMENSION(klon,klev),INTENT(IN) :: diafra ! fraction nuageuse (convection ou stratus artificiels)
86  REAL,DIMENSION(klon,klev),INTENT(IN) :: rneb ! fraction nuageuse (grande echelle)
87  INTEGER,DIMENSION(klon),INTENT(IN) :: itop_con
88  INTEGER,DIMENSION(klon),INTENT(IN) :: ibas_con
89  REAL,DIMENSION(klon),INTENT(IN) :: albsol ! albedo surface
90 !
91 !Convection:
92 !----------
93  REAL,DIMENSION(klon,klev),INTENT(IN) :: pmfu ! flux de masse dans le panache montant - Tiedtke
94  REAL,DIMENSION(klon,klev),INTENT(IN) :: upwd ! flux de masse dans le panache montant - Emanuel
95 
96 !...Tiedke
97  REAL,DIMENSION(klon,klev+1),INTENT(IN) :: pmflxr, pmflxs ! Flux precipitant de pluie, neige aux interfaces [convection]
98  REAL,DIMENSION(klon,klev+1),INTENT(IN) :: prfl, psfl ! Flux precipitant de pluie, neige aux interfaces [large-scale]
99 
100  LOGICAL,INTENT(IN) :: aerosol_couple
101  REAL,DIMENSION(klon,klev),INTENT(IN) :: flxmass_w
102  REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: tau_aero
103  REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: piz_aero
104  REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: cg_aero
105  CHARACTER(len=4),DIMENSION(naero_grp),INTENT(IN) :: rfname
106  REAL,DIMENSION(klon,klev,2),INTENT(IN) :: ccm
107 
108 ! Arguments necessaires pour les sources et puits de traceur:
109  REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: ftsol ! Temperature du sol (surf)(Kelvin)
110  REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: pctsrf ! Pourcentage de sol f(nature du sol)
111 
112 
113  ! InOutput argument
114  REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT) :: tr_seri ! Concentration Traceur [U/KgA]
115 
116  ! Output arguments
117  REAL,DIMENSION(klon,nbtr), INTENT(OUT) :: source ! a voir lorsque le flux de surface est prescrit
118 
119 !=======================================================================================
120 ! -- VARIABLES LOCALES TRACEURS --
121 !=======================================================================================
122 
123  INTEGER :: k
124  REAL,DIMENSION(klon,klev) :: pdel
125  REAL,DIMENSION(klon,klev) :: zpmfu ! flux de masse dans le panache montant
126  REAL :: calday
127  INTEGER :: ncsec
128 
129  CALL vte(vtphysiq)
130  CALL vtb(vtinca)
131 
132  calday = REAL(julien) + gmtime
133  ncsec = nint(86400.*gmtime)
134 
135  DO k = 1, klev
136  pdel(:,k) = paprs(:,k) - paprs(:,k+1)
137  END DO
138 
139 #ifdef INCA
140  IF (config_inca == 'aero') THEN
141  zpmfu(:,:)=pmfu(:,:)
142  ELSE IF (config_inca == 'aeNP') THEN
143  zpmfu(:,:)=upwd(:,:)
144  ENDIF
145 
146  CALL aerosolmain( &
147  aerosol_couple,tr_seri,pdtphys, &
148  pplay,pdel,prfl,pmflxr,psfl, &
149  pmflxs,zpmfu,itop_con,ibas_con, &
150  pphi,cell_area,nstep,rneb,t_seri, &
151  rh,tau_aero,piz_aero,cg_aero, &
152  rfname,ccm,lafin, config_inca)
153 #endif
154 
155 
156 #ifdef INCA
157  CALL chemmain (tr_seri, & !mmr
158  nstep, & !nstep
159  calday, & !calday
160  julien, & !ncdate
161  ncsec, & !ncsec
162  1, & !lat
163  pdtphys, & !delt
164  paprs(1,1), & !ps
165  pplay, & !pmid
166  pdel, & !pdel
167  cell_area, &
168  pctsrf(1,1),& !oro
169  ftsol, & !tsurf
170  albsol, & !albs
171  pphi, & !zma
172  pphis, & !phis
173  cldfra, & !cldfr
174  rneb, & !cldfr_st
175  diafra, & !cldfr_cv
176  itop_con, & !cldtop
177  ibas_con, & !cldbot
178  cldliq, & !cwat
179  prfl, & !flxrst
180  pmflxr, & !flxrcv
181  psfl, & !flxsst
182  pmflxs, & !flxscv
183  zpmfu, & !flxupd !--now depends on whether AP or NP
184  flxmass_w, & !flxmass_w
185  t_seri, & !tfld
186  sh, & !sh
187  rh, & !rh
188  nbp_lon+1, & !nx
189  nbp_lat, & !ny
190  source )
191 #endif
192 
193  CALL vte(vtinca)
194  CALL vtb(vtphysiq)
195 
196 
197  END SUBROUTINE tracinca
198 
199 
200 END MODULE tracinca_mod
character(len=4), save config_inca
Definition: control_mod.F90:31
integer, save nbtr
Definition: vampir.F90:1
subroutine vtb(number)
Definition: vampir.F90:52
integer, parameter vtinca
Definition: vampir.F90:9
integer, save klev
Definition: dimphy.F90:7
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
subroutine tracinca_init(aerosol, lessivage)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL pplay
Definition: calcul_STDlev.h:26
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le paprs
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL pdtphys
Definition: ini_histrac.h:11
subroutine vte(number)
Definition: vampir.F90:69
subroutine tracinca(nstep, julien, gmtime, lafin, pdtphys, t_seri, paprs, pplay, pmfu, upwd, ftsol, pctsrf, pphis, pphi, albsol, sh, rh, cldfra, rneb, diafra, cldliq, itop_con, ibas_con, pmflxr, pmflxs, prfl, psfl, aerosol_couple, flxmass_w, tau_aero, piz_aero, cg_aero, ccm, rfname, tr_seri, source)
Definition: dimphy.F90:1
integer, parameter naero_grp
Definition: aero_mod.F90:64
real, dimension(:), allocatable, save cell_area
integer, parameter vtphysiq
Definition: vampir.F90:8