Changeset 1246 for trunk/LMDZ.MARS/libf/phymars
- Timestamp:
- May 11, 2014, 2:37:58 PM (11 years ago)
- Location:
- trunk/LMDZ.MARS/libf/phymars
- Files:
-
- 3 deleted
- 24 edited
- 1 moved
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/libf/phymars/aeropacity.F
r1226 r1246 9 9 & nqdust 10 10 use comgeomfi_h, only: lati, sinlat ! grid point latitudes (rad) 11 use yomaer_h, only: tauvis12 11 use planete_h 13 12 USE comcstfi_h 13 use dimradmars_mod, only: naerkind, name_iaer, 14 & iaerdust,tauvis, 15 & iaer_dust_conrath,iaer_dust_doubleq, 16 & iaer_dust_submicron,iaer_h2o_ice 14 17 IMPLICIT NONE 15 18 c======================================================================= … … 58 61 !#include "comgeomfi.h" 59 62 !#include "dimradmars.h" 60 !#include "yomaer.h"61 63 !#include "tracer.h" 62 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)63 #include"scatterers.h"64 #include "aerkind.h"65 64 66 65 c----------------------------------------------------------------------- … … 131 130 CHARACTER(LEN=1) :: txt2 ! to temporarly store text 132 131 ! indexes of dust scatterers: 133 INTEGER,SAVE :: iaerdust(naerkind)134 132 INTEGER,SAVE :: naerdust ! number of dust scatterers 135 133 -
trunk/LMDZ.MARS/libf/phymars/aeroptproperties.F
r1212 r1246 4 4 & QREFvis3d,QREFir3d, 5 5 & omegaREFvis3d,omegaREFir3d) 6 use dimradmars_mod, only: nir, nsun 7 use yomaer_h, only:radiustab, nsize, QVISsQREF, omegavis, gvis,8 & 9 & 6 use dimradmars_mod, only: nir, nsun, naerkind, 7 & radiustab, nsize, QVISsQREF, omegavis, gvis, 8 & QIRsQREF, omegaIR, gIR, QREFvis, QREFir, 9 & omegaREFvis, omegaREFir 10 10 IMPLICIT NONE 11 11 c ============================================================= … … 31 31 #include "callkeys.h" 32 32 !#include "dimradmars.h" 33 !#include "yomaer.h"34 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)35 #include"scatterers.h"36 33 37 34 c Local variables … … 39 36 40 37 c ============================================================= 41 LOGICAL, PARAMETER :: varyingnueff(naerkind) = .false.38 LOGICAL,SAVE,ALLOCATABLE :: varyingnueff(:) 42 39 c ============================================================= 43 40 44 41 c Min. and max radius of the interpolation grid (in METERS) 45 REAL, SAVE :: refftabmin(naerkind,2) 46 REAL, SAVE :: refftabmax(naerkind,2) 42 REAL, SAVE, ALLOCATABLE :: refftabmin(:,:) 43 REAL, SAVE, ALLOCATABLE :: refftabmax(:,:) 44 47 45 c Log of the min and max variance of the interpolation grid 48 46 REAL, PARAMETER :: nuefftabmin = -4.6 … … 97 95 REAL,SAVE,ALLOCATABLE :: nuefftab(:,:,:) 98 96 c Volume ratio of the grid 99 REAL,SAVE :: logvratgrid(naerkind,2)97 REAL,SAVE,ALLOCATABLE :: logvratgrid(:,:) 100 98 c Grid used to remember which calculation is done 101 LOGICAL,SAVE :: checkgrid(refftabsize,nuefftabsize,naerkind,2) 102 & = .false. 99 LOGICAL,SAVE,ALLOCATABLE :: checkgrid(:,:,:,:) 103 100 c Optical properties of the grid (VISIBLE) 104 101 REAL,SAVE,ALLOCATABLE :: qsqrefVISgrid(:,:,:,:) … … 114 111 REAL,SAVE,ALLOCATABLE :: gIRgrid(:,:,:,:) 115 112 c Optical properties of the grid (REFERENCE WAVELENGTHS) 116 REAL,SAVE :: qrefVISgrid(refftabsize,nuefftabsize,naerkind)117 REAL,SAVE :: qscatrefVISgrid(refftabsize,nuefftabsize,naerkind)118 REAL,SAVE :: qrefIRgrid(refftabsize,nuefftabsize,naerkind)119 REAL,SAVE :: qscatrefIRgrid(refftabsize,nuefftabsize,naerkind)120 REAL,SAVE :: omegrefVISgrid(refftabsize,nuefftabsize,naerkind)121 REAL,SAVE :: omegrefIRgrid(refftabsize,nuefftabsize,naerkind)113 REAL,SAVE,ALLOCATABLE :: qrefVISgrid(:,:,:) 114 REAL,SAVE,ALLOCATABLE :: qscatrefVISgrid(:,:,:) 115 REAL,SAVE,ALLOCATABLE :: qrefIRgrid(:,:,:) 116 REAL,SAVE,ALLOCATABLE :: qscatrefIRgrid(:,:,:) 117 REAL,SAVE,ALLOCATABLE :: omegrefVISgrid(:,:,:) 118 REAL,SAVE,ALLOCATABLE :: omegrefIRgrid(:,:,:) 122 119 c Firstcall 123 120 LOGICAL,SAVE :: firstcall = .true. 124 121 c Variables used by the Gauss-Legendre integration: 125 REAL,SAVE :: normd(refftabsize,nuefftabsize,naerkind,2) 126 REAL,SAVE :: dista(refftabsize,nuefftabsize,naerkind,2,ngau) 127 REAL,SAVE :: distb(refftabsize,nuefftabsize,naerkind,2,ngau) 128 129 REAL,SAVE :: radGAUSa(ngau,naerkind,2) 130 REAL,SAVE :: radGAUSb(ngau,naerkind,2) 122 REAL,SAVE,ALLOCATABLE :: normd(:,:,:,:) 123 REAL,SAVE,ALLOCATABLE :: dista(:,:,:,:,:) 124 REAL,SAVE,ALLOCATABLE :: distb(:,:,:,:,:) 125 REAL,SAVE,ALLOCATABLE :: radGAUSa(:,:,:) 126 REAL,SAVE,ALLOCATABLE :: radGAUSb(:,:,:) 131 127 132 128 REAL,SAVE,ALLOCATABLE :: qsqrefVISa(:,:,:) … … 233 229 allocate(gIRa(nir,ngau,naerkind)) 234 230 allocate(gIRb(nir,ngau,naerkind)) 235 231 232 allocate(qrefVISgrid(refftabsize,nuefftabsize,naerkind)) 233 allocate(qscatrefVISgrid(refftabsize,nuefftabsize,naerkind)) 234 allocate(qrefIRgrid(refftabsize,nuefftabsize,naerkind)) 235 allocate(qscatrefIRgrid(refftabsize,nuefftabsize,naerkind)) 236 allocate(omegrefVISgrid(refftabsize,nuefftabsize,naerkind)) 237 allocate(omegrefIRgrid(refftabsize,nuefftabsize,naerkind)) 238 239 allocate(normd(refftabsize,nuefftabsize,naerkind,2)) 240 allocate(dista(refftabsize,nuefftabsize,naerkind,2,ngau)) 241 allocate(distb(refftabsize,nuefftabsize,naerkind,2,ngau)) 242 allocate(radGAUSa(ngau,naerkind,2)) 243 allocate(radGAUSb(ngau,naerkind,2)) 244 245 allocate(checkgrid(refftabsize,nuefftabsize,naerkind,2)) 246 checkgrid(1:refftabsize,1:nuefftabsize,1:naerkind,1:2) = .false. 247 248 allocate(logvratgrid(naerkind,2)) 249 250 allocate(refftabmin(naerkind,2)) 251 allocate(refftabmax(naerkind,2)) 252 253 allocate(varyingnueff(naerkind)) 254 varyingnueff(1:naerkind) = .false. 255 236 256 c 0.1 Pi! 237 257 pi = 2. * asin(1.e0) -
trunk/LMDZ.MARS/libf/phymars/callradite.F
r1226 r1246 6 6 7 7 use dimradmars_mod, only: ndomainsz, nflev, nsun, nir 8 use dimradmars_mod, only: naerkind, name_iaer, 9 & iaer_dust_conrath,iaer_dust_doubleq, 10 & iaer_dust_submicron,iaer_h2o_ice 8 11 use yomlw_h, only: gcp, nlaylte 9 12 USE comcstfi_h … … 153 156 #include "callkeys.h" 154 157 !#include "yomlw.h" 155 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)156 #include"scatterers.h"157 #include "aerkind.h"158 158 159 159 c----------------------------------------------------------------------- … … 272 272 allocate(pview(ngrid)) 273 273 274 c Please name the different scatterers here ----------------275 c PLEASE MAKE SURE that you set up the right number of276 c scatterers in scatterers.h (naerkind);277 name_iaer(1) = "dust_conrath" !! default choice is good old Conrath profile278 IF (doubleq.AND.active) name_iaer(1) = "dust_doubleq" !! two-moment scheme279 if (nq.gt.1) then280 ! trick to avoid problems compiling with 1 tracer281 ! and picky compilers who know name_iaer(2) is out of bounds282 j=2283 IF (water.AND.activice) name_iaer(j) = "h2o_ice" !! radiatively-active clouds284 IF (submicron.AND.active) name_iaer(j) = "dust_submicron" !! JBM experimental stuff285 endif ! of if (nq.gt.1)286 c ----------------------------------------------------------287 288 274 c Assign a number to the different scatterers 289 275 c ------------------------------------------- … … 352 338 ENDDO 353 339 gcp = g/cpp 354 355 c Logical tests for radiatively active water-ice clouds:356 IF ( (activice.AND.(.NOT.water)).OR.357 & (activice.AND.(naerkind.LT.2)) ) THEN358 WRITE(*,*) 'If activice is TRUE, water has to be set'359 WRITE(*,*) 'to TRUE, and "naerkind" must be at least'360 WRITE(*,*) 'equal to 2 in scatterers.h.'361 CALL ABORT362 ELSE IF ( (.NOT.activice).AND.(naerkind.GT.1) ) THEN363 WRITE(*,*) 'naerkind is greater than unity, but'364 WRITE(*,*) 'activice has not been set to .true.'365 WRITE(*,*) 'in callphys.def; this is not logical!'366 CALL ABORT367 ENDIF368 340 369 341 c Loading the optical properties in external look-up tables: -
trunk/LMDZ.MARS/libf/phymars/conf_phys.F
r1240 r1246 1 SUBROUTINE conf_phys(n q)1 SUBROUTINE conf_phys(ngrid,nlayer,nq) 2 2 3 3 !======================================================================= … … 38 38 use surfdat_h, only: albedo_h2o_ice, inert_h2o_ice, 39 39 & frost_albedo_threshold 40 use yomaer_h,only: tauvis41 40 use control_mod, only: ecritphy 42 41 use planete_h 43 42 USE comcstfi_h, only: daysec,dtphys 43 use dimradmars_mod, only: naerkind, name_iaer, 44 & ini_scatterers,tauvis 44 45 45 46 IMPLICIT NONE … … 52 53 !#include "surfdat.h" 53 54 !#include "dimradmars.h" 54 !#include "yomaer.h"55 55 #include "datafile.h" 56 56 !#include "slope.h" 57 57 #include "microphys.h" 58 58 !#include "tracer.h" 59 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #) 60 #include"scatterers.h" 61 62 INTEGER,INTENT(IN) :: nq 63 INTEGER ig,ierr 59 60 INTEGER,INTENT(IN) :: ngrid,nlayer,nq 61 INTEGER ig,ierr,j 64 62 65 63 CHARACTER ch1*12 … … 536 534 537 535 536 ! SCATTERERS 537 write(*,*) "how many scatterers?" 538 naerkind=1 ! default value 539 call getin("naerkind",naerkind) 540 write(*,*)" naerkind = ",naerkind 541 542 ! Test of incompatibility 543 c Logical tests for radiatively active water-ice clouds: 544 IF ( (activice.AND.(.NOT.water)).OR. 545 & (activice.AND.(naerkind.LT.2)) ) THEN 546 WRITE(*,*) 'If activice is TRUE, water has to be set' 547 WRITE(*,*) 'to TRUE, and "naerkind" must be at least' 548 WRITE(*,*) 'equal to 2.' 549 CALL ABORT 550 ELSE IF ( (.NOT.activice).AND.(naerkind.GT.1) ) THEN 551 WRITE(*,*) 'naerkind is greater than unity, but' 552 WRITE(*,*) 'activice has not been set to .true.' 553 WRITE(*,*) 'in callphys.def; this is not logical!' 554 CALL ABORT 555 ENDIF 556 557 !------------------------------------------ 558 !------------------------------------------ 559 ! once naerkind is known allocate arrays 560 ! -- we do it here and not in phys_var_init 561 ! -- because we need to know naerkind first 562 CALL ini_scatterers(ngrid,nlayer) 563 !------------------------------------------ 564 !------------------------------------------ 565 566 567 c Please name the different scatterers here ---------------- 568 name_iaer(1) = "dust_conrath" !! default choice is good old Conrath profile 569 IF (doubleq.AND.active) name_iaer(1) = "dust_doubleq" !! two-moment scheme 570 if (nq.gt.1) then 571 ! trick to avoid problems compiling with 1 tracer 572 ! and picky compilers who know name_iaer(2) is out of bounds 573 j=2 574 IF (water.AND.activice) name_iaer(j) = "h2o_ice" !! radiatively-active clouds 575 IF (submicron.AND.active) name_iaer(j) = "dust_submicron" !! JBM experimental stuff 576 endif ! of if (nq.gt.1) 577 c ---------------------------------------------------------- 578 538 579 ! THERMOSPHERE 539 580 -
trunk/LMDZ.MARS/libf/phymars/dimradmars_mod.F90
r1224 r1246 16 16 ! Number of kind of tracer radiative properties 17 17 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 18 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #) 19 20 #include"scatterers.h" 21 ! NB: May have to change value of nsizemax below when changing scatterers 18 ! naerkind is set by reading callphys.def 19 ! -- see conf_phys 20 ! -- value of nsizemax below is comfortably high 21 ! but beware in case you add a lot of scatterers 22 INTEGER, SAVE :: naerkind 23 24 ! AS: previously in aerkind.h 25 character*20, SAVE, ALLOCATABLE :: name_iaer(:) ! name of the scatterers 26 integer iaer_dust_conrath ! Typical dust profiles using a 27 ! Conrath type analytical equation 28 integer iaer_dust_doubleq ! Dust profile is given by the 29 ! mass mixing ratio of the two- 30 ! moment scheme method (doubleq) 31 integer iaer_dust_submicron ! Dust profile is given by a 32 ! submicron population of dust 33 ! particles 34 integer iaer_h2o_ice ! Water ice particles 35 36 ! AS: was in aeropacity 37 INTEGER,SAVE,ALLOCATABLE :: iaerdust(:) 38 39 ! AS: was in suaer 40 CHARACTER(LEN=30), SAVE, ALLOCATABLE :: file_id(:,:) 22 41 23 42 ! Reference wavelengths used to compute reference optical depth (m) 24 43 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 25 26 real,save :: longrefir(naerkind),longrefvis(naerkind) 44 REAL,SAVE,ALLOCATABLE :: longrefir(:),longrefvis(:) 27 45 28 46 ! Definition of spectral intervals at thermal infrared wavelengths (LW) … … 86 104 REAL,SAVE,ALLOCATABLE :: nueffdust(:,:) ! Dust effective variance 87 105 106 !! ------------------------------------------------------ 107 !! AS: what was previously in yomaer 108 ! Shortwave 109 ! ~~~~~~~~~ 110 ! 111 ! tauvis: dust optical depth at reference wavelength ("longrefvis" set 112 ! in dimradmars_mod : typically longrefvis = 0.67E-6 m, as measured by Viking ) 113 114 ! For the "naerkind" kind of aerosol radiative properties : 115 ! QVISsQREF : Qext / Qext("longrefvis") <--- For both solar bands 116 ! omegavis : sinle scattering albedo <--- For both solar bands 117 ! gvis : assymetry factor <--- For both solar bands 118 ! 119 ! Longwave 120 ! ~~~~~~~~ 121 ! 122 ! For the "naerkind" kind of aerosol radiative properties : 123 ! QIRsQREF : Qext / Qext("longrefvis") <--- For the nir bandes IR 124 ! omegaIR : mean single scattering albedo <--- For the nir bandes IR 125 ! gIR : mean assymetry factor <--- For the nir bandes IR 126 ! 127 real,save :: tauvis 128 real,save,allocatable :: QVISsQREF(:,:,:) 129 real,save,allocatable :: omegavis(:,:,:) 130 real,save,allocatable :: gvis(:,:,:) 131 real,save,allocatable :: QIRsQREF(:,:,:) 132 real,save,allocatable :: omegaIR(:,:,:) 133 real,save,allocatable :: gIR(:,:,:) 134 ! Actual number of grain size classes in each domain for a 135 ! given aerosol: 136 integer,save,allocatable :: nsize(:,:) 137 ! Particle size axis (depend on the kind of aerosol and the 138 ! radiation domain) 139 real,save,allocatable :: radiustab(:,:,:) 140 ! Extinction coefficient at reference wavelengths; 141 ! These wavelengths are defined in dimradmars_mod, and called 142 ! longrefvis and longrefir. 143 real,save,allocatable :: QREFvis(:,:) 144 real,save,allocatable :: QREFir(:,:) 145 real,save,allocatable :: omegaREFvis(:,:) 146 real,save,allocatable :: omegaREFir(:,:) 147 !! ------------------------------------------------------ 148 88 149 contains 89 150 90 151 subroutine ini_dimradmars_mod(ngrid,nlayer) 91 152 … … 107 168 allocate(fluxrad(ngrid)) 108 169 allocate(tauscaling(ngrid)) 170 allocate(nueffdust(ngrid,nlayer)) 171 172 end subroutine ini_dimradmars_mod 173 174 subroutine ini_scatterers(ngrid,nlayer) 175 176 implicit none 177 178 integer,intent(in) :: ngrid ! number of atmospheric columns 179 integer,intent(in) :: nlayer ! number of atmospheric layers 180 181 allocate(name_iaer(naerkind)) 109 182 allocate(aerosol(ngrid,nlayer,naerkind)) 110 allocate(nueffdust(ngrid,nlayer)) 111 112 end subroutine ini_dimradmars_mod 113 183 allocate(longrefir(naerkind)) 184 allocate(longrefvis(naerkind)) 185 allocate(iaerdust(naerkind)) 186 allocate(file_id(naerkind,2)) 187 188 allocate(QVISsQREF(nsun,naerkind,nsizemax)) 189 allocate(omegavis(nsun,naerkind,nsizemax)) 190 allocate(gvis(nsun,naerkind,nsizemax)) 191 allocate(QIRsQREF(nir,naerkind,nsizemax)) 192 allocate(omegaIR(nir,naerkind,nsizemax)) 193 allocate(gIR(nir,naerkind,nsizemax)) 194 allocate(nsize(naerkind,2)) 195 allocate(radiustab(naerkind,2,nsizemax)) 196 allocate(QREFvis(naerkind,nsizemax)) 197 allocate(QREFir(naerkind,nsizemax)) 198 allocate(omegaREFvis(naerkind,nsizemax)) 199 allocate(omegaREFir(naerkind,nsizemax)) 200 201 end subroutine ini_scatterers 202 114 203 end module dimradmars_mod -
trunk/LMDZ.MARS/libf/phymars/iniphysiq.F90
r1233 r1246 73 73 punjours,ptimestep,prad,pg,pr,pcpp) 74 74 call ini_fillgeom(ngrid,rlatd,rlond,airephy) 75 call conf_phys(n qtot)75 call conf_phys(ngrid,nlayer,nqtot) 76 76 77 77 !$OMP END PARALLEL -
trunk/LMDZ.MARS/libf/phymars/lect_start_archive.F
r1232 r1246 27 27 !#include "comsoil.h" 28 28 !#include "dimradmars.h" 29 !#include "yomaer.h"30 29 #include "paramet.h" 31 30 #include "comconst.h" -
trunk/LMDZ.MARS/libf/phymars/lwdiff.F
r1226 r1246 15 15 #include "callkeys.h" 16 16 17 !#include "yomaer.h"18 17 !#include "yomlw.h" 19 18 C----------------------------------------------------------------------- -
trunk/LMDZ.MARS/libf/phymars/lwmain.F
r1047 r1246 13 13 14 14 use dimradmars_mod, only: ndlo2, nflev, nir, ndlon, nuco2 15 use dimradmars_mod, only: naerkind 15 16 use yomlw_h, only: nlaylte, xi 16 17 implicit none … … 21 22 #include "callkeys.h" 22 23 #include "comg1d.h" 23 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)24 #include"scatterers.h"25 24 !#include "yomlw.h" 26 25 -
trunk/LMDZ.MARS/libf/phymars/lwu.F
r1226 r1246 32 32 33 33 use dimradmars_mod, only: ndlo2, nir, nuco2, ndlon, nflev 34 use dimradmars_mod, only: naerkind 34 35 use yomlw_h, only: nlaylte, tref, at, bt, cst_voigt 35 36 USE comcstfi_h … … 40 41 !#include "dimradmars.h" 41 42 42 !#include "yomaer.h"43 43 !#include "yomlw.h" 44 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)45 #include"scatterers.h"46 44 47 45 #include "callkeys.h" -
trunk/LMDZ.MARS/libf/phymars/newstart.F
r1241 r1246 43 43 !#include "comsoil.h" 44 44 !#include "dimradmars.h" 45 !#include "yomaer.h"46 45 #include "paramet.h" 47 46 #include "comconst.h" … … 391 390 . daysec,dtphys,rad,g,r,cpp) 392 391 call ini_fillgeom(ngridmx,latfi,lonfi,airefi) 393 call conf_phys(n qtot)392 call conf_phys(ngridmx,llm,nqtot) 394 393 395 394 c======================================================================= -
trunk/LMDZ.MARS/libf/phymars/phyetat0.F90
r1229 r1246 28 28 !#include "surfdat.h" 29 29 !#include "dimradmars.h" 30 !#include "yomaer.h"31 30 !#include "tracer.h" 32 31 !#include "advtrac.h" -
trunk/LMDZ.MARS/libf/phymars/phyredem.F90
r1226 r1246 18 18 z0_default, albedice, emisice, emissiv, & 19 19 iceradius, dtemisice, phisfi, z0 20 use yomaer_h, only: tauvis20 use dimradmars_mod, only: tauvis 21 21 use iostart, only : open_restartphy, close_restartphy, & 22 22 put_var, put_field, length -
trunk/LMDZ.MARS/libf/phymars/phys_state_var_init.F
r1233 r1246 35 35 use comsoil_h, only: ini_comsoil_h 36 36 use dimradmars_mod, only: ini_dimradmars_mod 37 use yomaer_h,only: ini_yomaer_h38 37 use yomlw_h, only: ini_yomlw_h 39 38 use conc_mod, only: ini_conc_mod … … 80 79 call ini_dimradmars_mod(ngrid,nlayer) 81 80 82 ! allocate arrays in "yomaer_h"83 call ini_yomaer_h84 85 81 ! allocate arrays in "yomlw_h" 86 82 call ini_yomlw_h(ngrid) -
trunk/LMDZ.MARS/libf/phymars/physiq.F
r1242 r1246 27 27 use control_mod, only: iphysiq, day_step, ecritstart 28 28 use dimradmars_mod, only: tauscaling, aerosol, 29 & dtrad, fluxrad_sky, fluxrad, albedo 29 & dtrad, fluxrad_sky, fluxrad, albedo, 30 & naerkind 30 31 use turb_mod, only: q2, wstar, ustar, sensibFlux, 31 32 & zmax_th, hfmax_th, turb_resolved … … 152 153 !#include "control.h" 153 154 !#include "dimradmars.h" 154 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)155 #include"scatterers.h"156 155 #include "comg1d.h" 157 156 !#include "tracer.h" … … 237 236 real,parameter :: odpref=610. ! DOD reference pressure (Pa) 238 237 REAL tau(ngrid,naerkind) ! Column dust optical depth at each point 238 ! AS: TBD: this one should be in a module ! 239 239 REAL zls ! solar longitude (rad) 240 240 REAL zday ! date (time since Ls=0, in martian days) … … 1168 1168 1169 1169 ! dust and ice surface area 1170 call surfacearea(ngrid, nlayer, ptimestep, zplay, zzlay, 1170 call surfacearea(ngrid, nlayer, naerkind, 1171 $ ptimestep, zplay, zzlay, 1171 1172 $ pt, pq, pdq, nq, 1172 1173 $ rdust, rice, tau, tauscaling, -
trunk/LMDZ.MARS/libf/phymars/simpleclouds.F
r1226 r1246 6 6 use tracer_mod, only: igcm_h2o_vap, igcm_h2o_ice 7 7 USE comcstfi_h 8 use dimradmars_mod, only: naerkind 8 9 implicit none 9 10 c------------------------------------------------------------------ … … 36 37 !#include "comgeomfi.h" 37 38 !#include "dimradmars.h" 38 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)39 #include"scatterers.h"40 39 41 40 c------------------------------------------------------------------ -
trunk/LMDZ.MARS/libf/phymars/suaer.F90
r1047 r1246 1 1 SUBROUTINE suaer 2 2 use dimradmars_mod, only: longrefvis, longrefir, nsizemax, long1vis, & 3 long2vis, long3vis, long1ir, long2ir, long1co2, & 4 long2co2, nsun, nir 5 use yomaer_h, only: radiustab, gvis, omegavis, QVISsQREF, gIR, omegaIR, & 6 QIRsQREF, QREFvis, QREFir, omegaREFvis, omegaREFir, & 3 long2vis, long3vis, long1ir, long2ir, long1co2, & 4 long2co2, nsun, nir,& 5 naerkind, name_iaer, & 6 iaer_dust_conrath,iaer_dust_doubleq,& 7 iaer_dust_submicron,iaer_h2o_ice,& 8 file_id,radiustab, gvis, omegavis, & 9 QVISsQREF, gIR, omegaIR, & 10 QIRsQREF, QREFvis, QREFir, & 11 omegaREFvis, omegaREFir, & 7 12 nsize 8 13 IMPLICIT NONE … … 43 48 !#include "dimphys.h" 44 49 !#include "dimradmars.h" 45 !#include "yomaer.h"46 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)47 #include"scatterers.h"48 #include "aerkind.h"49 50 50 51 ! Optical properties (read in external ASCII files) … … 92 93 REAL omegav(nir) ! Average sing.scat.albedo 93 94 REAL gav(nir) ! Average assymetry parameter 94 95 ! Local saved variables:96 97 CHARACTER(LEN=30), DIMENSION(naerkind,2), SAVE :: file_id98 95 99 96 !================================================================== -
trunk/LMDZ.MARS/libf/phymars/swmain.F
r1047 r1246 5 5 & QVISsQREF3d,omegaVIS3d,gVIS3d) 6 6 7 use dimradmars_mod, only: ndlo2, ndlon, nflev, nsun 7 use dimradmars_mod, only: ndlo2, ndlon, nflev, 8 & nsun,naerkind 8 9 use yomlw_h, only: nlaylte, gcp 9 10 IMPLICIT NONE … … 13 14 !#include "dimradmars.h" 14 15 15 !#include "yomaer.h"16 16 !#include "yomlw.h" 17 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)18 #include"scatterers.h"19 17 #include "callkeys.h" 20 18 c -
trunk/LMDZ.MARS/libf/phymars/swr_fouquart.F
r1047 r1246 4 4 S , PFD,PFU ) 5 5 6 use dimradmars_mod, only: sunfr, ndlo2, nsun, ndlon, nflev 6 use dimradmars_mod, only: sunfr, ndlo2, nsun, 7 & ndlon, nflev, naerkind 7 8 use yomlw_h, only: nlaylte 8 9 IMPLICIT NONE … … 12 13 !#include "dimradmars.h" 13 14 #include "callkeys.h" 14 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)15 #include"scatterers.h"16 !#include "yomaer.h"17 15 !#include "yomlw.h" 18 16 -
trunk/LMDZ.MARS/libf/phymars/swr_toon.F
r1047 r1246 4 4 S , PFD,PFU ) 5 5 6 use dimradmars_mod, only: sunfr, ndlo2, nsun, nflev, ndlon 6 use dimradmars_mod, only: sunfr, ndlo2, nsun, nflev, 7 & ndlon, naerkind 7 8 use yomlw_h, only: nlaylte 8 9 … … 13 14 !#include "dimradmars.h" 14 15 #include "callkeys.h" 15 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)16 #include"scatterers.h"17 16 !#include "yomaer.h" 18 17 !#include "yomlw.h" -
trunk/LMDZ.MARS/libf/phymars/tabfi.F
r1226 r1246 47 47 use surfdat_h, only: z0_default, emissiv, emisice, albedice, 48 48 & iceradius, dtemisice, iceradius 49 use yomaer_h, only: tauvis49 use dimradmars_mod, only: tauvis 50 50 use iostart, only: get_var 51 51 use mod_phys_lmdz_para, only: is_parallel … … 61 61 #include "netcdf.inc" 62 62 !#include "dimradmars.h" 63 !#include "yomaer.h"64 63 65 64 c----------------------------------------------------------------------- -
trunk/LMDZ.MARS/libf/phymars/testphys1d.F
r1233 r1246 6 6 use comsoil_h, only: volcapa, layer, mlayer, inertiedat, nsoilmx 7 7 use comgeomfi_h, only: lati, long, area, sinlat, ini_fillgeom 8 9 8 use surfdat_h, only: albedodat, z0_default, emissiv, emisice, 10 9 & albedice, iceradius, dtemisice, z0, … … 12 11 & watercaptag 13 12 use slope_mod, only: theta_sl, psi_sl 14 use yomaer_h, only: tauvis15 13 use control_mod, only: day_step 16 14 use phyredem, only: physdem0,physdem1 … … 20 18 use comcstfi_h, only: pi, rad, daysec, omeg, g, mugaz, rcp, r, 21 19 & cpp, dtphys 22 use dimradmars_mod, only: tauscaling 20 use dimradmars_mod, only: tauscaling,tauvis 23 21 IMPLICIT NONE 24 22 … … 53 51 #include "callkeys.h" 54 52 !#include "comsaison.h" 55 !#include "yomaer.h"56 53 !#include "control.h" 57 54 #include "comvert.h" … … 483 480 . daysec,dtphys,rad,g,r,cpp) 484 481 call ini_fillgeom(1,latitude,longitude,1.0) 485 call conf_phys( nq)482 call conf_phys(1,llm,nq) 486 483 487 484 -
trunk/LMDZ.MARS/libf/phymars/updatereffrad.F
r1226 r1246 8 8 & igcm_ccn_number, nuice_ref, varian, 9 9 & ref_r0, igcm_dust_submicron 10 USE dimradmars_mod, only: nueffdust 10 USE dimradmars_mod, only: nueffdust,naerkind, 11 & name_iaer, 12 & iaer_dust_conrath,iaer_dust_doubleq, 13 & iaer_dust_submicron,iaer_h2o_ice 11 14 USE comcstfi_h 12 15 IMPLICIT NONE … … 37 40 !#include "dimradmars.h" 38 41 !#include "tracer.h" 39 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)40 #include"scatterers.h"41 #include "aerkind.h"42 42 !#include "yomaer.h" 43 43 -
trunk/LMDZ.MARS/libf/phymars/watercloud.F
r1226 r1246 12 12 & igcm_ccn_mass, igcm_ccn_number, 13 13 & rho_dust, nuice_sed, nuice_ref 14 use dimradmars_mod, only: naerkind 14 15 IMPLICIT NONE 15 16 … … 41 42 !#include "comgeomfi.h" 42 43 !#include "dimradmars.h" 43 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #)44 #include"scatterers.h"45 44 46 45 c Inputs:
Note: See TracChangeset
for help on using the changeset viewer.