| Directory: | ./ |
|---|---|
| File: | phys/phyredem.f90 |
| Date: | 2022-01-11 19:19:34 |
| Exec | Total | Coverage | |
|---|---|---|---|
| Lines: | 145 | 165 | 87.9% |
| Branches: | 37 | 88 | 42.0% |
| Line | Branch | Exec | Source |
|---|---|---|---|
| 1 | ! | ||
| 2 | ! $Id: phyredem.F90 3956 2021-07-06 07:16:14Z jyg $ | ||
| 3 | ! | ||
| 4 | 17 | SUBROUTINE phyredem (fichnom) | |
| 5 | ! | ||
| 6 | !------------------------------------------------------------------------------- | ||
| 7 | ! Author: Z.X. Li (LMD/CNRS), 1993/08/18 | ||
| 8 | !------------------------------------------------------------------------------- | ||
| 9 | ! Purpose: Write restart state for physics. | ||
| 10 | !------------------------------------------------------------------------------- | ||
| 11 | USE dimphy, ONLY: klon, klev | ||
| 12 | USE fonte_neige_mod, ONLY : fonte_neige_final | ||
| 13 | USE pbl_surface_mod, ONLY : pbl_surface_final | ||
| 14 | USE phys_state_var_mod, ONLY: radpas, zmasq, pctsrf, & | ||
| 15 | ftsol, beta_aridity, delta_tsurf, falb_dir, & | ||
| 16 | falb_dif, qsol, fevap, radsol, solsw, sollw, & | ||
| 17 | sollwdown, rain_fall, snow_fall, z0m, z0h, & | ||
| 18 | agesno, zmea, zstd, zsig, zgam, zthe, zpic, & | ||
| 19 | zval, rugoro, t_ancien, q_ancien, & | ||
| 20 | prw_ancien, prlw_ancien, prsw_ancien, & | ||
| 21 | ql_ancien, qs_ancien, u_ancien, & | ||
| 22 | v_ancien, clwcon, rnebcon, ratqs, pbl_tke, & | ||
| 23 | wake_delta_pbl_tke, zmax0, f0, sig1, w01, & | ||
| 24 | wake_deltat, wake_deltaq, wake_s, wake_dens, & | ||
| 25 | awake_dens, cv_gen, & | ||
| 26 | wake_cstar, & | ||
| 27 | wake_pe, wake_fip, fm_therm, entr_therm, & | ||
| 28 | detr_therm, ale_bl, ale_bl_trig, alp_bl, & | ||
| 29 | ale_wake, ale_bl_stat, & | ||
| 30 | du_gwd_rando, du_gwd_front, u10m, v10m, & | ||
| 31 | treedrg, solswfdiff, delta_sal, ds_ns, dt_ns, & | ||
| 32 | delta_sst, ratqs_inter | ||
| 33 | |||
| 34 | USE geometry_mod, ONLY : longitude_deg, latitude_deg | ||
| 35 | USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var | ||
| 36 | USE traclmdz_mod, ONLY : traclmdz_to_restart | ||
| 37 | USE infotrac_phy, ONLY: type_trac, niadv, tname, nbtr, nqo | ||
| 38 | USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send | ||
| 39 | USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra | ||
| 40 | USE surface_data, ONLY: type_ocean, version_ocean | ||
| 41 | USE ocean_slab_mod, ONLY : nslay, tslab, seaice, tice, fsic | ||
| 42 | USE time_phylmdz_mod, ONLY: annee_ref, day_end, itau_phy, pdtphys | ||
| 43 | use config_ocean_skin_m, only: activate_ocean_skin | ||
| 44 | |||
| 45 | IMPLICIT none | ||
| 46 | |||
| 47 | include "dimsoil.h" | ||
| 48 | include "clesphys.h" | ||
| 49 | include "thermcell.h" | ||
| 50 | include "compbl.h" | ||
| 51 | !====================================================================== | ||
| 52 | CHARACTER*(*) fichnom | ||
| 53 | |||
| 54 | ! les variables globales ecrites dans le fichier restart | ||
| 55 | |||
| 56 | 2 | REAL tsoil(klon, nsoilmx, nbsrf) | |
| 57 | 2 | REAL qsurf(klon, nbsrf) | |
| 58 | 2 | REAL snow(klon, nbsrf) | |
| 59 | 2 | real fder(klon) | |
| 60 | 2 | REAL run_off_lic_0(klon) | |
| 61 | 2 | REAL trs(klon, nbtr) | |
| 62 | |||
| 63 | INTEGER nid, nvarid, idim1, idim2, idim3 | ||
| 64 | INTEGER ierr | ||
| 65 | INTEGER length | ||
| 66 | PARAMETER (length=100) | ||
| 67 | REAL tab_cntrl(length) | ||
| 68 | |||
| 69 | INTEGER isoil, nsrf,isw | ||
| 70 | CHARACTER (len=2) :: str2 | ||
| 71 | CHARACTER (len=256) :: nam, lnam | ||
| 72 | INTEGER :: it, iiq, pass | ||
| 73 | |||
| 74 | !====================================================================== | ||
| 75 | |||
| 76 | ! Get variables which will be written to restart file from module | ||
| 77 | ! pbl_surface_mod | ||
| 78 | 1 | CALL pbl_surface_final(fder, snow, qsurf, tsoil) | |
| 79 | |||
| 80 | ! Get a variable calculated in module fonte_neige_mod | ||
| 81 | 1 | CALL fonte_neige_final(run_off_lic_0) | |
| 82 | |||
| 83 | !====================================================================== | ||
| 84 | |||
| 85 | 1 | CALL open_restartphy(fichnom) | |
| 86 | |||
| 87 | |||
| 88 |
2/2✓ Branch 0 taken 100 times.
✓ Branch 1 taken 1 times.
|
101 | DO ierr = 1, length |
| 89 | 101 | tab_cntrl(ierr) = 0.0 | |
| 90 | ENDDO | ||
| 91 | 1 | tab_cntrl(1) = pdtphys | |
| 92 | 1 | tab_cntrl(2) = radpas | |
| 93 | ! co2_ppm : current value of atmospheric CO2 | ||
| 94 | 1 | tab_cntrl(3) = co2_ppm | |
| 95 | 1 | tab_cntrl(4) = solaire | |
| 96 | 1 | tab_cntrl(5) = iflag_con | |
| 97 | 1 | tab_cntrl(6) = nbapp_rad | |
| 98 | |||
| 99 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | IF( iflag_cycle_diurne.GE.1 ) tab_cntrl( 7 ) = iflag_cycle_diurne |
| 100 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | IF( soil_model ) tab_cntrl( 8 ) = 1. |
| 101 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | IF( new_oliq ) tab_cntrl( 9 ) = 1. |
| 102 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | IF( ok_orodr ) tab_cntrl(10 ) = 1. |
| 103 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | IF( ok_orolf ) tab_cntrl(11 ) = 1. |
| 104 | |||
| 105 | 1 | tab_cntrl(13) = day_end | |
| 106 | 1 | tab_cntrl(14) = annee_ref | |
| 107 | 1 | tab_cntrl(15) = itau_phy | |
| 108 | |||
| 109 | ! co2_ppm0 : initial value of atmospheric CO2 | ||
| 110 | 1 | tab_cntrl(16) = co2_ppm0 | |
| 111 | |||
| 112 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | DO pass=1,2 ! pass=1 netcdf definition ; pass=2 netcdf write |
| 113 | |||
| 114 | 2 | CALL put_var(pass, "controle", "Parametres de controle", tab_cntrl) | |
| 115 | |||
| 116 | CALL put_field(pass,"longitude", & | ||
| 117 | 2 | "Longitudes de la grille physique", longitude_deg) | |
| 118 | |||
| 119 | 2 | CALL put_field(pass,"latitude", "Latitudes de la grille physique", latitude_deg) | |
| 120 | |||
| 121 | ! PB ajout du masque terre/mer | ||
| 122 | |||
| 123 | 2 | CALL put_field(pass,"masque", "masque terre mer", zmasq) | |
| 124 | |||
| 125 | ! BP ajout des fraction de chaque sous-surface | ||
| 126 | |||
| 127 | ! Get last fractions from slab ocean | ||
| 128 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
2 | IF (type_ocean == 'slab' .AND. version_ocean == "sicINT") THEN |
| 129 | ✗ | WHERE (1.-zmasq(:).GT.EPSFRA) | |
| 130 | pctsrf(:,is_oce)=(1.-fsic(:))*(1.-zmasq(:)) | ||
| 131 | pctsrf(:,is_sic)=fsic(:)*(1.-zmasq(:)) | ||
| 132 | END WHERE | ||
| 133 | END IF | ||
| 134 | |||
| 135 | ! 1. fraction de terre | ||
| 136 | |||
| 137 | 2 | CALL put_field(pass,"FTER", "fraction de continent", pctsrf(:, is_ter)) | |
| 138 | |||
| 139 | ! 2. Fraction de glace de terre | ||
| 140 | |||
| 141 | 2 | CALL put_field(pass,"FLIC", "fraction glace de terre", pctsrf(:, is_lic)) | |
| 142 | |||
| 143 | ! 3. fraction ocean | ||
| 144 | |||
| 145 | 2 | CALL put_field(pass,"FOCE", "fraction ocean", pctsrf(:, is_oce)) | |
| 146 | |||
| 147 | ! 4. Fraction glace de mer | ||
| 148 | |||
| 149 | 2 | CALL put_field(pass,"FSIC", "fraction glace mer", pctsrf(:, is_sic)) | |
| 150 | |||
| 151 | IF(nbsrf>99) THEN | ||
| 152 | PRINT*, "Trop de sous-mailles"; CALL abort_physic("phyredem", "", 1) | ||
| 153 | END IF | ||
| 154 | IF(nsoilmx>99) THEN | ||
| 155 | PRINT*, "Trop de sous-surfaces"; CALL abort_physic("phyredem", "", 1) | ||
| 156 | END IF | ||
| 157 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
|
2 | IF(nsw>99) THEN |
| 158 | ✗ | PRINT*, "Trop de bandes"; CALL abort_physic("phyredem", "", 1) | |
| 159 | END IF | ||
| 160 | |||
| 161 | ! Surface variables | ||
| 162 | 2 | CALL put_field_srf1(pass,"TS","Temperature",ftsol(:,:)) | |
| 163 | |||
| 164 | !! CALL put_field_srf1(pass,"DELTA_TS","w-x surface temperature difference", delta_tsurf(:,:)) | ||
| 165 | 2 | CALL put_field_srf1(pass,"DELTATS","w-x surface temperature difference", delta_tsurf(:,:)) | |
| 166 | |||
| 167 | ! CALL put_field_srf1(pass,"BETA_S","Aridity factor", beta_aridity(:,:)) | ||
| 168 | 2 | CALL put_field_srf1(pass,"BETAS","Aridity factor", beta_aridity(:,:)) | |
| 169 | ! End surface variables | ||
| 170 | |||
| 171 | ! ================== Albedo ======================================= | ||
| 172 | 2 | print*,'PHYREDEM NOUVEAU' | |
| 173 | 2 | CALL put_field_srf2(pass,"A_dir_SW","Albedo direct",falb_dir(:,:,:)) | |
| 174 | 2 | CALL put_field_srf2(pass,"A_dif_SW","Albedo diffus",falb_dif(:,:,:)) | |
| 175 | |||
| 176 | 2 | CALL put_field_srf1(pass,"U10M", "u a 10m", u10m) | |
| 177 | |||
| 178 | 2 | CALL put_field_srf1(pass,"V10M", "v a 10m", v10m) | |
| 179 | |||
| 180 | |||
| 181 | ! ================== Tsoil ========================================= | ||
| 182 | 2 | CALL put_field_srf2(pass,"Tsoil","Temperature",tsoil(:,:,:)) | |
| 183 | !FC | ||
| 184 | ! CALL put_field_srf2("treedrg","freinage arbres",treedrg(:,:,:)) | ||
| 185 | 2 | CALL put_field(pass,"treedrg_ter","freinage arbres",treedrg(:,:,is_ter)) | |
| 186 | |||
| 187 | |||
| 188 | 2 | CALL put_field_srf1(pass,"QS" , "Humidite",qsurf(:,:)) | |
| 189 | |||
| 190 | 2 | CALL put_field (pass,"QSOL", "Eau dans le sol (mm)", qsol) | |
| 191 | |||
| 192 | 2 | CALL put_field_srf1(pass,"EVAP", "Evaporation", fevap(:,:)) | |
| 193 | |||
| 194 | 2 | CALL put_field_srf1(pass,"SNOW", "Neige", snow(:,:)) | |
| 195 | |||
| 196 | 2 | CALL put_field(pass,"RADS", "Rayonnement net a la surface", radsol) | |
| 197 | |||
| 198 | 2 | CALL put_field(pass,"solsw", "Rayonnement solaire a la surface", solsw) | |
| 199 | |||
| 200 | 2 | CALL put_field(pass,"solswfdiff", "Fraction du rayonnement solaire a la surface qui est diffus", solswfdiff) | |
| 201 | |||
| 202 | 2 | CALL put_field(pass,"sollw", "Rayonnement IF a la surface", sollw) | |
| 203 | |||
| 204 | 2 | CALL put_field(pass,"sollwdown", "Rayonnement down IF a la surface", sollwdown) | |
| 205 | |||
| 206 | 2 | CALL put_field(pass,"fder", "Derive de flux", fder) | |
| 207 | |||
| 208 | 2 | CALL put_field(pass,"rain_f", "precipitation liquide", rain_fall) | |
| 209 | |||
| 210 | 2 | CALL put_field(pass,"snow_f", "precipitation solide", snow_fall) | |
| 211 | |||
| 212 | 2 | CALL put_field_srf1(pass,"Z0m", "rugosite", z0m(:,:)) | |
| 213 | |||
| 214 | 2 | CALL put_field_srf1(pass,"Z0h", "rugosite", z0h(:,:)) | |
| 215 | |||
| 216 | 2 | CALL put_field_srf1(pass,"AGESNO", "Age de la neige", agesno(:,:)) | |
| 217 | |||
| 218 | 2 | CALL put_field(pass,"ZMEA", "ZMEA", zmea) | |
| 219 | |||
| 220 | 2 | CALL put_field(pass,"ZSTD", "ZSTD", zstd) | |
| 221 | |||
| 222 | 2 | CALL put_field(pass,"ZSIG", "ZSIG", zsig) | |
| 223 | |||
| 224 | 2 | CALL put_field(pass,"ZGAM", "ZGAM", zgam) | |
| 225 | |||
| 226 | 2 | CALL put_field(pass,"ZTHE", "ZTHE", zthe) | |
| 227 | |||
| 228 | 2 | CALL put_field(pass,"ZPIC", "ZPIC", zpic) | |
| 229 | |||
| 230 | 2 | CALL put_field(pass,"ZVAL", "ZVAL", zval) | |
| 231 | |||
| 232 | 2 | CALL put_field(pass,"RUGSREL", "RUGSREL", rugoro) | |
| 233 | |||
| 234 | 2 | CALL put_field(pass,"TANCIEN", "TANCIEN", t_ancien) | |
| 235 | |||
| 236 | 2 | CALL put_field(pass,"QANCIEN", "QANCIEN", q_ancien) | |
| 237 | |||
| 238 | 2 | CALL put_field(pass,"QLANCIEN", "QLANCIEN", ql_ancien) | |
| 239 | |||
| 240 | 2 | CALL put_field(pass,"QSANCIEN", "QSANCIEN", qs_ancien) | |
| 241 | |||
| 242 | 2 | CALL put_field(pass,"PRWANCIEN", "PRWANCIEN", prw_ancien) | |
| 243 | |||
| 244 | 2 | CALL put_field(pass,"PRLWANCIEN", "PRLWANCIEN", prlw_ancien) | |
| 245 | |||
| 246 | 2 | CALL put_field(pass,"PRSWANCIEN", "PRSWANCIEN", prsw_ancien) | |
| 247 | |||
| 248 | 2 | CALL put_field(pass,"UANCIEN", "UANCIEN", u_ancien) | |
| 249 | |||
| 250 | 2 | CALL put_field(pass,"VANCIEN", "VANCIEN", v_ancien) | |
| 251 | |||
| 252 | 2 | CALL put_field(pass,"CLWCON", "Eau liquide convective", clwcon) | |
| 253 | |||
| 254 | 2 | CALL put_field(pass,"RNEBCON", "Nebulosite convective", rnebcon) | |
| 255 | |||
| 256 | 2 | CALL put_field(pass,"RATQS", "Ratqs", ratqs) | |
| 257 | |||
| 258 | ! run_off_lic_0 | ||
| 259 | |||
| 260 | 2 | CALL put_field(pass,"RUNOFFLIC0", "Runofflic0", run_off_lic_0) | |
| 261 | |||
| 262 | ! DEB TKE PBL ! | ||
| 263 | |||
| 264 |
1/2✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
|
2 | IF (iflag_pbl>1) then |
| 265 | CALL put_field_srf3(pass,"TKE", "Energ. Cineti. Turb.", & | ||
| 266 | 2 | pbl_tke(:,:,:)) | |
| 267 | CALL put_field_srf3(pass,"DELTATKE", "Del TKE wk/env.", & | ||
| 268 | 2 | wake_delta_pbl_tke(:,:,:)) | |
| 269 | END IF | ||
| 270 | |||
| 271 | ! FIN TKE PBL ! | ||
| 272 | !IM ajout zmax0, f0, sig1, w01 | ||
| 273 | !IM wake_deltat, wake_deltaq, wake_s, wake_cstar, wake_pe, wake_fip | ||
| 274 | |||
| 275 | 2 | CALL put_field(pass,"ZMAX0", "ZMAX0", zmax0) | |
| 276 | |||
| 277 | 2 | CALL put_field(pass,"F0", "F0", f0) | |
| 278 | |||
| 279 | 2 | CALL put_field(pass,"sig1", "sig1 Emanuel", sig1) | |
| 280 | |||
| 281 | 2 | CALL put_field(pass,"w01", "w01 Emanuel", w01) | |
| 282 | |||
| 283 | ! wake_deltat | ||
| 284 | 2 | CALL put_field(pass,"WAKE_DELTAT", "WAKE_DELTAT", wake_deltat) | |
| 285 | |||
| 286 | 2 | CALL put_field(pass,"WAKE_DELTAQ", "WAKE_DELTAQ", wake_deltaq) | |
| 287 | |||
| 288 | 2 | CALL put_field(pass,"WAKE_S", "Wake frac. area", wake_s) | |
| 289 | |||
| 290 | 2 | CALL put_field(pass,"WAKE_DENS", "Wake num. /unit area", wake_dens) | |
| 291 | |||
| 292 | 2 | CALL put_field(pass,"AWAKE_DENS", "Active Wake num. /unit area", awake_dens) | |
| 293 | |||
| 294 | 2 | CALL put_field(pass,"CV_GEN", "CB birth rate", cv_gen) | |
| 295 | |||
| 296 | 2 | CALL put_field(pass,"WAKE_CSTAR", "WAKE_CSTAR", wake_cstar) | |
| 297 | |||
| 298 | 2 | CALL put_field(pass,"WAKE_PE", "WAKE_PE", wake_pe) | |
| 299 | |||
| 300 | 2 | CALL put_field(pass,"WAKE_FIP", "WAKE_FIP", wake_fip) | |
| 301 | |||
| 302 | ! thermiques | ||
| 303 | |||
| 304 | 2 | CALL put_field(pass,"FM_THERM", "FM_THERM", fm_therm) | |
| 305 | |||
| 306 | 2 | CALL put_field(pass,"ENTR_THERM", "ENTR_THERM", entr_therm) | |
| 307 | |||
| 308 | 2 | CALL put_field(pass,"DETR_THERM", "DETR_THERM", detr_therm) | |
| 309 | |||
| 310 | 2 | CALL put_field(pass,"ALE_BL", "ALE_BL", ale_bl) | |
| 311 | |||
| 312 | 2 | CALL put_field(pass,"ALE_BL_TRIG", "ALE_BL_TRIG", ale_bl_trig) | |
| 313 | |||
| 314 | 2 | CALL put_field(pass,"ALP_BL", "ALP_BL", alp_bl) | |
| 315 | |||
| 316 | 2 | CALL put_field(pass,"ALE_WAKE", "ALE_WAKE", ale_wake) | |
| 317 | |||
| 318 | 2 | CALL put_field(pass,"ALE_BL_STAT", "ALE_BL_STAT", ale_bl_stat) | |
| 319 | |||
| 320 | |||
| 321 | ! fisrtilp/clouds | ||
| 322 | 2 | CALL put_field(pass,"RATQS_INTER","Relative width of the lsc sugrid scale water",ratqs_inter) | |
| 323 | |||
| 324 | |||
| 325 | ! trs from traclmdz_mod | ||
| 326 |
1/2✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
|
2 | IF (type_trac == 'lmdz') THEN |
| 327 | 2 | CALL traclmdz_to_restart(trs) | |
| 328 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 2 times.
|
6 | DO it=1, nbtr |
| 329 | !! iiq=niadv(it+2) ! jyg | ||
| 330 | 4 | iiq=niadv(it+nqo) ! jyg | |
| 331 | 6 | CALL put_field(pass,"trs_"//tname(iiq), "", trs(:, it)) | |
| 332 | END DO | ||
| 333 | END IF | ||
| 334 | |||
| 335 |
2/4✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
|
2 | IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN |
| 336 | ✗ | IF (carbon_cycle_cpl) THEN | |
| 337 | ✗ | IF (.NOT. ALLOCATED(co2_send)) THEN | |
| 338 | ! This is the case of create_etat0_limit, ce0l | ||
| 339 | ✗ | ALLOCATE(co2_send(klon)) | |
| 340 | ✗ | co2_send(:) = co2_ppm0 | |
| 341 | END IF | ||
| 342 | ✗ | CALL put_field(pass,"co2_send", "co2_ppm for coupling", co2_send) | |
| 343 | END IF | ||
| 344 | END IF | ||
| 345 | |||
| 346 | ! Restart variables for Slab ocean | ||
| 347 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
|
2 | IF (type_ocean == 'slab') THEN |
| 348 | ✗ | IF (nslay.EQ.1) THEN | |
| 349 | ✗ | CALL put_field(pass,"tslab", "Slab ocean temperature", tslab) | |
| 350 | ELSE | ||
| 351 | ✗ | DO it=1,nslay | |
| 352 | ✗ | WRITE(str2,'(i2.2)') it | |
| 353 | ✗ | CALL put_field(pass,"tslab"//str2, "Slab ocean temperature", tslab(:,it)) | |
| 354 | END DO | ||
| 355 | END IF | ||
| 356 | ✗ | IF (version_ocean == 'sicINT') THEN | |
| 357 | ✗ | CALL put_field(pass,"seaice", "Slab seaice (kg/m2)", seaice) | |
| 358 | ✗ | CALL put_field(pass,"slab_tice", "Slab sea ice temperature", tice) | |
| 359 | END IF | ||
| 360 | END IF | ||
| 361 | |||
| 362 |
1/2✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
|
2 | if (ok_gwd_rando) call put_field(pass,"du_gwd_rando", & |
| 363 | 2 | "tendency on zonal wind due to flott gravity waves", du_gwd_rando) | |
| 364 | |||
| 365 |
2/4✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
|
2 | IF (.not. ok_hines .and. ok_gwd_rando) call put_field(pass,"du_gwd_front", & |
| 366 | 2 | "tendency on zonal wind due to acama gravity waves", du_gwd_front) | |
| 367 | |||
| 368 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
|
2 | if (activate_ocean_skin >= 1) then |
| 369 | ✗ | if (activate_ocean_skin == 2 .and. type_ocean == 'couple') then | |
| 370 | CALL put_field(pass, "delta_sal", & | ||
| 371 | ✗ | "ocean-air interface salinity minus bulk salinity", delta_sal) | |
| 372 | CALL put_field(pass, "delta_SST", & | ||
| 373 | ✗ | "ocean-air interface temperature minus bulk SST", delta_sst) | |
| 374 | end if | ||
| 375 | |||
| 376 | ✗ | CALL put_field(pass, "dS_ns", "delta salinity near surface", ds_ns) | |
| 377 | ✗ | CALL put_field(pass, "dT_ns", "delta temperature near surface", dT_ns) | |
| 378 | end if | ||
| 379 | |||
| 380 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | IF (pass==1) CALL enddef_restartphy |
| 381 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
3 | IF (pass==2) CALL close_restartphy |
| 382 | ENDDO | ||
| 383 | |||
| 384 | !$OMP BARRIER | ||
| 385 | |||
| 386 | |||
| 387 | CONTAINS | ||
| 388 | |||
| 389 | |||
| 390 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 22 times.
|
22 | SUBROUTINE put_field_srf1(pass,nam,lnam,field) |
| 391 | |||
| 392 | IMPLICIT NONE | ||
| 393 | INTEGER, INTENT(IN) :: pass | ||
| 394 | CHARACTER(LEN=*), INTENT(IN) :: nam, lnam | ||
| 395 | REAL, INTENT(IN) :: field(:,:) | ||
| 396 | CHARACTER(LEN=256) :: nm, lm, str | ||
| 397 |
2/2✓ Branch 0 taken 92 times.
✓ Branch 1 taken 22 times.
|
114 | DO nsrf = 1, SIZE(field,2) |
| 398 | 92 | WRITE(str, '(i2.2)') nsrf | |
| 399 | 92 | nm=TRIM(nam)//TRIM(str) | |
| 400 | 92 | lm=TRIM(lnam)//" de surface No. "//TRIM(str) | |
| 401 | 114 | CALL put_field(pass,nm,lm,field(:,nsrf)) | |
| 402 | END DO | ||
| 403 | |||
| 404 | 22 | END SUBROUTINE put_field_srf1 | |
| 405 | |||
| 406 | |||
| 407 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
|
6 | SUBROUTINE put_field_srf2(pass,nam,lnam,field) |
| 408 | |||
| 409 | IMPLICIT NONE | ||
| 410 | INTEGER, INTENT(IN) :: pass | ||
| 411 | CHARACTER(LEN=*), INTENT(IN) :: nam, lnam | ||
| 412 | REAL, INTENT(IN) :: field(:,:,:) | ||
| 413 | CHARACTER(LEN=256) :: nm, lm, str | ||
| 414 |
2/2✓ Branch 0 taken 24 times.
✓ Branch 1 taken 6 times.
|
30 | DO nsrf = 1, SIZE(field,3) |
| 415 |
2/2✓ Branch 0 taken 184 times.
✓ Branch 1 taken 24 times.
|
214 | DO isoil=1, SIZE(field,2) |
| 416 | 184 | WRITE(str, '(i2.2,"srf",i2.2)')isoil,nsrf | |
| 417 | ! WRITE(lunout,*)"PHYREDEM ",TRIM(nam)//TRIM(str) | ||
| 418 | 184 | nm=TRIM(nam)//TRIM(str) | |
| 419 | 184 | lm=TRIM(lnam)//" du sol No. "//TRIM(str) | |
| 420 | 208 | CALL put_field(pass,nm,lm,field(:,isoil,nsrf)) | |
| 421 | END DO | ||
| 422 | END DO | ||
| 423 | |||
| 424 | 6 | END SUBROUTINE put_field_srf2 | |
| 425 | |||
| 426 | |||
| 427 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | SUBROUTINE put_field_srf3(pass,nam,lnam,field) |
| 428 | |||
| 429 | IMPLICIT NONE | ||
| 430 | INTEGER, INTENT(IN) :: pass | ||
| 431 | CHARACTER(LEN=*), INTENT(IN) :: nam, lnam | ||
| 432 | REAL, INTENT(IN) :: field(:,:,:) | ||
| 433 | CHARACTER(LEN=256) :: nm, lm, str | ||
| 434 |
2/2✓ Branch 0 taken 20 times.
✓ Branch 1 taken 4 times.
|
24 | DO nsrf = 1, SIZE(field,3) |
| 435 | 20 | WRITE(str, '(i2.2)') nsrf | |
| 436 | 20 | nm=TRIM(nam)//TRIM(str) | |
| 437 | 20 | lm=TRIM(lnam)//TRIM(str) | |
| 438 | 24 | CALL put_field(pass,nm,lm,field(:,1:klev+1,nsrf)) | |
| 439 | END DO | ||
| 440 | |||
| 441 | 4 | END SUBROUTINE put_field_srf3 | |
| 442 | |||
| 443 | |||
| 444 | END SUBROUTINE phyredem | ||
| 445 |