Changeset 2099 for trunk/LMDZ.TITAN/libf/phytitan
- Timestamp:
- Feb 12, 2019, 3:07:22 PM (6 years ago)
- Location:
- trunk/LMDZ.TITAN/libf/phytitan
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.TITAN/libf/phytitan/calchim.F90
r2097 r2099 35 35 ! even if in physiq we keep altitudes coherent with dynamics ! 36 36 ! 37 ! + STILL TO DO : Replug the interaction with haze (cf titan.old) -> to see with JB. 37 ! + STILL TO DO : + Replug the interaction with haze (cf titan.old) -> to see with JB. 38 ! + Use iso_c_binding for the fortran-C exchanges. 38 39 !--------------------------------------------------------------------------------------------------------- 39 40 … … 131 132 !$OMP THREADPRIVATE(kedd) 132 133 133 REAL*8, DIMENSION(: ), ALLOCATABLE, SAVE :: mass ! Molar mass of the compunds (g.mol-1)134 REAL*8, DIMENSION(: ,:), ALLOCATABLE, SAVE :: md134 REAL*8, DIMENSION(:,:), ALLOCATABLE, SAVE :: md ! Mean molecular diffusion coefficients (cm^2.s-1) 135 REAL*8, DIMENSION(:), ALLOCATABLE, SAVE :: mass ! Molar mass of the compounds (g.mol-1) 135 136 !$OMP THREADPRIVATE(mass,md) 136 137 … … 185 186 ALLOCATE(perte(2,200,nkim)) 186 187 188 ! 0. Deal with characters for C-interoperability 189 ! ---------------------------------------------- 190 ! NB ( JVO 19 ) : Using iso_c_binding would do things in an even cleaner way ! 191 DO ic=1,nkim 192 nomqy_c(ic) = trim(cnames(ic))//char(0) ! Add the C null terminator 193 ENDDO 194 nomqy_c(nkim+1)="HV"//char(0) ! For photodissociations 195 187 196 ! 1. Read Vervack profile "tcp.ver", once for all 188 197 ! ----------------------------------------------- … … 291 300 292 301 ! Kedd from (E7) in Vuitton 2019 293 DO l=klev-4,nlaykim_tot 294 kedd(l) = 300.0 * ( 1.0E2 / press_c(l) )**1.5 * 3.0E7 / & 302 if (ngrid .eq. 1) then ! if 1D no dynamic mixing, we set the kedd in all column 303 DO l=1,nlaykim_tot 304 kedd(l) = 300.0 * ( 1.0E2 / press_c(l) )**1.5 * 3.0E7 / & 305 ( 300.0 * ( 1.0E2 / press_c(l) )**1.5 + 3.0E7 ) 306 ENDDO 307 else 308 DO l=klev-4,nlaykim_tot 309 ! JVO 18 : We keep the nominal profile in the GCM 5 upper layers 310 ! to have a correct vertical mixing in the sponge layer 311 kedd(l) = 300.0 * ( 1.0E2 / press_c(l) )**1.5 * 3.0E7 / & 295 312 ( 300.0 * ( 1.0E2 / press_c(l) )**1.5 + 3.0E7 ) 296 ENDDO297 298 ! JVO 18 : We keep the nominal profile in the GCM 5 upper layers299 ! to have a correct vertical mixing in the sponge layer300 301 ! Then adjust 10 layers profile fading to default value depending on kedd(ptop)302 DO l=klev-15,klev-5303 temp1 = ( log10(press_c(l)/press_c(klev-15)) ) / ( log10(press_c(klev-4)/press_c(klev-15)))304 kedd(l) = 10.**( 3.0 + log10(kedd(klev-4)/1.e3) * temp1 )305 ENDDO306 313 ENDDO 314 endif 315 316 if (ngrid .gt. 1) then ! not in 1D, no dynamic mixing 317 ! Then adjust 10 layers profile fading to default value depending on kedd(ptop) 318 DO l=klev-15,klev-5 319 temp1 = ( log10(press_c(l)/press_c(klev-15)) ) / ( log10(press_c(klev-4)/press_c(klev-15)) ) 320 kedd(l) = 10.**( 3.0 + log10(kedd(klev-4)/1.e3) * temp1 ) 321 ENDDO 322 endif 323 307 324 firstcall = .FALSE. 308 325 ENDIF ! firstcall … … 328 345 ! ------------------------------------------------------------------------------------------------------- 329 346 330 IF ( ( moyzon_ch .AND. ( ig.EQ.1 .OR. (ABS(latitude(ig)-latitude(igm1)).GT.0.1*pi/180 )) ) .OR. (.NOT. moyzon_ch) ) THEN347 IF ( ( moyzon_ch .AND. ( ig.EQ.1 .OR. (ABS(latitude(ig)-latitude(igm1)).GT.0.1*pi/180.0)) ) .OR. (.NOT. moyzon_ch) ) THEN 331 348 332 349 ! 1. Compute altitude for the grid point with hydrostat. equilib. -
trunk/LMDZ.TITAN/libf/phytitan/comchem_h.F90
r2003 r2099 44 44 "NCCN ", "C4N2 "/) 45 45 !! Hard-coded chemical species for Titan chemistry + "HV" specie for the photochem module. 46 CHARACTER(len=10), DIMENSION(nkim+1), PARAMETER :: nomqy_c = & 47 (/"H ", "H2 ", "CH ", "CH2s ", "CH2 ", "CH3 ", & 48 "CH4 ", "C2 ", "C2H ", "C2H2 ", "C2H3 ", "C2H4 ", & 49 "C2H5 ", "C2H6 ", "C3H3 ", "C3H5 ", "C3H6 ", "C3H7 ", & 50 "C4H ", "C4H3 ", "C4H4 ", "C4H2s ", "CH2CCH2 ", "CH3CCH ", & 51 "C3H8 ", "C4H2 ", "C4H6 ", "C4H10 ", "AC6H6 ", "C3H2 ", & 52 "C4H5 ", "AC6H5 ", "N2 ", "N4S ", "CN ", "HCN ", & 53 "H2CN ", "CHCN ", "CH2CN ", "CH3CN ", "C3N ", "HC3N ", & 54 "NCCN ", "C4N2 ", "HV "/) 46 CHARACTER(len=10), DIMENSION(nkim+1) :: nomqy_c ! Initialized in calchim with null terminator 55 47 !! Hard-coded chemical species molar mass (g.mol-1), shares the same indexing than cnames. 56 48 REAL, DIMENSION(nkim), PARAMETER :: cmmol = (/ & … … 75 67 ! NB : For the startfile we use nlaykim_up grid (upper atm) and for outputs we use nlaykim_tot grid (all layers) 76 68 77 REAL*8, PARAMETER :: grkim_dz = 10.0 ! Vertical discretization of the upper chem sitry grid (km)69 REAL*8, PARAMETER :: grkim_dz = 10.0 ! Vertical discretization of the upper chemistry grid (km) 78 70 79 71 REAL,SAVE,ALLOCATABLE,DIMENSION(:) :: preskim ! Pressure (Pa) of upper chemistry (mid)-layers
Note: See TracChangeset
for help on using the changeset viewer.