Changeset 2265
- Timestamp:
- Mar 20, 2020, 6:42:17 PM (5 years ago)
- Location:
- trunk/LMDZ.MARS
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/README
r2264 r2265 2907 2907 start file. 2908 2908 2909 == 20/03/2020 == EM 2910 Save "dtau", the opacity difference between model and target dust scenario 2911 in the restartfi.nc file so that we have 1+1=2 when running with dust 2912 injection schemes. 2913 -
trunk/LMDZ.MARS/libf/phymars/compute_dtau_mod.F90
r2166 r2265 1 1 MODULE compute_dtau_mod 2 2 3 3 IMPLICIT NONE 4 4 5 5 include "callkeys.h" 6 6 7 8 7 REAL,SAVE :: ti_injection_sol ! time of beginning injection 8 REAL,SAVE :: tf_injection_sol ! time of end injection 9 9 REAL,PARAMETER :: t_scenario_sol=14/24. ! time of tauref_scenario 10 10 11 CONTAINS 11 REAL,SAVE,ALLOCATABLE :: dtau(:) ! Dust opacity difference (at 610Pa) 12 ! between GCM and dust scenario 12 13 13 SUBROUTINE compute_dtau(ngrid,nlayer, & 14 & zday,pplev,tauref, & 15 & ptimestep,dustliftday,local_time) 14 CONTAINS 16 15 17 USE geometry_mod, only: longitude_deg 16 SUBROUTINE compute_dtau(ngrid,nlayer, & 17 zday,pplev,tauref, & 18 ptimestep,dustliftday,local_time) 19 20 USE geometry_mod, only: longitude_deg 18 21 USE time_phylmdz_mod, only: dtphys, daysec 19 22 USE comcstfi_h, only: g 20 23 USE tracer_mod, only: alpha_lift,igcm_dust_mass,igcm_dust_number 21 22 23 24 USE dimradmars_mod, only: tauvis 25 26 IMPLICIT NONE 24 27 25 28 include "callkeys.h" 26 29 27 30 INTEGER, INTENT(in) :: ngrid 28 31 INTEGER, INTENT(in) :: nlayer 29 32 REAL, INTENT(in) :: zday ! date at lon=0, in fraction of sols 30 31 32 33 REAL, INTENT(in) :: pplev(ngrid,nlayer+1) ! pressure (Pa) 34 REAL, INTENT(in) :: tauref(ngrid) ! Computed dust opacity at 610Pa 35 REAL, INTENT(in) :: ptimestep 33 36 REAL, INTENT(in) :: local_time(ngrid) 34 37 REAL, INTENT(out) :: dustliftday(ngrid) ! Dust injection rate (s-1) 35 38 36 39 INTEGER :: ig, l 37 40 INTEGER, SAVE :: nb_daystep ! nomber of step a day 38 41 REAL :: tauref_scenario(ngrid) ! from dust scenario 39 42 REAL :: zday_scenario 40 43 REAL,ALLOCATABLE,SAVE :: local_time_prev(:) 41 REAL,ALLOCATABLE,SAVE :: dtau(:) ! Dust opacity increment (at 610Pa)42 44 REAL,PARAMETER :: odpref=610. !DOD reference pressure (Pa) 43 45 … … 47 49 IF(firstcall)THEN 48 50 ALLOCATE(local_time_prev(ngrid)) 49 ALLOCATE(dtau(ngrid))50 51 DO ig=1,ngrid 51 52 local_time_prev(ig)=modulo(1.+(zday-ptimestep/daysec)& 52 -INT(zday-ptimestep/daysec) 53 -INT(zday-ptimestep/daysec) & 53 54 +(longitude_deg(ig)/15)/24,1.) 54 dtau(ig)=0.55 55 ENDDO 56 56 nb_daystep=(daysec/dtphys) … … 61 61 ENDIF 62 62 63 64 65 66 67 63 ! 1. Obtain tauref_scenario from dust scenario at zday+1 64 if (iaervar.eq.1) then 65 tauref_scenario = tauvis 66 else 67 zday_scenario=zday-modulo(zday,1.) ! integer value of the day: the scenario opacity is measured at 14:00 68 68 zday_scenario=zday_scenario+1 ! opacity of the dust scenario is read the day after 69 call read_dust_scenario(ngrid,nlayer,zday_scenario,pplev, 70 &tauref_scenario)69 call read_dust_scenario(ngrid,nlayer,zday_scenario,pplev, & 70 tauref_scenario) 71 71 endif 72 72 ! for diagnostics 73 73 call WRITEDIAGFI(ngrid,"tauref_scenario","tauref_scenario", & 74 &"",2,tauref_scenario)74 "",2,tauref_scenario) 75 75 76 ! 2. Compute dtau 77 78 IF ((local_time(ig).ge.t_scenario_sol).and. 79 &(local_time_prev(ig).lt.(t_scenario_sol)))THEN80 76 ! 2. Compute dtau() and dustliftday() 77 DO ig=1,ngrid 78 IF ((local_time(ig).ge.t_scenario_sol).and. & 79 (local_time_prev(ig).lt.(t_scenario_sol)))THEN 80 dtau(ig)=tauref_scenario(ig)-tauref(ig) 81 81 ENDIF 82 83 ! Use dtau (when positiove) to compute dustliftday 82 84 IF (dtau(ig).LT.0) THEN 83 dtau(ig)=0. 85 dustliftday(ig)=0. 86 ELSE 87 dustliftday(ig)=coeff_injection* & 88 (dtau(ig)*pplev(ig,1)/odpref) & 89 /(daysec*(tf_injection_sol-ti_injection_sol)) 84 90 ENDIF 85 86 ! 3. Use dtau to compute dustliftday 87 dustliftday(ig)=coeff_injection* & 88 & (dtau(ig)*pplev(ig,1)/odpref) & 89 & /(daysec*(tf_injection_sol-ti_injection_sol)) 90 ENDDO 91 ENDDO ! of DO ig=1,ngrid 92 93 ! for diagnostics 94 call WRITEDIAGFI(ngrid,"dtau","opacity difference wrt scenario",& 95 "",2,dtau) 96 call WRITEDIAGFI(ngrid,"dustliftday","dust injection rate", & 97 "s-1",2,dustliftday) 91 98 92 99 ! 4. Save local time … … 95 102 end subroutine compute_dtau 96 103 97 end module compute_dtau_mod 104 !======================================================================= 105 ! Initialization of the module variables 106 107 subroutine ini_compute_dtau_mod(ngrid) 108 109 implicit none 110 111 integer, intent(in) :: ngrid 112 113 allocate(dtau(ngrid)) 114 115 end subroutine ini_compute_dtau_mod 116 117 subroutine end_compute_dtau_mod 118 119 implicit none 120 121 if (allocated(dtau)) deallocate(dtau) 122 123 end subroutine end_compute_dtau_mod 124 125 END MODULE compute_dtau_mod -
trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90
r2264 r2265 18 18 use ioipsl_getincom, only : getin 19 19 use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd 20 use compute_dtau_mod, only: dtau 21 20 22 implicit none 21 23 … … 342 344 endif 343 345 346 ! dtau: opacity difference between GCM and dust scenario 347 call get_field("dtau",dtau,found,indextime) 348 if (.not.found) then 349 write(*,*) "phyetat0: <dtau> not in file; set to zero" 350 dtau(:) = 0 351 else 352 write(*,*) "phyetat0: opacity diff wrt scenario <dtau> range:", & 353 minval(dtau), maxval(dtau) 354 endif 355 356 344 357 ! Sub-grid cloud fraction 345 358 call get_field("totcloudfrac",totcloudfrac,found,indextime) -
trunk/LMDZ.MARS/libf/phymars/phyredem.F90
r2260 r2265 156 156 use tracer_mod, only: noms ! tracer names 157 157 use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd 158 use compute_dtau_mod, only: dtau 158 159 159 160 implicit none … … 226 227 call put_field("tauscaling","dust conversion factor",tauscaling,time) 227 228 229 if (dustinjection.gt.0) then 230 call put_field("dtau","dust opacity difference between GCM and scenario",& 231 dtau,time) 232 endif 233 228 234 if (calltherm) then 229 235 call put_field("wstar","Max vertical velocity in thermals",wstar,time) -
trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90
r2223 r2265 48 48 use time_phylmdz_mod, only: init_time 49 49 use co2cloud_mod, only: ini_co2cloud,end_co2cloud 50 use compute_dtau_mod, only: ini_compute_dtau_mod, & 51 end_compute_dtau_mod 50 52 use rocketduststorm_mod, only: ini_rocketduststorm_mod, & 51 53 end_rocketduststorm_mod … … 126 128 call ini_co2cloud(ngrid,nlayer) 127 129 130 ! allocate arrays in "compute_dtau_mod": 131 call end_compute_dtau_mod 132 call ini_compute_dtau_mod(ngrid) 133 128 134 ! allocate arrays in "rocketduststorm_mod": 129 135 call end_rocketduststorm_mod -
trunk/LMDZ.MARS/libf/phymars/physiq_mod.F
r2260 r2265 909 909 ENDIF ! (CLFvarying) 910 910 911 ! ! Dustinjection 912 ! if (dustinjection.gt.0) then 913 ! CALL compute_dtau(ngrid,nlayer, 914 ! & zday,pplev,tauref, 915 ! & ptimestep,dustliftday,local_time) 916 ! endif 917 c============================================================================ 911 !============================================================================ 918 912 919 913 #ifdef DUSTSTORM … … 2024 2018 ENDDO 2025 2019 2026 c Test watercap2027 c DO ig=1,ngrid2028 c qsurf(iq,igcm_h2o_ice)=qsurf(iq,igcm_h2o_ice)+watercap(ig)2029 c ENDDO2030 2031 2020 c----------------------------------------------------------------------- 2032 2021 c 13. Write output files
Note: See TracChangeset
for help on using the changeset viewer.