Changeset 2897 for trunk/LMDZ.COMMON/libf/evolution/read_data_GCM.F90
- Timestamp:
- Feb 16, 2023, 5:29:48 PM (22 months ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/read_data_GCM.F90
r2895 r2897 2 2 ! $Id $ 3 3 ! 4 SUBROUTINE read_data_GCM(fichnom,timelen, iim_input,jjm_input, vmr_co2_gcm,ps_GCM, &5 min_co2_ice _slope,min_h2o_ice_slope,nslope,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,TI_ave,q_co2_GCM,q_h2o_GCM,co2_ice_slope, &6 watersurf_density ,watersoil_density)4 SUBROUTINE read_data_GCM(fichnom,timelen, iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries, & 5 min_co2_ice,min_h2o_ice,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,TI_ave,q_co2,q_h2o,co2_ice_slope, & 6 watersurf_density_ave,watersoil_density) 7 7 8 8 use netcdf, only: nf90_open,NF90_NOWRITE,nf90_noerr,nf90_strerror, & … … 28 28 CHARACTER(LEN=*), INTENT(IN) :: fichnom !--- FILE NAME 29 29 INTEGER, INTENT(IN) :: timelen ! number of times stored in the file 30 INTEGER :: iim_input,jjm_input,nslope ! number of points in the lat x lon dynamical grid, number of subgrid slopes 31 30 INTEGER :: iim_input,jjm_input,ngrid,nslope ! number of points in the lat x lon dynamical grid, number of subgrid slopes 32 31 ! Ouputs 33 REAL, INTENT(OUT) :: min_co2_ice_slope(iim_input+1,jjm_input+1,nslope) ! Minimum of co2 ice per slope of the year [kg/m^2] 34 REAL, INTENT(OUT) :: min_h2o_ice_slope(iim_input+1,jjm_input+1,nslope) ! Minimum of h2o ice per slope of the year [kg/m^2] 35 REAL, INTENT(OUT) :: vmr_co2_gcm(iim_input+1,jjm_input+1,timelen) ! CO2 volume mixing ratio in the first layer [mol/m^3] 36 REAL, INTENT(OUT) :: q_h2o_GCM(iim_input+1,jjm_input+1,timelen) ! H2O mass mixing ratio in the first layer [kg/m^3] 37 REAL, INTENT(OUT) :: q_co2_GCM(iim_input+1,jjm_input+1,timelen) ! CO2 mass mixing ratio in the first layer [kg/m^3] 38 REAL, INTENT(OUT) :: ps_GCM(iim_input+1,jjm_input+1,timelen) ! Surface Pressure [Pa] 39 REAL, INTENT(OUT) :: co2_ice_slope(iim_input+1,jjm_input+1,nslope,timelen) ! co2 ice amount per slope of the year [kg/m^2] 40 32 REAL, INTENT(OUT) :: min_co2_ice(ngrid,nslope) ! Minimum of co2 ice per slope of the year [kg/m^2] 33 REAL, INTENT(OUT) :: min_h2o_ice(ngrid,nslope) ! Minimum of h2o ice per slope of the year [kg/m^2] 34 REAL, INTENT(OUT) :: vmr_co2_gcm_phys(ngrid,timelen) ! Physics x Times co2 volume mixing ratio retrieve from the gcm [m^3/m^3] 35 REAL, INTENT(OUT) :: ps_timeseries(ngrid,timelen)! Surface Pressure [Pa] 36 REAL, INTENT(OUT) :: q_co2(ngrid,timelen) ! CO2 mass mixing ratio in the first layer [kg/m^3] 37 REAL, INTENT(OUT) :: q_h2o(ngrid,timelen) ! H2O mass mixing ratio in the first layer [kg/m^3] 38 REAL, INTENT(OUT) :: co2_ice_slope(ngrid,nslope,timelen) ! co2 ice amount per slope of the year [kg/m^2] 41 39 !SOIL 42 REAL, INTENT(OUT) :: tsurf_ave(iim_input+1,jjm_input+1,nslope) ! Average surface temperature of the concatenated file [K] 43 REAL, INTENT(OUT) :: tsoil_ave(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average soil temperature of the concatenated file [K] 44 REAL ,INTENT(OUT) :: tsurf_gcm(iim_input+1,jjm_input+1,nslope,timelen) ! Surface temperature of the concatenated file, time series [K] 45 REAL , INTENT(OUT) :: tsoil_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Soil temperature of the concatenated file, time series [K] 46 REAL , INTENT(OUT) :: watersurf_density(iim_input+1,jjm_input+1,nslope,timelen) ! Water density at the surface, time series [kg/m^3] 47 REAL , INTENT(OUT) :: watersoil_density(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Water density in the soil layer, time series [kg/m^3] 48 REAL :: TI_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Thermal Inertia of the concatenated file, times series [SI] 49 REAL, INTENT(OUT) :: TI_ave(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average Thermal Inertia of the concatenated file [SI] 40 REAL, INTENT(OUT) :: tsurf_ave(ngrid,nslope) ! Average surface temperature of the concatenated file [K] 41 REAL, INTENT(OUT) :: tsoil_ave(ngrid,nsoilmx,nslope) ! Average soil temperature of the concatenated file [K] 42 REAL ,INTENT(OUT) :: tsurf_gcm(ngrid,nslope,timelen) ! Surface temperature of the concatenated file, time series [K] 43 REAL , INTENT(OUT) :: tsoil_gcm(ngrid,nsoilmx,nslope,timelen) ! Soil temperature of the concatenated file, time series [K] 44 REAL , INTENT(OUT) :: watersurf_density_ave(ngrid,nslope) ! Water density at the surface [kg/m^3] 45 REAL , INTENT(OUT) :: watersoil_density(ngrid,nsoilmx,nslope,timelen) ! Water density in the soil layer, time series [kg/m^3] 46 REAL, INTENT(OUT) :: TI_ave(ngrid,nsoilmx,nslope) ! Average Thermal Inertia of the concatenated file [SI] 50 47 !=============================================================================== 51 48 ! Local Variables … … 59 56 60 57 INTEGER :: edges(4),corner(4) 61 INTEGER :: i,j, t ! loop variables58 INTEGER :: i,j,l,t ! loop variables 62 59 real,save :: m_co2, m_noco2, A , B, mmean ! Molar Mass of co2 and no co2, A;B intermediate variables to compute the mean molar mass of the layer 63 60 64 61 INTEGER :: islope ! loop for variables 65 62 CHARACTER*2 :: num ! for reading sloped variables 66 REAL, ALLOCATABLE :: h2o_ice_s(:,:,:) ! h2o ice, mesh averaged, of the concatenated file [kg/m^2] 67 REAL, ALLOCATABLE :: co2_ice_s(:,:,:) ! co2 ice, mesh averaged, of the concatenated file [kg/m^2] 68 REAL, ALLOCATABLE :: h2o_ice_s_slope(:,:,:,:) ! h2o ice per slope of the concatenated file [kg/m^2] 69 REAL, ALLOCATABLE :: watercap_slope(:,:,:,:) 63 REAL :: h2o_ice_s_dyn(iim_input+1,jjm_input+1,nslope,timelen) ! h2o ice per slope of the concatenated file [kg/m^2] 64 REAL :: watercap_slope(iim_input+1,jjm_input+1,nslope,timelen) 65 REAL :: vmr_co2_gcm(iim_input+1,jjm_input+1,timelen) ! CO2 volume mixing ratio in the first layer [mol/m^3] 66 REAL :: ps_GCM(iim_input+1,jjm_input+1,timelen) ! Surface Pressure [Pa] 67 REAL :: min_co2_ice_dyn(iim_input+1,jjm_input+1,nslope) 68 REAL :: min_h2o_ice_dyn(iim_input+1,jjm_input+1,nslope) 69 REAL :: tsurf_ave_dyn(iim_input+1,jjm_input+1,nslope) ! Average surface temperature of the concatenated file [K] 70 REAL :: tsoil_ave_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average soil temperature of the concatenated file [K] 71 REAL :: tsurf_gcm_dyn(iim_input+1,jjm_input+1,nslope,timelen) ! Surface temperature of the concatenated file, time series [K] 72 REAL :: tsoil_gcm_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen)! Soil temperature of the concatenated file, time series [K] 73 REAL :: TI_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Thermal Inertia of the concatenated file, times series [SI] 74 REAL :: TI_ave_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average Thermal Inertia of the concatenated file [SI] 75 REAL :: q_co2_dyn(iim_input+1,jjm_input+1,timelen) ! CO2 mass mixing ratio in the first layer [kg/m^3] 76 REAL :: q_h2o_dyn(iim_input+1,jjm_input+1,timelen) ! H2O mass mixing ratio in the first layer [kg/m^3] 77 REAL :: co2_ice_slope_dyn(iim_input+1,jjm_input+1,nslope,timelen) ! co2 ice amount per slope of the year [kg/m^2] 78 REAL :: watersurf_density_dyn(iim_input+1,jjm_input+1,nslope,timelen)! Water density at the surface, time series [kg/m^3] 79 REAL :: watersurf_density(ngrid,nslope,timelen) ! Water density at the surface, time series [kg/m^3] 80 REAL :: watersoil_density_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Water density in the soil layer, time series [kg/m^3] 81 70 82 !----------------------------------------------------------------------- 71 83 modname="read_data_gcm" … … 76 88 B=1/m_noco2 77 89 78 allocate(h2o_ice_s_slope(iim+1,jjm+1,nslope,timelen))79 80 90 print *, "Opening ", fichnom, "..." 81 91 … … 86 96 print *, "Downloading data for vmr co2..." 87 97 88 CALL get_var3("co2_cropped" ,q_co2_ GCM)98 CALL get_var3("co2_cropped" ,q_co2_dyn) 89 99 90 100 print *, "Downloading data for vmr co2 done" 91 101 print *, "Downloading data for vmr h20..." 92 102 93 CALL get_var3("h2o_cropped" ,q_h2o_ GCM)103 CALL get_var3("h2o_cropped" ,q_h2o_dyn) 94 104 95 105 print *, "Downloading data for vmr h2o done" … … 106 116 DO islope=1,nslope 107 117 write(num,fmt='(i2.2)') islope 108 call get_var3("co2ice_slope"//num,co2_ice_slope (:,:,islope,:))118 call get_var3("co2ice_slope"//num,co2_ice_slope_dyn(:,:,islope,:)) 109 119 ENDDO 110 120 … … 114 124 DO islope=1,nslope 115 125 write(num,fmt='(i2.2)') islope 116 call get_var3("h2o_ice_s_slope"//num,h2o_ice_s_ slope(:,:,islope,:))126 call get_var3("h2o_ice_s_slope"//num,h2o_ice_s_dyn(:,:,islope,:)) 117 127 ENDDO 118 128 … … 122 132 DO islope=1,nslope 123 133 write(num,fmt='(i2.2)') islope 124 !call get_var3("watercap_slope"//num,watercap_slope(:,:,islope,:))125 watercap_slope(:,:,:,:)= 0.134 call get_var3("watercap_slope"//num,watercap_slope(:,:,islope,:)) 135 ! watercap_slope(:,:,:,:)= 0. 126 136 ENDDO 127 137 print *, "Downloading data for watercap_slope done" … … 131 141 DO islope=1,nslope 132 142 write(num,fmt='(i2.2)') islope 133 call get_var3("tsurf_slope"//num,tsurf_gcm (:,:,islope,:))143 call get_var3("tsurf_slope"//num,tsurf_gcm_dyn(:,:,islope,:)) 134 144 ENDDO 135 145 … … 142 152 DO islope=1,nslope 143 153 write(num,fmt='(i2.2)') islope 144 call get_var4("tsoil_slope"//num,tsoil_gcm (:,:,:,islope,:))154 call get_var4("tsoil_slope"//num,tsoil_gcm_dyn(:,:,:,islope,:)) 145 155 ENDDO 146 156 … … 159 169 DO islope=1,nslope 160 170 write(num,fmt='(i2.2)') islope 161 call get_var4("Waterdensity_soil_slope"//num,watersoil_density (:,:,:,islope,:))171 call get_var4("Waterdensity_soil_slope"//num,watersoil_density_dyn(:,:,:,islope,:)) 162 172 ENDDO 163 173 … … 168 178 DO islope=1,nslope 169 179 write(num,fmt='(i2.2)') islope 170 call get_var3("Waterdensity_surface"//num,watersurf_density (:,:,islope,:))180 call get_var3("Waterdensity_surface"//num,watersurf_density_dyn(:,:,islope,:)) 171 181 ENDDO 172 182 … … 176 186 177 187 else !nslope=1 no slope, we copy all the values 178 co2_ice_slope(:,:,1,:)=co2_ice_s(:,:,:) 179 h2o_ice_s_slope(:,:,1,:)=h2o_ice_s(:,:,:) 180 call get_var3("tsurf",tsurf_gcm(:,:,1,:)) 188 189 CALL get_var3("h2o_ice_s", h2o_ice_s_dyn(:,:,1,:)) 190 CALL get_var3("co2ice", co2_ice_slope_dyn(:,:,1,:)) 191 call get_var3("tsurf", tsurf_gcm_dyn(:,:,1,:)) 192 #ifndef CPP_STD 193 call get_var3("watercap", watercap_slope(:,:,1,:)) 194 #endif 195 181 196 if(soil_pem) then 182 call get_var4("tsoil",tsoil_gcm (:,:,:,1,:))197 call get_var4("tsoil",tsoil_gcm_dyn(:,:,:,1,:)) 183 198 call get_var4("inertiesoil",TI_gcm(:,:,:,1,:)) 184 199 endif !soil_pem … … 187 202 ! Compute the minimum over the year for each point 188 203 print *, "Computing the min of h2o_ice_slope" 189 ! min_h2o_ice_slope(:,:,:)=minval(h2o_ice_s_slope+watercap_slope,4)190 min_h2o_ice_slope(:,:,:)=minval(h2o_ice_s_slope,4)204 min_h2o_ice_dyn(:,:,:)=minval(h2o_ice_s_dyn+watercap_slope,4) 205 ! min_h2o_ice_dyn(:,:,:)=minval(h2o_ice_s_dyn,4) 191 206 print *, "Computing the min of co2_ice_slope" 192 min_co2_ice_ slope(:,:,:)=minval(co2_ice_slope,4)207 min_co2_ice_dyn(:,:,:)=minval(co2_ice_slope_dyn,4) 193 208 194 209 !Compute averages 195 210 196 211 print *, "Computing average of tsurf" 197 tsurf_ave(:,:,:)=SUM(tsurf_gcm(:,:,:,:),4)/timelen 212 tsurf_ave_dyn(:,:,:)=SUM(tsurf_gcm_dyn(:,:,:,:),4)/timelen 213 214 DO islope = 1,nslope 215 DO t=1,timelen 216 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,watersurf_density_dyn(:,:,islope,t),watersurf_density(:,islope,t)) 217 ENDDO 218 ENDDO 198 219 199 220 if(soil_pem) then 200 221 print *, "Computing average of tsoil" 201 tsoil_ave (:,:,:,:)=SUM(tsoil_gcm(:,:,:,:,:),5)/timelen222 tsoil_ave_dyn(:,:,:,:)=SUM(tsoil_gcm_dyn(:,:,:,:,:),5)/timelen 202 223 print *, "Computing average of TI" 203 TI_ave(:,:,:,:)=SUM(TI_gcm(:,:,:,:,:),5)/timelen 224 TI_ave_dyn(:,:,:,:)=SUM(TI_gcm(:,:,:,:,:),5)/timelen 225 print *, "Computing average of watersurf_density" 226 watersurf_density_ave(:,:) = SUM(watersurf_density(:,:,:),3)/timelen 204 227 endif 205 228 … … 208 231 DO j = 1, jjm+1 209 232 DO islope=1,nslope 210 if (min_co2_ice_ slope(i,j,islope).LT.0) then211 min_co2_ice_ slope(i,j,islope) = 0.233 if (min_co2_ice_dyn(i,j,islope).LT.0) then 234 min_co2_ice_dyn(i,j,islope) = 0. 212 235 endif 213 if (min_h2o_ice_ slope(i,j,islope).LT.0) then214 min_h2o_ice_ slope(i,j,islope) = 0.236 if (min_h2o_ice_dyn(i,j,islope).LT.0) then 237 min_h2o_ice_dyn(i,j,islope) = 0. 215 238 endif 216 239 ENDDO … … 221 244 DO j = 1, jjm+1 222 245 DO t = 1, timelen 223 if (q_co2_ GCM(i,j,t).LT.0) then224 q_co2_ GCM(i,j,t)=1E-10225 elseif (q_co2_ GCM(i,j,t).GT.1) then226 q_co2_ GCM(i,j,t)=1.246 if (q_co2_dyn(i,j,t).LT.0) then 247 q_co2_dyn(i,j,t)=1E-10 248 elseif (q_co2_dyn(i,j,t).GT.1) then 249 q_co2_dyn(i,j,t)=1. 227 250 endif 228 if (q_h2o_ GCM(i,j,t).LT.0) then229 q_h2o_ GCM(i,j,t)=1E-30230 elseif (q_h2o_ GCM(i,j,t).GT.1) then231 q_h2o_ GCM(i,j,t)=1.251 if (q_h2o_dyn(i,j,t).LT.0) then 252 q_h2o_dyn(i,j,t)=1E-30 253 elseif (q_h2o_dyn(i,j,t).GT.1) then 254 q_h2o_dyn(i,j,t)=1. 232 255 endif 233 mmean=1/(A*q_co2_ GCM(i,j,t) +B)234 vmr_co2_gcm(i,j,t) = q_co2_ GCM(i,j,t)*mmean/m_co2256 mmean=1/(A*q_co2_dyn(i,j,t) +B) 257 vmr_co2_gcm(i,j,t) = q_co2_dyn(i,j,t)*mmean/m_co2 235 258 ENDDO 236 259 ENDDO 237 260 ENDDO 238 261 239 deallocate(h2o_ice_s_slope) 262 CALL gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,vmr_co2_gcm,vmr_co2_gcm_phys) 263 call gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,ps_GCM,ps_timeseries) 264 CALL gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,q_co2_dyn,q_co2) 265 CALL gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,q_h2o_dyn,q_h2o) 266 267 DO islope = 1,nslope 268 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,min_co2_ice_dyn(:,:,islope),min_co2_ice(:,islope)) 269 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,min_h2o_ice_dyn(:,:,islope),min_h2o_ice(:,islope)) 270 if(soil_pem) then 271 CALL gr_dyn_fi(nsoilmx,iim_input+1,jjm_input+1,ngrid,TI_ave_dyn(:,:,:,islope),TI_ave(:,:,islope)) 272 DO l=1,nsoilmx 273 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tsoil_ave_dyn(:,:,l,islope),tsoil_ave(:,l,islope)) 274 DO t=1,timelen 275 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tsoil_gcm_dyn(:,:,l,islope,t),tsoil_gcm(:,l,islope,t)) 276 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,watersoil_density_dyn(:,:,l,islope,t),watersoil_density(:,l,islope,t)) 277 ENDDO 278 ENDDO 279 endif !soil_pem 280 DO t=1,timelen 281 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tsurf_GCM_dyn(:,:,islope,t),tsurf_GCM(:,islope,t)) 282 CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,co2_ice_slope_dyn(:,:,islope,t),co2_ice_slope(:,islope,t)) 283 ENDDO 284 ENDDO 285 286 CALL gr_dyn_fi(nslope,iim_input+1,jjm_input+1,ngrid,tsurf_ave_dyn,tsurf_ave) 240 287 241 288 CONTAINS
Note: See TracChangeset
for help on using the changeset viewer.