| Directory: | ./ | 
|---|---|
| File: | phys/limit_read_mod.f90 | 
| Date: | 2022-01-11 19:19:34 | 
| Exec | Total | Coverage | |
|---|---|---|---|
| Lines: | 107 | 115 | 93.0% | 
| Branches: | 75 | 138 | 54.3% | 
| Line | Branch | Exec | Source | 
|---|---|---|---|
| 1 | ! | ||
| 2 | ! $Id: limit_read_mod.F90 3435 2019-01-22 15:21:59Z fairhead $ | ||
| 3 | ! | ||
| 4 | MODULE limit_read_mod | ||
| 5 | ! | ||
| 6 | ! This module reads the fichier "limit.nc" containing fields for surface forcing. | ||
| 7 | ! | ||
| 8 | ! Module subroutines : | ||
| 9 | ! limit_read_frac : call limit_read_tot and return the fractions | ||
| 10 | ! limit_read_rug_alb : return rugosity and albedo, if coupled ocean call limit_read_tot first | ||
| 11 | ! limit_read_sst : return sea ice temperature | ||
| 12 | ! limit_read_tot : read limit.nc and store the fields in local modules variables | ||
| 13 | ! | ||
| 14 | IMPLICIT NONE | ||
| 15 | |||
| 16 | REAL, ALLOCATABLE, DIMENSION(:,:), SAVE, PRIVATE :: pctsrf | ||
| 17 | !$OMP THREADPRIVATE(pctsrf) | ||
| 18 | REAL, ALLOCATABLE, DIMENSION(:), SAVE, PRIVATE :: rugos | ||
| 19 | !$OMP THREADPRIVATE(rugos) | ||
| 20 | REAL, ALLOCATABLE, DIMENSION(:), SAVE, PRIVATE :: albedo | ||
| 21 | !$OMP THREADPRIVATE(albedo) | ||
| 22 | REAL, ALLOCATABLE, DIMENSION(:), SAVE, PRIVATE :: sst | ||
| 23 | !$OMP THREADPRIVATE(sst) | ||
| 24 | LOGICAL,SAVE :: read_continents=.FALSE. | ||
| 25 | !$OMP THREADPRIVATE(read_continents) | ||
| 26 | |||
| 27 | CONTAINS | ||
| 28 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | ||
| 29 | !! | ||
| 30 | !! Public subroutines : | ||
| 31 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | ||
| 32 | |||
| 33 | |||
| 34 | 1 | SUBROUTINE init_limit_read(first_day) | |
| 35 | USE mod_grid_phy_lmdz | ||
| 36 | USE surface_data | ||
| 37 | USE mod_phys_lmdz_para | ||
| 38 | IMPLICIT NONE | ||
| 39 | INTEGER, INTENT(IN) :: first_day | ||
| 40 | |||
| 41 | |||
| 42 | IF ( type_ocean /= 'couple') THEN | ||
| 43 | IF (grid_type==unstructured) THEN | ||
| 44 | ENDIF | ||
| 45 | ENDIF | ||
| 46 | |||
| 47 | 1 | END SUBROUTINE init_limit_read | |
| 48 | |||
| 49 | 480 | SUBROUTINE limit_read_frac(itime, dtime, jour, pctsrf_new, is_modified) | |
| 50 | ! | ||
| 51 | ! This subroutine is called from "change_srf_frac" for case of | ||
| 52 | ! ocean=force or from ocean_slab_frac for ocean=slab. | ||
| 53 | ! The fraction for all sub-surfaces at actual time step is returned. | ||
| 54 | |||
| 55 | USE dimphy | ||
| 56 | USE indice_sol_mod | ||
| 57 | |||
| 58 | ! Input arguments | ||
| 59 | !**************************************************************************************** | ||
| 60 | INTEGER, INTENT(IN) :: itime ! time step | ||
| 61 | INTEGER, INTENT(IN) :: jour ! current day | ||
| 62 | REAL , INTENT(IN) :: dtime ! length of time step | ||
| 63 | |||
| 64 | ! Output arguments | ||
| 65 | !**************************************************************************************** | ||
| 66 | REAL, DIMENSION(klon,nbsrf), INTENT(OUT) :: pctsrf_new ! sub surface fractions | ||
| 67 | LOGICAL, INTENT(OUT) :: is_modified ! true if pctsrf is modified at this time step | ||
| 68 | |||
| 69 | ! End declaration | ||
| 70 | !**************************************************************************************** | ||
| 71 | |||
| 72 | ! 1) Read file limit.nc | ||
| 73 | 480 | CALL limit_read_tot(itime, dtime, jour, is_modified) | |
| 74 | |||
| 75 | ! 2) Return the fraction read in limit_read_tot | ||
| 76 | 4/4✓ Branch 0 taken 1920 times. ✓ Branch 1 taken 480 times. ✓ Branch 2 taken 1908480 times. ✓ Branch 3 taken 1920 times. | 1910880 | pctsrf_new(:,:) = pctsrf(:,:) | 
| 77 | |||
| 78 | 480 | END SUBROUTINE limit_read_frac | |
| 79 | |||
| 80 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | ||
| 81 | |||
| 82 | 480 | SUBROUTINE limit_read_rug_alb(itime, dtime, jour, & | |
| 83 | knon, knindex, & | ||
| 84 | rugos_out, alb_out) | ||
| 85 | ! | ||
| 86 | ! This subroutine is called from surf_land_bucket. | ||
| 87 | ! The flag "ok_veget" must can not be true. If coupled run, "ocean=couple" | ||
| 88 | ! then this routine will call limit_read_tot. | ||
| 89 | ! | ||
| 90 | USE dimphy | ||
| 91 | USE surface_data | ||
| 92 | |||
| 93 | ! Input arguments | ||
| 94 | !**************************************************************************************** | ||
| 95 | INTEGER, INTENT(IN) :: itime ! numero du pas de temps courant | ||
| 96 | INTEGER, INTENT(IN) :: jour ! jour a lire dans l'annee | ||
| 97 | REAL , INTENT(IN) :: dtime ! pas de temps de la physique (en s) | ||
| 98 | INTEGER, INTENT(IN) :: knon ! nomber of points on compressed grid | ||
| 99 | INTEGER, DIMENSION(klon), INTENT(IN) :: knindex ! grid point number for compressed grid | ||
| 100 | ! Output arguments | ||
| 101 | !**************************************************************************************** | ||
| 102 | REAL, DIMENSION(klon), INTENT(OUT) :: rugos_out | ||
| 103 | REAL, DIMENSION(klon), INTENT(OUT) :: alb_out | ||
| 104 | |||
| 105 | ! Local variables | ||
| 106 | !**************************************************************************************** | ||
| 107 | INTEGER :: i | ||
| 108 | LOGICAL :: is_modified | ||
| 109 | !**************************************************************************************** | ||
| 110 | |||
| 111 | 2/6✓ Branch 0 taken 480 times. ✗ Branch 1 not taken. ✗ Branch 2 not taken. ✓ Branch 3 taken 480 times. ✗ Branch 4 not taken. ✗ Branch 5 not taken. | 480 | IF (type_ocean == 'couple'.OR. & | 
| 112 | (type_ocean == 'slab' .AND. version_ocean == 'sicINT')) THEN | ||
| 113 | ! limit.nc has not yet been read. Do it now! | ||
| 114 | ✗ | CALL limit_read_tot(itime, dtime, jour, is_modified) | |
| 115 | END IF | ||
| 116 | |||
| 117 | 2/2✓ Branch 0 taken 247680 times. ✓ Branch 1 taken 480 times. | 248160 | DO i=1,knon | 
| 118 | 247680 | rugos_out(i) = rugos(knindex(i)) | |
| 119 | 248160 | alb_out(i) = albedo(knindex(i)) | |
| 120 | END DO | ||
| 121 | |||
| 122 | 480 | END SUBROUTINE limit_read_rug_alb | |
| 123 | |||
| 124 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | ||
| 125 | |||
| 126 | 480 | SUBROUTINE limit_read_sst(knon, knindex, sst_out) | |
| 127 | ! | ||
| 128 | ! This subroutine returns the sea surface temperature already read from limit.nc. | ||
| 129 | ! | ||
| 130 | USE dimphy, ONLY : klon | ||
| 131 | |||
| 132 | INTEGER, INTENT(IN) :: knon ! nomber of points on compressed grid | ||
| 133 | INTEGER, DIMENSION(klon), INTENT(IN) :: knindex ! grid point number for compressed grid | ||
| 134 | REAL, DIMENSION(klon), INTENT(OUT) :: sst_out | ||
| 135 | |||
| 136 | INTEGER :: i | ||
| 137 | |||
| 138 | 2/2✓ Branch 0 taken 362977 times. ✓ Branch 1 taken 480 times. | 363457 | DO i = 1, knon | 
| 139 | 363457 | sst_out(i) = sst(knindex(i)) | |
| 140 | END DO | ||
| 141 | |||
| 142 | 480 | END SUBROUTINE limit_read_sst | |
| 143 | |||
| 144 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | ||
| 145 | !! | ||
| 146 | !! Private subroutine : | ||
| 147 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! | ||
| 148 | |||
| 149 | 480 | SUBROUTINE limit_read_tot(itime, dtime, jour, is_modified) | |
| 150 | ! | ||
| 151 | ! Read everything needed from limit.nc | ||
| 152 | ! | ||
| 153 | ! 0) Initialize | ||
| 154 | ! 1) Open the file limit.nc, if it is time | ||
| 155 | ! 2) Read fraction, if not type_ocean=couple | ||
| 156 | ! 3) Read sea surface temperature, if not type_ocean=couple | ||
| 157 | ! 4) Read albedo and rugosity for land surface, only in case of no vegetation model | ||
| 158 | ! 5) Close file and distribuate variables to all processus | ||
| 159 | |||
| 160 | USE dimphy | ||
| 161 | USE mod_grid_phy_lmdz | ||
| 162 | USE mod_phys_lmdz_para | ||
| 163 | USE surface_data, ONLY : type_ocean, ok_veget | ||
| 164 | USE netcdf | ||
| 165 | USE indice_sol_mod | ||
| 166 | USE phys_cal_mod, ONLY : calend, year_len | ||
| 167 | USE print_control_mod, ONLY: lunout, prt_level | ||
| 168 | |||
| 169 | IMPLICIT NONE | ||
| 170 | |||
| 171 | ! In- and ouput arguments | ||
| 172 | !**************************************************************************************** | ||
| 173 | INTEGER, INTENT(IN) :: itime ! numero du pas de temps courant | ||
| 174 | INTEGER, INTENT(IN) :: jour ! jour a lire dans l'annee | ||
| 175 | REAL , INTENT(IN) :: dtime ! pas de temps de la physique (en s) | ||
| 176 | |||
| 177 | LOGICAL, INTENT(OUT) :: is_modified ! true if pctsrf is modified at this time step | ||
| 178 | |||
| 179 | ! Locals variables with attribute SAVE | ||
| 180 | !**************************************************************************************** | ||
| 181 | ! frequence de lecture des conditions limites (en pas de physique) | ||
| 182 | INTEGER,SAVE :: lmt_pas | ||
| 183 | !$OMP THREADPRIVATE(lmt_pas) | ||
| 184 | LOGICAL, SAVE :: first_call=.TRUE. | ||
| 185 | !$OMP THREADPRIVATE(first_call) | ||
| 186 | INTEGER, SAVE :: jour_lu = -1 | ||
| 187 | !$OMP THREADPRIVATE(jour_lu) | ||
| 188 | ! Locals variables | ||
| 189 | !**************************************************************************************** | ||
| 190 | INTEGER :: nid, nvarid, ndimid, nn | ||
| 191 | INTEGER :: ii, ierr | ||
| 192 | INTEGER, DIMENSION(2) :: start, epais | ||
| 193 | 960 | REAL, DIMENSION(klon_glo,nbsrf) :: pct_glo ! fraction at global grid | |
| 194 | 960 | REAL, DIMENSION(klon_glo) :: sst_glo ! sea-surface temperature at global grid | |
| 195 | 960 | REAL, DIMENSION(klon_glo) :: rug_glo ! rugosity at global grid | |
| 196 | 960 | REAL, DIMENSION(klon_glo) :: alb_glo ! albedo at global grid | |
| 197 | |||
| 198 | REAL, DIMENSION(klon_mpi,nbsrf) :: pct_mpi ! fraction at global grid | ||
| 199 | REAL, DIMENSION(klon_mpi) :: sst_mpi ! sea-surface temperature at global grid | ||
| 200 | REAL, DIMENSION(klon_mpi) :: rug_mpi ! rugosity at global grid | ||
| 201 | REAL, DIMENSION(klon_mpi) :: alb_mpi ! albedo at global grid | ||
| 202 | |||
| 203 | CHARACTER(len=20) :: modname='limit_read_mod' | ||
| 204 | CHARACTER(LEN=99) :: abort_message, calendar, str | ||
| 205 | |||
| 206 | ! End declaration | ||
| 207 | !**************************************************************************************** | ||
| 208 | |||
| 209 | !**************************************************************************************** | ||
| 210 | ! 0) Initialization | ||
| 211 | ! | ||
| 212 | !**************************************************************************************** | ||
| 213 | 2/2✓ Branch 0 taken 1 times. ✓ Branch 1 taken 479 times. | 480 | IF (first_call) THEN | 
| 214 | 1 | first_call=.FALSE. | |
| 215 | ! calculate number of time steps for one day | ||
| 216 | 1 | lmt_pas = NINT(86400./dtime * 1.0) | |
| 217 | |||
| 218 | ! Allocate module save variables | ||
| 219 | 1/2✓ Branch 0 taken 1 times. ✗ Branch 1 not taken. | 1 | IF ( type_ocean /= 'couple' ) THEN | 
| 220 | 9/18✓ Branch 0 taken 1 times. ✗ Branch 1 not taken. ✓ Branch 2 taken 1 times. ✗ Branch 3 not taken. ✗ Branch 4 not taken. ✓ Branch 5 taken 1 times. ✓ Branch 6 taken 1 times. ✗ Branch 7 not taken. ✓ Branch 8 taken 1 times. ✗ Branch 9 not taken. ✓ Branch 10 taken 1 times. ✗ Branch 11 not taken. ✓ Branch 12 taken 1 times. ✗ Branch 13 not taken. ✗ Branch 14 not taken. ✓ Branch 15 taken 1 times. ✓ Branch 16 taken 1 times. ✗ Branch 17 not taken. | 1 | ALLOCATE(pctsrf(klon,nbsrf), sst(klon), stat=ierr) | 
| 221 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating pctsrf and sst',1) | 
| 222 | END IF | ||
| 223 | |||
| 224 | 1/2✓ Branch 0 taken 1 times. ✗ Branch 1 not taken. | 1 | IF ( .NOT. ok_veget ) THEN | 
| 225 | 8/16✓ Branch 0 taken 1 times. ✗ Branch 1 not taken. ✓ Branch 2 taken 1 times. ✗ Branch 3 not taken. ✗ Branch 4 not taken. ✓ Branch 5 taken 1 times. ✓ Branch 6 taken 1 times. ✗ Branch 7 not taken. ✓ Branch 8 taken 1 times. ✗ Branch 9 not taken. ✓ Branch 10 taken 1 times. ✗ Branch 11 not taken. ✗ Branch 12 not taken. ✓ Branch 13 taken 1 times. ✓ Branch 14 taken 1 times. ✗ Branch 15 not taken. | 1 | ALLOCATE(rugos(klon), albedo(klon), stat=ierr) | 
| 226 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating rugos and albedo',1) | 
| 227 | END IF | ||
| 228 | |||
| 229 | !$OMP MASTER ! Only master thread | ||
| 230 | 1/2✓ Branch 0 taken 1 times. ✗ Branch 1 not taken. | 1 | IF (is_mpi_root) THEN ! Only master processus | 
| 231 | 1 | ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid) | |
| 232 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,& | 
| 233 | ✗ | 'Pb d''ouverture du fichier de conditions aux limites',1) | |
| 234 | |||
| 235 | !--- WARNING IF CALENDAR IS KNOWN AND DOES NOT MATCH THE ONE OF LMDZ | ||
| 236 | 1 | ierr=NF90_INQ_VARID(nid, 'TEMPS', nvarid) | |
| 237 | 1 | ierr=NF90_GET_ATT(nid, nvarid, 'calendar', calendar) | |
| 238 | 1/6✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. ✗ Branch 2 not taken. ✗ Branch 3 not taken. ✗ Branch 4 not taken. ✗ Branch 5 not taken. | 1 | IF(ierr==NF90_NOERR.AND.calendar/=calend.AND.prt_level>=1) THEN | 
| 239 | ✗ | WRITE(lunout,*)'BEWARE: gcm and limit.nc calendars differ: ' | |
| 240 | ✗ | WRITE(lunout,*)' '//TRIM(calend)//' for gcm' | |
| 241 | ✗ | WRITE(lunout,*)' '//TRIM(calendar)//' for limit.nc file' | |
| 242 | END IF | ||
| 243 | |||
| 244 | !--- ERROR IF FILE RECORDS NUMBER IS NOT EQUAL TO EXPECTED NUMBER OF DAYS | ||
| 245 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (grid_type==unstructured) THEN | 
| 246 | ✗ | ierr=NF90_INQ_DIMID(nid,"time_year",ndimid) | |
| 247 | ELSE | ||
| 248 | 1 | ierr=NF90_INQUIRE(nid, UnlimitedDimID=ndimid) | |
| 249 | ENDIF | ||
| 250 | 1 | ierr=NF90_INQUIRE_DIMENSION(nid, ndimid, len=nn) | |
| 251 | 1 | WRITE(abort_message,'(a,2(i0,a))')'limit.nc records number (',nn,') does no'//& | |
| 252 | 2 | 't match year length (',year_len,')' | |
| 253 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF(nn/=year_len) CALL abort_physic(modname,abort_message,1) | 
| 254 | |||
| 255 | !--- ERROR IF FILES AND LMDZ HORIZONTAL RESOLUTIONS DO NOT MATCH | ||
| 256 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (grid_type==unstructured) THEN | 
| 257 | ✗ | ierr=NF90_INQ_DIMID(nid, 'cell', ndimid) | |
| 258 | ELSE | ||
| 259 | 1 | ierr=NF90_INQ_DIMID(nid, 'points_physiques', ndimid) | |
| 260 | ENDIF | ||
| 261 | 1 | ierr=NF90_INQUIRE_DIMENSION(nid, ndimid, len=nn) | |
| 262 | 1 | WRITE(abort_message,'(a,2(i0,a))')'limit.nc horizontal number of cells (',nn, & | |
| 263 | 2 | ') does not match LMDZ klon_glo (',klon_glo,')' | |
| 264 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF(nn/=klon_glo) CALL abort_physic(modname,abort_message,1) | 
| 265 | |||
| 266 | 1 | ierr = NF90_CLOSE(nid) | |
| 267 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1) | 
| 268 | END IF ! is_mpi_root | ||
| 269 | !$OMP END MASTER | ||
| 270 | !$OMP BARRIER | ||
| 271 | END IF | ||
| 272 | |||
| 273 | !**************************************************************************************** | ||
| 274 | ! 1) Open the file limit.nc if it is the right moment to read, once a day. | ||
| 275 | ! The file is read only by the master thread of the master mpi process(is_mpi_root) | ||
| 276 | ! Check by the way if the number of records is correct. | ||
| 277 | ! | ||
| 278 | !**************************************************************************************** | ||
| 279 | |||
| 280 | 480 | is_modified = .FALSE. | |
| 281 | !ym IF (MOD(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour ) THEN ! time to read | ||
| 282 | ! not REALLY PERIODIC | ||
| 283 | 5/6✓ Branch 0 taken 475 times. ✓ Branch 1 taken 5 times. ✓ Branch 2 taken 5 times. ✓ Branch 3 taken 470 times. ✓ Branch 4 taken 5 times. ✗ Branch 5 not taken. | 480 | IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read | 
| 284 | ! IF (MOD(itime-1, lmt_pas) == 0) THEN ! time to read | ||
| 285 | 10 | jour_lu = jour | |
| 286 | 10 | is_modified = .TRUE. | |
| 287 | |||
| 288 | 1/2✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. | 10 | IF (grid_type==unstructured) THEN | 
| 289 | |||
| 290 | |||
| 291 | |||
| 292 | ELSE ! grid_type==regular | ||
| 293 | |||
| 294 | !$OMP MASTER ! Only master thread | ||
| 295 | 1/2✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. | 10 | IF (is_mpi_root) THEN ! Only master processus! | 
| 296 | |||
| 297 | 10 | ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid) | |
| 298 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,& | 
| 299 | ✗ | 'Pb d''ouverture du fichier de conditions aux limites',1) | |
| 300 | |||
| 301 | ! La tranche de donnees a lire: | ||
| 302 | 10 | start(1) = 1 | |
| 303 | 10 | start(2) = jour | |
| 304 | 10 | epais(1) = klon_glo | |
| 305 | 10 | epais(2) = 1 | |
| 306 | |||
| 307 | |||
| 308 | !**************************************************************************************** | ||
| 309 | ! 2) Read fraction if not type_ocean=couple | ||
| 310 | ! | ||
| 311 | !**************************************************************************************** | ||
| 312 | |||
| 313 | 1/2✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. | 10 | IF ( type_ocean /= 'couple') THEN | 
| 314 | ! | ||
| 315 | ! Ocean fraction | ||
| 316 | 10 | ierr = NF90_INQ_VARID(nid, 'FOCE', nvarid) | |
| 317 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname, 'Le champ <FOCE> est absent',1) | 
| 318 | |||
| 319 | 10 | ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_oce),start,epais) | |
| 320 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FOCE>' ,1) | 
| 321 | ! | ||
| 322 | ! Sea-ice fraction | ||
| 323 | 10 | ierr = NF90_INQ_VARID(nid, 'FSIC', nvarid) | |
| 324 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FSIC> est absent',1) | 
| 325 | |||
| 326 | 10 | ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_sic),start,epais) | |
| 327 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FSIC>' ,1) | 
| 328 | |||
| 329 | |||
| 330 | ! Read land and continentals fraction only if asked for | ||
| 331 | 3/4✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. ✓ Branch 2 taken 1 times. ✓ Branch 3 taken 9 times. | 10 | IF (read_continents .OR. itime == 1) THEN | 
| 332 | ! | ||
| 333 | ! Land fraction | ||
| 334 | 1 | ierr = NF90_INQ_VARID(nid, 'FTER', nvarid) | |
| 335 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FTER> est absent',1) | 
| 336 | |||
| 337 | 1 | ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_ter),start,epais) | |
| 338 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FTER>',1) | 
| 339 | ! | ||
| 340 | ! Continentale ice fraction | ||
| 341 | 1 | ierr = NF90_INQ_VARID(nid, 'FLIC', nvarid) | |
| 342 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FLIC> est absent',1) | 
| 343 | |||
| 344 | 1 | ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_lic),start,epais) | |
| 345 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 1 times. | 1 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FLIC>',1) | 
| 346 | END IF | ||
| 347 | |||
| 348 | END IF ! type_ocean /= couple | ||
| 349 | |||
| 350 | !**************************************************************************************** | ||
| 351 | ! 3) Read sea-surface temperature, if not coupled ocean | ||
| 352 | ! | ||
| 353 | !**************************************************************************************** | ||
| 354 | 1/2✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. | 10 | IF ( type_ocean /= 'couple') THEN | 
| 355 | |||
| 356 | 10 | ierr = NF90_INQ_VARID(nid, 'SST', nvarid) | |
| 357 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <SST> est absent',1) | 
| 358 | |||
| 359 | 10 | ierr = NF90_GET_VAR(nid,nvarid,sst_glo,start,epais) | |
| 360 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <SST>',1) | 
| 361 | |||
| 362 | END IF | ||
| 363 | |||
| 364 | !**************************************************************************************** | ||
| 365 | ! 4) Read albedo and rugosity for land surface, only in case of no vegetation model | ||
| 366 | ! | ||
| 367 | !**************************************************************************************** | ||
| 368 | |||
| 369 | 1/2✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. | 10 | IF (.NOT. ok_veget) THEN | 
| 370 | ! | ||
| 371 | ! Read albedo | ||
| 372 | 10 | ierr = NF90_INQ_VARID(nid, 'ALB', nvarid) | |
| 373 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <ALB> est absent',1) | 
| 374 | |||
| 375 | 10 | ierr = NF90_GET_VAR(nid,nvarid,alb_glo,start,epais) | |
| 376 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <ALB>',1) | 
| 377 | ! | ||
| 378 | ! Read rugosity | ||
| 379 | 10 | ierr = NF90_INQ_VARID(nid, 'RUG', nvarid) | |
| 380 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <RUG> est absent',1) | 
| 381 | |||
| 382 | 10 | ierr = NF90_GET_VAR(nid,nvarid,rug_glo,start,epais) | |
| 383 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <RUG>',1) | 
| 384 | |||
| 385 | END IF | ||
| 386 | |||
| 387 | !**************************************************************************************** | ||
| 388 | ! 5) Close file and distribuate variables to all processus | ||
| 389 | ! | ||
| 390 | !**************************************************************************************** | ||
| 391 | 10 | ierr = NF90_CLOSE(nid) | |
| 392 | 1/2✗ Branch 0 not taken. ✓ Branch 1 taken 10 times. | 10 | IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1) | 
| 393 | ENDIF ! is_mpi_root | ||
| 394 | |||
| 395 | !$OMP END MASTER | ||
| 396 | !$OMP BARRIER | ||
| 397 | |||
| 398 | 1/2✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. | 10 | IF ( type_ocean /= 'couple') THEN | 
| 399 | 10 | CALL Scatter(sst_glo,sst) | |
| 400 | 10 | CALL Scatter(pct_glo(:,is_oce),pctsrf(:,is_oce)) | |
| 401 | 10 | CALL Scatter(pct_glo(:,is_sic),pctsrf(:,is_sic)) | |
| 402 | 3/4✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. ✓ Branch 2 taken 1 times. ✓ Branch 3 taken 9 times. | 10 | IF (read_continents .OR. itime == 1) THEN | 
| 403 | 1 | CALL Scatter(pct_glo(:,is_ter),pctsrf(:,is_ter)) | |
| 404 | 1 | CALL Scatter(pct_glo(:,is_lic),pctsrf(:,is_lic)) | |
| 405 | END IF | ||
| 406 | END IF | ||
| 407 | |||
| 408 | 1/2✓ Branch 0 taken 10 times. ✗ Branch 1 not taken. | 10 | IF (.NOT. ok_veget) THEN | 
| 409 | 10 | CALL Scatter(alb_glo, albedo) | |
| 410 | 10 | CALL Scatter(rug_glo, rugos) | |
| 411 | END IF | ||
| 412 | |||
| 413 | ENDIF ! Grid type | ||
| 414 | |||
| 415 | ENDIF ! time to read | ||
| 416 | |||
| 417 | 480 | END SUBROUTINE limit_read_tot | |
| 418 | |||
| 419 | END MODULE limit_read_mod | ||
| 420 |