Changeset 12250
- Timestamp:
- 2019-12-14T09:41:16+01:00 (3 years ago)
- Location:
- NEMO/branches/2019/dev_r11943_MERGE_2019/src
- Files:
-
- 1 deleted
- 10 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/BDY/bdydta.F90
r12205 r12250 75 75 CONTAINS 76 76 77 SUBROUTINE bdy_dta( kt, Kmm, kt_offset )77 SUBROUTINE bdy_dta( kt, Kmm, pt_offset ) 78 78 !!---------------------------------------------------------------------- 79 79 !! *** SUBROUTINE bdy_dta *** … … 86 86 INTEGER, INTENT(in) :: kt ! ocean time-step index 87 87 INTEGER, INTENT(in) :: Kmm ! ocean time level index 88 INTEGER, INTENT(in), OPTIONAL :: kt_offset ! time offset in units of timesteps 89 ! ! is present then units = subcycle timesteps. 90 ! ! kt_offset = 0 => get data at "now" time level 91 ! ! kt_offset = -1 => get data at "before" time level 92 ! ! kt_offset = +1 => get data at "after" time level 93 ! ! etc. 88 REAL(wp),INTENT(in), OPTIONAL :: pt_offset ! time offset in units of timesteps 94 89 ! 95 90 INTEGER :: jbdy, jfld, jstart, jend, ib, jl ! dummy loop indices … … 216 211 ! read/update all bdy data 217 212 ! ------------------------ 218 CALL fld_read( kt, 1, bf_alias, kt_offset = kt_offset)213 CALL fld_read( kt, 1, bf_alias, pt_offset = pt_offset, Kmm = Kmm ) 219 214 ! apply some corrections in some specific cases... 220 215 ! -------------------------------------------------- … … 336 331 nblen => idx_bdy(jbdy)%nblen 337 332 nblenrim => idx_bdy(jbdy)%nblenrim 338 IF( cn_dyn2d(jbdy) == 'frs' ) THEN ; ilen1(:)=nblen(:) ; ELSE ; ilen1(:)=nblenrim(:) ; ENDIF 339 IF ( dta_bdy(jbdy)%lneed_ssh ) dta_bdy_s(jbdy)%ssh(1:ilen1(1)) = dta_bdy(jbdy)%ssh(1:ilen1(1)) 340 IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%u2d(1:ilen1(2)) = dta_bdy(jbdy)%u2d(1:ilen1(2)) 341 IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%v2d(1:ilen1(3)) = dta_bdy(jbdy)%v2d(1:ilen1(3)) 342 ENDIF 343 END DO 344 ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 345 ! 346 CALL bdy_dta_tides( kt=kt, kt_offset=kt_offset ) 347 ENDIF 333 IF( cn_dyn2d(jbdy) == 'frs' ) THEN ; ilen1(:)=nblen(:) 334 ELSE ; ilen1(:)=nblenrim(:) 335 ENDIF 336 IF ( dta_bdy(jbdy)%lneed_ssh ) dta_bdy_s(jbdy)%ssh(1:ilen1(1)) = dta_bdy(jbdy)%ssh(1:ilen1(1)) 337 IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%u2d(1:ilen1(2)) = dta_bdy(jbdy)%u2d(1:ilen1(2)) 338 IF ( dta_bdy(jbdy)%lneed_dyn2d ) dta_bdy_s(jbdy)%v2d(1:ilen1(3)) = dta_bdy(jbdy)%v2d(1:ilen1(3)) 339 ENDIF 340 END DO 341 ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 342 ! 343 CALL bdy_dta_tides( kt=kt, pt_offset=pt_offset ) 348 344 ENDIF 349 ! 350 IF( ln_timing ) CALL timing_stop('bdy_dta') 351 ! 352 END SUBROUTINE bdy_dta 345 ENDIF 346 ! 347 IF( ln_timing ) CALL timing_stop('bdy_dta') 348 ! 349 END SUBROUTINE bdy_dta 353 350 354 351 … … 449 446 IF( nn_ice_dta(jbdy) == 1 ) THEN ! if we get ice bdy data from netcdf file 450 447 CALL fld_fill( bf(jp_bdya_i,jbdy:jbdy), bn_a_i, cn_dir, 'bdy_dta', 'a_i'//' '//ctmp1, ctmp2 ) ! use namelist info 451 CALL fld_clopn( bf(jp_bdya_i,jbdy), nyear, nmonth, nday ) ! not a problem when we call it again after 448 CALL fld_def( bf(jp_bdya_i,jbdy) ) 449 CALL iom_open( bf(jp_bdya_i,jbdy)%clname, bf(jp_bdya_i,jbdy)%num ) 452 450 idvar = iom_varid( bf(jp_bdya_i,jbdy)%num, bf(jp_bdya_i,jbdy)%clvar, kndims=indims, kdimsz=i4dimsz, lduld=lluld ) 453 451 IF( indims == 4 .OR. ( indims == 3 .AND. .NOT. lluld ) ) THEN ; ipl = i4dimsz(3) ! xylt or xyl 454 452 ELSE ; ipl = 1 ! xy or xyt 455 453 ENDIF 454 CALL iom_close( bf(jp_bdya_i,jbdy)%num ) 456 455 bf(jp_bdya_i,jbdy)%clrootname = 'NOT USED' ! reset to default value as this subdomain may not need to read this bdy 457 456 ENDIF -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/BDY/bdytides.F90
r12205 r12250 269 269 270 270 271 SUBROUTINE bdy_dta_tides( kt, kit, kt_offset )271 SUBROUTINE bdy_dta_tides( kt, kit, pt_offset ) 272 272 !!---------------------------------------------------------------------- 273 273 !! *** SUBROUTINE bdy_dta_tides *** … … 278 278 INTEGER, INTENT(in) :: kt ! Main timestep counter 279 279 INTEGER, OPTIONAL, INTENT(in) :: kit ! Barotropic timestep counter (for timesplitting option) 280 INTEGER, OPTIONAL, INTENT(in) :: kt_offset ! time offset in units of timesteps. NB. if kit 281 ! ! is present then units = subcycle timesteps. 282 ! ! kt_offset = 0 => get data at "now" time level 283 ! ! kt_offset = -1 => get data at "before" time level 284 ! ! kt_offset = +1 => get data at "after" time level 285 ! ! etc. 280 REAL(wp),OPTIONAL, INTENT(in) :: pt_offset ! time offset in units of timesteps 286 281 ! 287 282 LOGICAL :: lk_first_btstp ! =.TRUE. if time splitting and first barotropic step 288 283 INTEGER :: itide, ib_bdy, ib, igrd ! loop indices 289 INTEGER :: time_add ! time offset in units of timesteps290 284 INTEGER, DIMENSION(jpbgrd) :: ilen0 291 285 INTEGER, DIMENSION(1:jpbgrd) :: nblen, nblenrim ! short cuts 292 REAL(wp) :: z_arg, z_sarg, zramp, zoff, z_cost, z_sist 286 REAL(wp) :: z_arg, z_sarg, zramp, zoff, z_cost, z_sist, zt_offset 293 287 !!---------------------------------------------------------------------- 294 288 ! … … 296 290 IF ( PRESENT(kit).AND.( kit /= 1 ) ) THEN ; lk_first_btstp=.FALSE. ; ENDIF 297 291 298 time_add = 0 299 IF( PRESENT(kt_offset) ) THEN 300 time_add = kt_offset 301 ENDIF 292 zt_offset = 0._wp 293 IF( PRESENT(pt_offset) ) zt_offset = pt_offset 302 294 303 295 ! Absolute time from model initialization: 304 296 IF( PRESENT(kit) ) THEN 305 z_arg = ( kt + (kit+time_add-1) / REAL(nn_baro,wp) ) * rdt297 z_arg = ( REAL(kt, wp) + ( REAL(kit, wp) + zt_offset - 1. ) / REAL(nn_baro, wp) ) * rdt 306 298 ELSE 307 z_arg = ( kt + time_add) * rdt299 z_arg = ( REAL(kt, wp) + zt_offset ) * rdt 308 300 ENDIF 309 301 310 302 ! Linear ramp on tidal component at open boundaries 311 303 zramp = 1. 312 IF (ln_tide_ramp) zramp = MIN(MAX( (z_arg - nit000*rdt)/(rn_tide_ramp_dt*rday),0.),1.)304 IF (ln_tide_ramp) zramp = MIN(MAX( (z_arg - REAL(nit000,wp)*rdt)/(rn_tide_ramp_dt*rday),0.),1.) 313 305 314 306 DO ib_bdy = 1,nb_bdy … … 327 319 IF ( ( nsec_day == NINT(0.5_wp * rdt) .OR. kt==nit000 ) .AND. lk_first_btstp ) THEN 328 320 ! 329 kt_tide = kt - (nsec_day - 0.5_wp * rdt)/rdt321 kt_tide = kt - NINT((REAL(nsec_day,wp) - 0.5_wp * rdt)/rdt) 330 322 ! 331 323 IF(lwp) THEN … … 339 331 ! 340 332 ENDIF 341 zoff = -kt_tide* rdt ! time offset relative to nodal factor computation time333 zoff = REAL(-kt_tide,wp) * rdt ! time offset relative to nodal factor computation time 342 334 ! 343 335 ! If time splitting, initialize arrays from slow varying open boundary data: -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DOM/daymod.F90
r12236 r12250 58 58 !! 59 59 !! ** Action : - nyear : current year 60 !! - nmonth : current month of the year nyear 61 !! - nday : current day of the month nmonth 62 !! - nday_year : current day of the year nyear 63 !! - nsec_year : current time step counted in second since 00h jan 1st of the current year 64 !! - nsec_month : current time step counted in second since 00h 1st day of the current month 65 !! - nsec_day : current time step counted in second since 00h of the current day 66 !! - nsec1jan000 : second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year 67 !! - nmonth_len, nyear_len, nmonth_half, nmonth_end through day_mth 68 !!---------------------------------------------------------------------- 69 INTEGER :: inbday, idweek ! local integers 60 !! - nmonth : current month of the current nyear 61 !! - nday : current day of the current nmonth 62 !! - nday_year : current day of the current nyear 63 !! - nsec_year : seconds between 00h jan 1st of the current year and half of the current time step 64 !! - nsec_month : seconds between 00h 1st day of the current month and half of the current time step 65 !! - nsec_monday : seconds between 00h of the last Monday and half of the current time step 66 !! - nsec_day : seconds between 00h of the current day and half of the current time step 67 !! - nsec1jan000 : seconds between Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year 68 !! - nmonth_len, nyear_len, nmonth_beg through day_mth 69 !!---------------------------------------------------------------------- 70 INTEGER :: inbday, imonday, isecrst ! local integers 70 71 REAL(wp) :: zjul ! local scalar 71 72 !!---------------------------------------------------------------------- … … 76 77 & 'You must do a restart at higher frequency (or remove this stop and recompile the code in I8)' ) 77 78 ENDIF 78 nsecd = NINT( rday)79 nsecd = NINT( rday ) 79 80 nsecd05 = NINT( 0.5 * rday ) 80 81 ndt = NINT( rdt ) … … 90 91 nhour = nn_time0 / 100 91 92 nminute = ( nn_time0 - nhour * 100 ) 92 93 CALL ymds2ju( nyear, nmonth, nday, nhour*3600._wp+nminute*60._wp, fjulday ) 93 isecrst = ( nhour * NINT(rhhmm) + nminute ) * NINT(rmmss) 94 95 CALL ymds2ju( nyear, nmonth, nday, REAL(isecrst,wp), fjulday ) 94 96 IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday ) fjulday = REAL(NINT(fjulday),wp) ! avoid truncation error 95 IF( n n_time0*3600 - ndt05 .lt. 0 ) fjulday = fjulday + 1.! move back to the day at nit000 (and not at nit000 - 1)97 IF( nhour*NINT(rhhmm*rmmss) + nminute*NINT(rmmss) - ndt05 .LT. 0 ) fjulday = fjulday+1. ! move back to the day at nit000 (and not at nit000 - 1) 96 98 97 99 nsec1jan000 = 0 … … 112 114 nday_year = nday + SUM( nmonth_len(1:nmonth - 1) ) 113 115 114 !compute number of days between last monday and today115 CALL ymds2ju( 1900, 01, 01, 0.0, zjul ) ! compute julian day value of 01.01.1900 (our reference that was a Monday)116 inbday = FLOOR(fjulday - zjul) ! compute nb day between 01.01.1900 and start of current day117 i dweek = MOD(inbday, 7)! compute nb day between last monday and current day118 IF (i dweek .lt. 0) idweek=idweek+7! Avoid negative values for dates before 01.01.1900116 !compute number of days between last Monday and today 117 CALL ymds2ju( 1900, 01, 01, 0.0, zjul ) ! compute julian day value of 01.01.1900 (our reference that was a Monday) 118 inbday = FLOOR(fjulday - zjul) ! compute nb day between 01.01.1900 and start of current day 119 imonday = MOD(inbday, 7) ! compute nb day between last monday and current day 120 IF (imonday .LT. 0) imonday = imonday + 7 ! Avoid negative values for dates before 01.01.1900 119 121 120 122 ! number of seconds since the beginning of current year/month/week/day at the middle of the time-step 121 IF (nhour*3600+nminute*60-ndt05 .gt. 0) THEN123 IF( isecrst - ndt05 .GT. 0 ) THEN 122 124 ! 1 timestep before current middle of first time step is still the same day 123 nsec_year = (nday_year-1) * nsecd + nhour*3600+nminute*60- ndt05124 nsec_month = (nday-1) * nsecd + nhour*3600+nminute*60- ndt05125 nsec_year = (nday_year-1) * nsecd + isecrst - ndt05 126 nsec_month = (nday-1) * nsecd + isecrst - ndt05 125 127 ELSE 126 128 ! 1 time step before the middle of the first time step is the previous day 127 nsec_year = nday_year * nsecd + nhour*3600+nminute*60- ndt05128 nsec_month = nday * nsecd + nhour*3600+nminute*60- ndt05129 ENDIF 130 nsec_ week = idweek * nsecd + nhour*3600+nminute*60- ndt05131 nsec_day = nhour*3600+nminute*60- ndt05132 IF( nsec_day .lt. 0 ) nsec_day = nsec_day+ nsecd133 IF( nsec_ week .lt. 0 ) nsec_week = nsec_week+ nsecd*7129 nsec_year = nday_year * nsecd + isecrst - ndt05 130 nsec_month = nday * nsecd + isecrst - ndt05 131 ENDIF 132 nsec_monday = imonday * nsecd + isecrst - ndt05 133 nsec_day = isecrst - ndt05 134 IF( nsec_day .LT. 0 ) nsec_day = nsec_day + nsecd 135 IF( nsec_monday .LT. 0 ) nsec_monday = nsec_monday + nsecd*7 134 136 135 137 ! control print 136 138 IF(lwp) WRITE(numout,'(a,i6,a,i2,a,i2,a,i8,a,i8,a,i8,a,i8)') & 137 139 & ' =======>> 1/2 time step before the start of the run DATE Y/M/D = ', & 138 & nyear, '/', nmonth, '/', nday, ' nsec_day:', nsec_day, ' nsec_ week:', nsec_week, ' &140 & nyear, '/', nmonth, '/', nday, ' nsec_day:', nsec_day, ' nsec_monday:', nsec_monday, ' & 139 141 & nsec_month:', nsec_month , ' nsec_year:' , nsec_year 140 142 143 nsec000_1jan000 = nsec1jan000 + nsec_year + ndt05 144 nsecend_1jan000 = nsec000_1jan000 + ndt * ( nitend - nit000 + 1 ) 145 141 146 ! Up to now, calendar parameters are related to the end of previous run (nit000-1) 142 147 ! call day to set the calendar parameters at the begining of the current simulaton. needed by iom_init … … 160 165 !! ** Purpose : calendar values related to the months 161 166 !! 162 !! ** Action : - nmonth_len : length in days of the months of the current year 163 !! - nyear_len : length in days of the previous/current year 164 !! - nmonth_half : second since the beginning of the year and the halft of the months 165 !! - nmonth_end : second since the beginning of the year and the end of the months 166 !!---------------------------------------------------------------------- 167 INTEGER :: jm ! dummy loop indice 167 !! ** Action : - nyear_len : length in days of the previous/current year 168 !! - nmonth_len : length in days of the months of the current year 169 !! - nmonth_half : second since the beginning of the current year and the halft of the months 170 !! - nmonth_end : second since the beginning of the current year and the end of the months 171 !!---------------------------------------------------------------------- 172 INTEGER :: jm ,jy ! dummy loop indice 173 INTEGER, DIMENSION(12) :: idaymt ! length in days of the 12 months for non-leap year 168 174 !!---------------------------------------------------------------------- 169 175 170 176 ! length of the month of the current year (from nleapy, read in namelist) 171 177 IF ( nleapy < 2 ) THEN 172 nmonth_len(:) = (/ 31, 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31, 31 /) 178 ! default values 179 idaymt(1:12) = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /) 180 nmonth_len(-11: 25) = (/ idaymt(1:12), idaymt(1:12), idaymt(1:12), idaymt(1) /) 173 181 nyear_len(:) = 365 182 ! 174 183 IF ( nleapy == 1 ) THEN ! we are using calandar with leap years 175 IF ( MOD(nyear-1, 4) == 0 .AND. ( MOD(nyear-1, 400) == 0 .OR. MOD(nyear-1, 100) /= 0 ) ) THEN 176 nyear_len(0) = 366 177 ENDIF 178 IF ( MOD(nyear , 4) == 0 .AND. ( MOD(nyear , 400) == 0 .OR. MOD(nyear , 100) /= 0 ) ) THEN 179 nmonth_len(2) = 29 180 nyear_len(1) = 366 181 ENDIF 182 IF ( MOD(nyear+1, 4) == 0 .AND. ( MOD(nyear+1, 400) == 0 .OR. MOD(nyear+1, 100) /= 0 ) ) THEN 183 nyear_len(2) = 366 184 ENDIF 184 DO jy = -1,1 185 IF ( MOD(nyear+jy, 4) == 0 .AND. ( MOD(nyear+jy, 400) == 0 .OR. MOD(nyear+jy, 100) /= 0 ) ) THEN 186 nmonth_len(2 + 12*jy) = 29 187 nyear_len( 1 + jy) = 366 188 ENDIF 189 ENDDO 185 190 ENDIF 186 191 ELSE … … 189 194 ENDIF 190 195 191 ! half month in second since the begining of the year:192 196 ! time since Jan 1st 0 1 2 ... 11 12 13 193 197 ! ---------*--|--*--|--*--| ... |--*--|--*--|--*--|-------------------------------------- 194 198 ! <---> <---> <---> ... <---> <---> <---> 195 199 ! month number 0 1 2 ... 11 12 13 196 ! 197 ! nmonth_half(jm) = rday * REAL( 0.5 * nmonth_len(jm) + SUM(nmonth_len(1:jm-1)) ) 198 nmonth_half(0) = - nsecd05 * nmonth_len(0) 199 DO jm = 1, 13 200 nmonth_half(jm) = nmonth_half(jm-1) + nsecd05 * ( nmonth_len(jm-1) + nmonth_len(jm) ) 200 nmonth_beg(1) = 0 201 DO jm = 2, 25 202 nmonth_beg(jm) = nmonth_beg(jm-1) + nsecd * nmonth_len(jm-1) 201 203 END DO 202 203 nmonth_end(0) = 0 204 DO jm = 1, 13 205 nmonth_end(jm) = nmonth_end(jm-1) + nsecd * nmonth_len(jm) 204 DO jm = 0,-11,-1 205 nmonth_beg(jm) = nmonth_beg(jm+1) - nsecd * nmonth_len(jm) 206 206 END DO 207 207 ! … … 235 235 zprec = 0.1 / rday 236 236 ! ! New time-step 237 nsec_year = nsec_year+ ndt238 nsec_month = nsec_month+ ndt239 nsec_ week = nsec_week+ ndt237 nsec_year = nsec_year + ndt 238 nsec_month = nsec_month + ndt 239 nsec_monday = nsec_monday + ndt 240 240 nsec_day = nsec_day + ndt 241 241 adatrj = adatrj + rdt / rday … … 272 272 & ' New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, ' nday_year = ', nday_year 273 273 IF(lwp) WRITE(numout,'(a,i8,a,i7,a,i5)') ' nsec_year = ', nsec_year, & 274 & ' nsec_month = ', nsec_month, ' nsec_day = ', nsec_day, ' nsec_ week = ', nsec_week275 ENDIF 276 277 IF( nsec_ week > 7*nsecd ) nsec_week= ndt05 ! New week274 & ' nsec_month = ', nsec_month, ' nsec_day = ', nsec_day, ' nsec_monday = ', nsec_monday 275 ENDIF 276 277 IF( nsec_monday > 7*nsecd ) nsec_monday = ndt05 ! New week 278 278 279 279 IF(sn_cfctl%l_prtctl) THEN … … 319 319 ! 320 320 REAL(wp) :: zkt, zndastp, zdayfrac, ksecs, ktime 321 INTEGER :: ihour, iminute 321 INTEGER :: ihour, iminute, isecond 322 322 !!---------------------------------------------------------------------- 323 323 … … 349 349 CALL iom_get( numror, 'adatrj', adatrj , ldxios = lrxios ) 350 350 CALL iom_get( numror, 'ntime' , ktime , ldxios = lrxios ) 351 nn_time0=INT(ktime)351 nn_time0 = NINT(ktime) 352 352 ! calculate start time in hours and minutes 353 zdayfrac=adatrj-INT(adatrj)354 ksecs = NINT(zdayfrac *86400) ! Nearest second to catch rounding errors in adatrj355 ihour = INT(ksecs/3600)356 iminute = ksecs /60-ihour*60353 zdayfrac = adatrj - REAL(INT(adatrj), wp) 354 ksecs = NINT(zdayfrac * rday) ! Nearest second to catch rounding errors in adatrj 355 ihour = ksecs / NINT( rhhmm*rmmss ) 356 iminute = ksecs / NINT(rmmss) - ihour*NINT(rhhmm) 357 357 358 358 ! Add to nn_time0 359 359 nhour = nn_time0 / 100 360 360 nminute = ( nn_time0 - nhour * 100 ) 361 nminute =nminute+iminute361 nminute = nminute + iminute 362 362 363 IF( nminute >= 60) THEN364 nminute =nminute-60365 nhour =nhour+1363 IF( nminute >= NINT(rhhmm) ) THEN 364 nminute = nminute - NINT(rhhmm) 365 nhour = nhour+1 366 366 ENDIF 367 367 nhour=nhour+ihour 368 IF( nhour >= 24) THEN369 nhour =nhour-24370 adatrj =adatrj+1368 IF( nhour >= NINT(rjjhh) ) THEN 369 nhour = nhour - NINT(rjjhh) 370 adatrj = adatrj + 1. 371 371 ENDIF 372 372 nn_time0 = nhour * 100 + nminute 373 adatrj = INT(adatrj) ! adatrj set to integer as nn_time0 updated373 adatrj = REAL(INT(adatrj), wp) ! adatrj set to integer as nn_time0 updated 374 374 ELSE 375 375 ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) … … 377 377 nhour = nn_time0 / 100 378 378 nminute = ( nn_time0 - nhour * 100 ) 379 IF( nhour*3600+nminute*60-ndt05 .lt. 0 ) ndastp=ndastp-1 ! Start hour is specified in the namelist (default 0) 379 isecond = ( nhour * NINT(rhhmm) + nminute ) * NINT(rmmss) 380 IF( isecond - ndt05 .lt. 0 ) ndastp = ndastp - 1 ! Start hour is specified in the namelist (default 0) 380 381 adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 381 382 ! note this is wrong if time step has changed during run … … 386 387 nhour = nn_time0 / 100 387 388 nminute = ( nn_time0 - nhour * 100 ) 388 IF( nhour*3600+nminute*60-ndt05 .lt. 0 ) ndastp=ndastp-1 ! Start hour is specified in the namelist (default 0) 389 isecond = ( nhour * NINT(rhhmm) + nminute ) * NINT(rmmss) 390 IF( isecond - ndt05 .LT. 0 ) ndastp = ndastp - 1 ! Start hour is specified in the namelist (default 0) 389 391 adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 390 392 ENDIF -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DOM/dom_oce.F90
r12150 r12250 195 195 INTEGER , PUBLIC :: ndastp !: time step date in yyyymmdd format 196 196 INTEGER , PUBLIC :: nday_year !: current day counted from jan 1st of the current year 197 INTEGER , PUBLIC :: nsec_year !: current time step counted in second since 00h jan 1st of the current year198 INTEGER , PUBLIC :: nsec_month !: current time step counted in second since 00h 1st day of the current month199 INTEGER , PUBLIC :: nsec_ week !: current time step counted in second since 00h of last monday200 INTEGER , PUBLIC :: nsec_day !: current time step counted in second since 00h of the current day197 INTEGER , PUBLIC :: nsec_year !: seconds between 00h jan 1st of the current year and half of the current time step 198 INTEGER , PUBLIC :: nsec_month !: seconds between 00h 1st day of the current month and half of the current time step 199 INTEGER , PUBLIC :: nsec_monday !: seconds between 00h of the last Monday and half of the current time step 200 INTEGER , PUBLIC :: nsec_day !: seconds between 00h of the current day and half of the current time step 201 201 REAL(wp), PUBLIC :: fjulday !: current julian day 202 202 REAL(wp), PUBLIC :: fjulstartyear !: first day of the current year in julian days 203 203 REAL(wp), PUBLIC :: adatrj !: number of elapsed days since the begining of the whole simulation 204 204 ! !: (cumulative duration of previous runs that may have used different time-step size) 205 INTEGER , PUBLIC, DIMENSION(0: 2) :: nyear_len !: length in days of the previous/current/next year 206 INTEGER , PUBLIC, DIMENSION(0:13) :: nmonth_len !: length in days of the months of the current year 207 INTEGER , PUBLIC, DIMENSION(0:13) :: nmonth_half !: second since Jan 1st 0h of the current year and the half of the months 208 INTEGER , PUBLIC, DIMENSION(0:13) :: nmonth_end !: second since Jan 1st 0h of the current year and the end of the months 209 INTEGER , PUBLIC :: nsec1jan000 !: second since Jan 1st 0h of nit000 year and Jan 1st 0h the current year 205 INTEGER , PUBLIC, DIMENSION( 0: 2) :: nyear_len !: length in days of the previous/current/next year 206 INTEGER , PUBLIC, DIMENSION(-11:25) :: nmonth_len !: length in days of the months of the current year 207 INTEGER , PUBLIC, DIMENSION(-11:25) :: nmonth_beg !: second since Jan 1st 0h of the current year and the half of the months 208 INTEGER , PUBLIC :: nsec1jan000 !: second since Jan 1st 0h of nit000 year and Jan 1st 0h the current year 209 INTEGER , PUBLIC :: nsec000_1jan000 !: second since Jan 1st 0h of nit000 year and nit000 210 INTEGER , PUBLIC :: nsecend_1jan000 !: second since Jan 1st 0h of nit000 year and nitend 210 211 211 212 !!---------------------------------------------------------------------- -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynspg_ts.F90
r12229 r12250 443 443 ! !== Update the forcing ==! (BDY and tides) 444 444 ! 445 IF( ln_bdy .AND. ln_tide ) CALL bdy_dta_tides( kt, kit=jn, kt_offset= noffset+1)445 IF( ln_bdy .AND. ln_tide ) CALL bdy_dta_tides( kt, kit=jn, pt_offset= REAL(noffset+1,wp) ) 446 446 ! Update tide potential at the beginning of current time substep 447 447 IF( ln_tide_pot .AND. ln_tide ) THEN -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/SBC/fldread.F90
r12182 r12250 13 13 !! fld_read : read input fields used for the computation of the surface boundary condition 14 14 !! fld_init : initialization of field read 15 !! fld_ rec : determined the record(s) to be read15 !! fld_def : define the record(s) of the file and its name 16 16 !! fld_get : read the data 17 17 !! fld_map : read global data from file and map onto local data using a general mapping (use for open boundaries) 18 18 !! fld_rot : rotate the vector fields onto the local grid direction 19 !! fld_clopn : update the data file name andclose/open the files19 !! fld_clopn : close/open the files 20 20 !! fld_fill : fill the data structure with the associated information read in namelist 21 21 !! wgt_list : manage the weights used for interpolation … … 25 25 !! seaoverland : create shifted matrices for seaoverland application 26 26 !! fld_interp : apply weights to input gridded data to create data on model grid 27 !! ksec_week : function returning the first 3 letters of the first day of the weekly file 27 !! fld_filename : define the filename according to a given date 28 !! ksec_week : function returning seconds between 00h of the beginning of the week and half of the current time step 28 29 !!---------------------------------------------------------------------- 29 30 USE oce ! ocean dynamics and tracers … … 44 45 PUBLIC fld_map ! routine called by tides_init 45 46 PUBLIC fld_read, fld_fill ! called by sbc... modules 46 PUBLIC fld_ clopn47 PUBLIC fld_def 47 48 48 49 TYPE, PUBLIC :: FLD_N !: Namelist field informations … … 72 73 INTEGER , DIMENSION(2) :: nrec_b ! before record (1: index, 2: second since Jan. 1st 00h of nit000 year) 73 74 INTEGER , DIMENSION(2) :: nrec_a ! after record (1: index, 2: second since Jan. 1st 00h of nit000 year) 74 REAL(wp) , ALLOCATABLE, DIMENSION(:,:,: ) :: fnow ! input fields interpolated to now time step 75 REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:,:) :: fdta ! 2 consecutive record of input fields 75 INTEGER , ALLOCATABLE, DIMENSION(: ) :: nrecsec ! 76 REAL(wp), ALLOCATABLE, DIMENSION(:,:,: ) :: fnow ! input fields interpolated to now time step 77 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: fdta ! 2 consecutive record of input fields 76 78 CHARACTER(len = 256) :: wgtname ! current name of the NetCDF weight file acting as a key 77 79 ! ! into the WGTLIST structure … … 118 120 TYPE( WGT ), DIMENSION(tot_wgts) :: ref_wgts ! array of wgts 119 121 INTEGER :: nxt_wgt = 1 ! point to next available space in ref_wgts array 122 INTEGER :: nflag = 0 120 123 REAL(wp), PARAMETER :: undeff_lsm = -999.00_wp 121 124 … … 129 132 CONTAINS 130 133 131 SUBROUTINE fld_read( kt, kn_fsbc, sd, kit, kt_offset, Kmm )134 SUBROUTINE fld_read( kt, kn_fsbc, sd, kit, pt_offset, Kmm ) 132 135 !!--------------------------------------------------------------------- 133 136 !! *** ROUTINE fld_read *** … … 145 148 TYPE(FLD), INTENT(inout), DIMENSION(:) :: sd ! input field related variables 146 149 INTEGER , INTENT(in ), OPTIONAL :: kit ! subcycle timestep for timesplitting option 147 INTEGER , INTENT(in ), OPTIONAL :: kt_offset ! provide fields at time other than "now" 148 ! ! kt_offset = -1 => fields at "before" time level 149 ! ! kt_offset = +1 => fields at "after" time level 150 ! ! etc. 151 INTEGER , INTENT(in ), OPTIONAL :: Kmm ! ocean time level index 152 !! 153 INTEGER :: itmp ! local variable 150 REAL(wp) , INTENT(in ), OPTIONAL :: pt_offset ! provide fields at time other than "now" 151 INTEGER , INTENT(in ), OPTIONAL :: Kmm ! ocean time level index 152 !! 154 153 INTEGER :: imf ! size of the structure sd 155 154 INTEGER :: jf ! dummy indices 156 INTEGER :: isecend ! number of second since Jan. 1st 00h of nit000 year at nitend157 155 INTEGER :: isecsbc ! number of seconds between Jan. 1st 00h of nit000 year and the middle of sbc time step 158 INTEGER :: it_offset ! local time offset variable159 LOGICAL :: llnxtyr ! open next year file?160 LOGICAL :: llnxtmth ! open next month file?161 LOGICAL :: llstop ! stop is the file does not exist162 156 LOGICAL :: ll_firstcall ! true if this is the first call to fld_read for this set of fields 157 REAL(wp) :: zt_offset ! local time offset variable 163 158 REAL(wp) :: ztinta ! ratio applied to after records when doing time interpolation 164 159 REAL(wp) :: ztintb ! ratio applied to before records when doing time interpolation … … 168 163 IF( PRESENT(kit) ) ll_firstcall = ll_firstcall .and. kit == 1 169 164 170 IF( nn_components == jp_iam_sas ) THEN ; it_offset = nn_fsbc171 ELSE ; it_offset = 0172 ENDIF 173 IF( PRESENT( kt_offset) ) it_offset = kt_offset174 175 ! Note that shifting time to be centrered in the middle of sbc time step impacts only nsec_* variables of the calendar176 IF( present(kit) ) THEN ! ignore kn_fsbc in this case177 isecsbc = nsec_year + nsec1jan000 + (kit+it_offset)*NINT( rdt/REAL(nn_baro,wp) )165 IF( nn_components == jp_iam_sas ) THEN ; zt_offset = REAL( nn_fsbc, wp ) 166 ELSE ; zt_offset = 0. 167 ENDIF 168 IF( PRESENT(pt_offset) ) zt_offset = pt_offset 169 170 ! Note that all varibles starting by nsec_* are shifted time by +1/2 time step to be centrered 171 IF( PRESENT(kit) ) THEN ! ignore kn_fsbc in this case 172 isecsbc = nsec_year + nsec1jan000 + NINT( ( REAL( kit,wp) + zt_offset ) * rdt / REAL(nn_baro,wp) ) 178 173 ELSE ! middle of sbc time step 179 isecsbc = nsec_year + nsec1jan000 + NINT(0.5 * REAL(kn_fsbc - 1,wp) * rdt) + it_offset * NINT(rdt) 174 ! note: we use kn_fsbc-1 because nsec_year is defined at the middle of the current time step 175 isecsbc = nsec_year + nsec1jan000 + NINT( ( 0.5*REAL(kn_fsbc-1,wp) + zt_offset ) * rdt ) 180 176 ENDIF 181 177 imf = SIZE( sd ) … … 184 180 DO jf = 1, imf 185 181 IF( TRIM(sd(jf)%clrootname) == 'NOT USED' ) CYCLE 186 CALL fld_init( kn_fsbc, sd(jf) ) ! read each before field (put them in after as they will be swapped)182 CALL fld_init( isecsbc, sd(jf) ) ! read each before field (put them in after as they will be swapped) 187 183 END DO 188 184 IF( lwp ) CALL wgt_print() ! control print … … 193 189 ! 194 190 DO jf = 1, imf ! --- loop over field --- ! 195 191 ! 196 192 IF( TRIM(sd(jf)%clrootname) == 'NOT USED' ) CYCLE 197 198 IF( isecsbc > sd(jf)%nrec_a(2) .OR. ll_firstcall ) THEN ! read/update the after data? 199 200 sd(jf)%nrec_b(:) = sd(jf)%nrec_a(:) ! swap before record informations 201 sd(jf)%rotn(1) = sd(jf)%rotn(2) ! swap before rotate informations 202 IF( sd(jf)%ln_tint ) sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2) ! swap before record field 203 204 CALL fld_rec( kn_fsbc, sd(jf), kt_offset = it_offset, kit = kit ) ! update after record informations 205 206 ! if kn_fsbc*rdt is larger than freqh (which is kind of odd), 207 ! it is possible that the before value is no more the good one... we have to re-read it 208 ! if before is not the last record of the file currently opened and after is the first record to be read 209 ! in a new file which means after = 1 (the file to be opened corresponds to the current time) 210 ! or after = nreclast + 1 (the file to be opened corresponds to a future time step) 211 IF( .NOT. ll_firstcall .AND. sd(jf)%ln_tint .AND. sd(jf)%nrec_b(1) /= sd(jf)%nreclast & 212 & .AND. MOD( sd(jf)%nrec_a(1), sd(jf)%nreclast ) == 1 ) THEN 213 itmp = sd(jf)%nrec_a(1) ! temporary storage 214 sd(jf)%nrec_a(1) = sd(jf)%nreclast ! read the last record of the file currently opened 215 CALL fld_get( sd(jf) ) ! read after data 216 sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2) ! re-swap before record field 217 sd(jf)%nrec_b(1) = sd(jf)%nrec_a(1) ! update before record informations 218 sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - NINT( sd(jf)%freqh * 3600. ) ! assume freq to be in hours in this case 219 sd(jf)%rotn(1) = sd(jf)%rotn(2) ! update before rotate informations 220 sd(jf)%nrec_a(1) = itmp ! move back to after record 221 ENDIF 222 223 CALL fld_clopn( sd(jf) ) ! Do we need to open a new year/month/week/day file? 224 225 IF( sd(jf)%ln_tint ) THEN 226 227 ! if kn_fsbc*rdt is larger than freqh (which is kind of odd), 228 ! it is possible that the before value is no more the good one... we have to re-read it 229 ! if before record is not just just before the after record... 230 IF( .NOT. ll_firstcall .AND. MOD( sd(jf)%nrec_a(1), sd(jf)%nreclast ) /= 1 & 231 & .AND. sd(jf)%nrec_b(1) /= sd(jf)%nrec_a(1) - 1 ) THEN 232 sd(jf)%nrec_a(1) = sd(jf)%nrec_a(1) - 1 ! move back to before record 233 CALL fld_get( sd(jf) ) ! read after data 234 sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2) ! re-swap before record field 235 sd(jf)%nrec_b(1) = sd(jf)%nrec_a(1) ! update before record informations 236 sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - NINT( sd(jf)%freqh * 3600. ) ! assume freq to be in hours in this case 237 sd(jf)%rotn(1) = sd(jf)%rotn(2) ! update before rotate informations 238 sd(jf)%nrec_a(1) = sd(jf)%nrec_a(1) + 1 ! move back to after record 239 ENDIF 240 ENDIF ! temporal interpolation? 241 242 ! do we have to change the year/month/week/day of the forcing field?? 243 ! if we do time interpolation we will need to open next year/month/week/day file before the end of the current 244 ! one. If so, we are still before the end of the year/month/week/day when calling fld_rec so sd(jf)%nrec_a(1) 245 ! will be larger than the record number that should be read for current year/month/week/day 246 ! do we need next file data? 247 ! This applies to both cases with or without time interpolation 248 IF( sd(jf)%nrec_a(1) > sd(jf)%nreclast ) THEN 249 250 sd(jf)%nrec_a(1) = sd(jf)%nrec_a(1) - sd(jf)%nreclast ! 251 252 IF( .NOT. ( sd(jf)%ln_clim .AND. sd(jf)%cltype == 'yearly' ) ) THEN ! close/open the current/new file 253 254 llnxtmth = sd(jf)%cltype == 'monthly' .OR. nday == nmonth_len(nmonth) ! open next month file? 255 llnxtyr = sd(jf)%cltype == 'yearly' .OR. (nmonth == 12 .AND. llnxtmth) ! open next year file? 256 257 ! if the run finishes at the end of the current year/month/week/day, we will allow next 258 ! year/month/week/day file to be not present. If the run continue further than the current 259 ! year/month/week/day, next year/month/week/day file must exist 260 isecend = nsec_year + nsec1jan000 + (nitend - kt) * NINT(rdt) ! second at the end of the run 261 llstop = isecend > sd(jf)%nrec_a(2) ! read more than 1 record of next year 262 ! we suppose that the date of next file is next day (should be ok even for weekly files...) 263 CALL fld_clopn( sd(jf), nyear + COUNT((/llnxtyr /)) , & 264 & nmonth + COUNT((/llnxtmth/)) - 12 * COUNT((/llnxtyr /)), & 265 & nday + 1 - nmonth_len(nmonth) * COUNT((/llnxtmth/)), llstop ) 266 267 IF( sd(jf)%num <= 0 .AND. .NOT. llstop ) THEN ! next year file does not exist 268 CALL ctl_warn('next year/month/week/day file: '//TRIM(sd(jf)%clname)// & 269 & ' not present -> back to current year/month/day') 270 CALL fld_clopn( sd(jf) ) ! back to the current year/month/day 271 sd(jf)%nrec_a(1) = sd(jf)%nreclast ! force to read the last record in the current year file 272 ENDIF 273 274 ENDIF 275 ENDIF ! open need next file? 276 277 ! read after data 278 279 CALL fld_get( sd(jf), Kmm ) 280 281 ENDIF ! read new data? 193 CALL fld_update( isecsbc, sd(jf), Kmm ) 194 ! 282 195 END DO ! --- end loop over field --- ! 283 196 … … 294 207 WRITE(numout, clfmt) TRIM( sd(jf)%clvar ), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday, & 295 208 & sd(jf)%nrec_b(1), sd(jf)%nrec_a(1), REAL(sd(jf)%nrec_b(2),wp)/rday, REAL(sd(jf)%nrec_a(2),wp)/rday 296 WRITE(numout, *) ' it_offset is : ',it_offset209 WRITE(numout, *) ' zt_offset is : ',zt_offset 297 210 ENDIF 298 211 ! temporal interpolation weights … … 318 231 319 232 320 SUBROUTINE fld_init( k n_fsbc, sdjf )233 SUBROUTINE fld_init( ksecsbc, sdjf ) 321 234 !!--------------------------------------------------------------------- 322 235 !! *** ROUTINE fld_init *** 323 236 !! 324 !! ** Purpose : - first call to fld_recto define before values325 !! - if time interpolation, read before data326 !!---------------------------------------------------------------------- 327 INTEGER , INTENT(in ) :: k n_fsbc ! sbc computation period (in time step)237 !! ** Purpose : - first call(s) to fld_def to define before values 238 !! - open file 239 !!---------------------------------------------------------------------- 240 INTEGER , INTENT(in ) :: ksecsbc ! 328 241 TYPE(FLD), INTENT(inout) :: sdjf ! input field related variables 329 !! 330 LOGICAL :: llprevyr ! are we reading previous year file? 331 LOGICAL :: llprevmth ! are we reading previous month file? 332 LOGICAL :: llprevweek ! are we reading previous week file? 333 LOGICAL :: llprevday ! are we reading previous day file? 334 LOGICAL :: llprev ! llprevyr .OR. llprevmth .OR. llprevweek .OR. llprevday 335 INTEGER :: idvar ! variable id 336 INTEGER :: inrec ! number of record existing for this variable 337 INTEGER :: iyear, imonth, iday ! first day of the current file in yyyy mm dd 338 INTEGER :: isec_week ! number of seconds since start of the weekly file 339 CHARACTER(LEN=1000) :: clfmt ! write format 340 !!--------------------------------------------------------------------- 341 ! 342 llprevyr = .FALSE. 343 llprevmth = .FALSE. 344 llprevweek = .FALSE. 345 llprevday = .FALSE. 346 isec_week = 0 347 ! 348 ! define record informations 349 CALL fld_rec( kn_fsbc, sdjf, ldbefore = .TRUE. ) ! return before values in sdjf%nrec_a (as we will swap it later) 350 ! 351 ! Note that shifting time to be centrered in the middle of sbc time step impacts only nsec_* variables of the calendar 352 ! 353 IF( sdjf%ln_tint ) THEN ! we need to read the previous record and we will put it in the current record structure 354 ! 355 IF( sdjf%nrec_a(1) == 0 ) THEN ! we redefine record sdjf%nrec_a(1) with the last record of previous year file 356 IF ( NINT(sdjf%freqh) == -12 ) THEN ! yearly mean 357 IF( sdjf%cltype == 'yearly' ) THEN ! yearly file 358 sdjf%nrec_a(1) = 1 ! force to read the unique record 359 llprevyr = .NOT. sdjf%ln_clim ! use previous year file? 360 ELSE 361 CALL ctl_stop( "fld_init: yearly mean file must be in a yearly type of file: "//TRIM(sdjf%clrootname) ) 362 ENDIF 363 ELSEIF( NINT(sdjf%freqh) == -1 ) THEN ! monthly mean 364 IF( sdjf%cltype == 'monthly' ) THEN ! monthly file 365 sdjf%nrec_a(1) = 1 ! force to read the unique record 366 llprevmth = .TRUE. ! use previous month file? 367 llprevyr = llprevmth .AND. nmonth == 1 ! use previous year file? 368 ELSE ! yearly file 369 sdjf%nrec_a(1) = 12 ! force to read december mean 370 llprevyr = .NOT. sdjf%ln_clim ! use previous year file? 371 ENDIF 372 ELSE ! higher frequency mean (in hours) 373 IF ( sdjf%cltype == 'monthly' ) THEN ! monthly file 374 sdjf%nrec_a(1) = NINT( 24. * REAL(nmonth_len(nmonth-1),wp) / sdjf%freqh )! last record of previous month 375 llprevmth = .TRUE. ! use previous month file? 376 llprevyr = llprevmth .AND. nmonth == 1 ! use previous year file? 377 ELSEIF( sdjf%cltype(1:4) == 'week' ) THEN ! weekly file 378 llprevweek = .TRUE. ! use previous week file? 379 sdjf%nrec_a(1) = NINT( 24. * 7. / sdjf%freqh ) ! last record of previous week 380 isec_week = NINT(rday) * 7 ! add a shift toward previous week 381 ELSEIF( sdjf%cltype == 'daily' ) THEN ! daily file 382 sdjf%nrec_a(1) = NINT( 24. / sdjf%freqh ) ! last record of previous day 383 llprevday = .TRUE. ! use previous day file? 384 llprevmth = llprevday .AND. nday == 1 ! use previous month file? 385 llprevyr = llprevmth .AND. nmonth == 1 ! use previous year file? 386 ELSE ! yearly file 387 sdjf%nrec_a(1) = NINT( 24. * REAL(nyear_len(0),wp) / sdjf%freqh ) ! last record of previous year 388 llprevyr = .NOT. sdjf%ln_clim ! use previous year file? 389 ENDIF 390 ENDIF 391 ENDIF 392 ! 393 IF( sdjf%cltype(1:4) == 'week' ) THEN 394 isec_week = isec_week + ksec_week( sdjf%cltype(6:8) ) ! second since the beginning of the week 395 llprevmth = isec_week > nsec_month ! longer time since the beginning of the week than the month 396 llprevyr = llprevmth .AND. nmonth == 1 397 ENDIF 398 llprev = llprevyr .OR. llprevmth .OR. llprevweek .OR. llprevday 399 ! 400 iyear = nyear - COUNT((/llprevyr /)) 401 imonth = nmonth - COUNT((/llprevmth/)) + 12 * COUNT((/llprevyr /)) 402 iday = nday - COUNT((/llprevday/)) + nmonth_len(nmonth-1) * COUNT((/llprevmth/)) - isec_week / NINT(rday) 403 ! 404 CALL fld_clopn( sdjf, iyear, imonth, iday, .NOT. llprev ) 405 ! 406 ! if previous year/month/day file does not exist, we switch to the current year/month/day 407 IF( llprev .AND. sdjf%num <= 0 ) THEN 408 CALL ctl_warn( 'previous year/month/week/day file: '//TRIM(sdjf%clrootname)// & 409 & ' not present -> back to current year/month/week/day' ) 410 ! we force to read the first record of the current year/month/day instead of last record of previous year/month/day 411 llprev = .FALSE. 412 sdjf%nrec_a(1) = 1 413 CALL fld_clopn( sdjf ) 414 ENDIF 415 ! 416 IF( llprev ) THEN ! check if the record sdjf%nrec_a(1) exists in the file 417 idvar = iom_varid( sdjf%num, sdjf%clvar ) ! id of the variable sdjf%clvar 418 IF( idvar <= 0 ) RETURN 419 inrec = iom_file( sdjf%num )%dimsz( iom_file( sdjf%num )%ndims(idvar), idvar ) ! size of the last dim of idvar 420 sdjf%nrec_a(1) = MIN( sdjf%nrec_a(1), inrec ) ! make sure we select an existing record 421 ENDIF 422 ! 423 ! read before data in after arrays(as we will swap it later) 424 CALL fld_get( sdjf ) 425 ! 426 clfmt = "(' fld_init : time-interpolation for ', a, ' read previous record = ', i6, ' at time = ', f7.2, ' days')" 427 IF(lwp) WRITE(numout, clfmt) TRIM(sdjf%clvar), sdjf%nrec_a(1), REAL(sdjf%nrec_a(2),wp)/rday 428 ! 429 ENDIF 242 !!--------------------------------------------------------------------- 243 ! 244 IF( nflag == 0 ) nflag = -( HUGE(0) - 10 ) 245 ! 246 CALL fld_def( sdjf ) 247 IF( sdjf%ln_tint .AND. ksecsbc < sdjf%nrecsec(1) ) CALL fld_def( sdjf, ldprev = .TRUE. ) 248 ! 249 CALL fld_clopn( sdjf ) 250 sdjf%nrec_a(:) = (/ 1, nflag /) ! default definition to force flp_update to read the file. 430 251 ! 431 252 END SUBROUTINE fld_init 432 253 433 254 434 SUBROUTINE fld_ rec( kn_fsbc, sdjf, ldbefore, kit, kt_offset)435 !!--------------------------------------------------------------------- 436 !! *** ROUTINE fld_ rec***255 SUBROUTINE fld_update( ksecsbc, sdjf, Kmm ) 256 !!--------------------------------------------------------------------- 257 !! *** ROUTINE fld_update *** 437 258 !! 438 259 !! ** Purpose : Compute … … 443 264 !! nrec_b(2) and nrec_a(2): time of the beginning and end of the record 444 265 !!---------------------------------------------------------------------- 445 INTEGER , INTENT(in ) :: kn_fsbc ! sbc computation period (in time step) 446 TYPE(FLD), INTENT(inout) :: sdjf ! input field related variables 447 LOGICAL , INTENT(in ), OPTIONAL :: ldbefore ! sent back before record values (default = .FALSE.) 448 INTEGER , INTENT(in ), OPTIONAL :: kit ! index of barotropic subcycle 449 ! ! used only if sdjf%ln_tint = .TRUE. 450 INTEGER , INTENT(in ), OPTIONAL :: kt_offset ! Offset of required time level compared to "now" 451 ! ! time level in units of time steps. 452 ! 453 LOGICAL :: llbefore ! local definition of ldbefore 454 INTEGER :: iendrec ! end of this record (in seconds) 455 INTEGER :: imth ! month number 456 INTEGER :: ifreq_sec ! frequency mean (in seconds) 457 INTEGER :: isec_week ! number of seconds since the start of the weekly file 458 INTEGER :: it_offset ! local time offset variable 459 REAL(wp) :: ztmp ! temporary variable 460 !!---------------------------------------------------------------------- 461 ! 462 ! Note that shifting time to be centrered in the middle of sbc time step impacts only nsec_* variables of the calendar 463 ! 464 IF( PRESENT(ldbefore) ) THEN ; llbefore = ldbefore .AND. sdjf%ln_tint ! needed only if sdjf%ln_tint = .TRUE. 465 ELSE ; llbefore = .FALSE. 466 ENDIF 467 ! 468 IF( nn_components == jp_iam_sas ) THEN ; it_offset = nn_fsbc 469 ELSE ; it_offset = 0 470 ENDIF 471 IF( PRESENT(kt_offset) ) it_offset = kt_offset 472 IF( PRESENT(kit) ) THEN ; it_offset = ( kit + it_offset ) * NINT( rdt/REAL(nn_baro,wp) ) 473 ELSE ; it_offset = it_offset * NINT( rdt ) 474 ENDIF 475 ! 476 ! ! =========== ! 477 IF ( NINT(sdjf%freqh) == -12 ) THEN ! yearly mean 478 ! ! =========== ! 479 ! 480 IF( sdjf%ln_tint ) THEN ! time interpolation, shift by 1/2 record 481 ! 482 ! INT( ztmp ) 483 ! /|\ 484 ! 1 | *---- 485 ! 0 |----( 486 ! |----+----|--> time 487 ! 0 /|\ 1 (nday/nyear_len(1)) 488 ! | 489 ! | 490 ! forcing record : 1 491 ! 492 ztmp = REAL( nsec_year, wp ) / ( REAL( nyear_len(1), wp ) * rday ) + 0.5 & 493 & + REAL( it_offset, wp ) / ( REAL( nyear_len(1), wp ) * rday ) 494 sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/)) 495 ! swap at the middle of the year 496 IF( llbefore ) THEN ; sdjf%nrec_a(2) = nsec1jan000 - (1 - INT(ztmp)) * NINT(0.5 * rday) * nyear_len(0) + & 497 & INT(ztmp) * NINT( 0.5 * rday) * nyear_len(1) 498 ELSE ; sdjf%nrec_a(2) = nsec1jan000 + (1 - INT(ztmp)) * NINT(0.5 * rday) * nyear_len(1) + & 499 & INT(ztmp) * INT(rday) * nyear_len(1) + INT(ztmp) * NINT( 0.5 * rday) * nyear_len(2) 266 INTEGER , INTENT(in ) :: ksecsbc ! 267 TYPE(FLD), INTENT(inout) :: sdjf ! input field related variables 268 INTEGER , OPTIONAL, INTENT(in ) :: Kmm ! ocean time level index 269 ! 270 INTEGER :: ja ! end of this record (in seconds) 271 !!---------------------------------------------------------------------- 272 ! 273 IF( ksecsbc > sdjf%nrec_a(2) ) THEN ! --> we need to update after data 274 275 ! find where is the new after record... (it is not necessary sdjf%nrec_a(1)+1 ) 276 ja = sdjf%nrec_a(1) 277 DO WHILE ( ksecsbc >= sdjf%nrecsec(ja) .AND. ja < sdjf%nreclast ) ! Warning: make sure ja <= sdjf%nreclast in this test 278 ja = ja + 1 279 END DO 280 IF( ksecsbc > sdjf%nrecsec(ja) ) ja = ja + 1 ! in case ksecsbc > sdjf%nrecsec(sdjf%nreclast) 281 282 ! if ln_tint and if the new after is not ja+1, we need also to update after data before the swap 283 ! so, after the swap, sdjf%nrec_b(2) will still be the closest value located just before ksecsbc 284 IF( sdjf%ln_tint .AND. ( ja > sdjf%nrec_a(1) + 1 .OR. sdjf%nrec_a(2) == nflag ) ) THEN 285 sdjf%nrec_a(:) = (/ ja-1, sdjf%nrecsec(ja-1) /) ! update nrec_a with before information 286 CALL fld_get( sdjf, Kmm ) ! read after data that will be used as before data 287 ENDIF 288 289 ! if after is in the next file... 290 IF( ja > sdjf%nreclast ) THEN 291 292 CALL fld_def( sdjf ) 293 IF( ksecsbc > sdjf%nrecsec(sdjf%nreclast) ) CALL fld_def( sdjf, ldnext = .TRUE. ) 294 CALL fld_clopn( sdjf ) ! open next file 295 296 ! find where is after in this new file 297 ja = 1 298 DO WHILE ( ksecsbc > sdjf%nrecsec(ja) .AND. ja < sdjf%nreclast ) 299 ja = ja + 1 300 END DO 301 IF( ksecsbc > sdjf%nrecsec(ja) ) ja = ja + 1 ! in case ksecsbc > sdjf%nrecsec(sdjf%nreclast) 302 303 IF( ja > sdjf%nreclast ) THEN 304 CALL ctl_stop( "STOP", "fld_def: need next-next file? we should not be there... file: "//TRIM(sdjf%clrootname) ) 500 305 ENDIF 501 ELSE ! no time interpolation 502 sdjf%nrec_a(1) = 1 503 sdjf%nrec_a(2) = NINT(rday) * nyear_len(1) + nsec1jan000 ! swap at the end of the year 504 sdjf%nrec_b(2) = nsec1jan000 ! beginning of the year (only for print) 505 ENDIF 506 ! 507 ! ! ============ ! 508 ELSEIF( NINT(sdjf%freqh) == -1 ) THEN ! monthly mean ! 509 ! ! ============ ! 510 ! 511 IF( sdjf%ln_tint ) THEN ! time interpolation, shift by 1/2 record 512 ! 513 ! INT( ztmp ) 514 ! /|\ 515 ! 1 | *---- 516 ! 0 |----( 517 ! |----+----|--> time 518 ! 0 /|\ 1 (nday/nmonth_len(nmonth)) 519 ! | 520 ! | 521 ! forcing record : nmonth 522 ! 523 ztmp = REAL( nsec_month, wp ) / ( REAL( nmonth_len(nmonth), wp ) * rday ) + 0.5 & 524 & + REAL( it_offset, wp ) / ( REAL( nmonth_len(nmonth), wp ) * rday ) 525 imth = nmonth + INT( ztmp ) - COUNT((/llbefore/)) 526 IF( sdjf%cltype == 'monthly' ) THEN ; sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/)) 527 ELSE ; sdjf%nrec_a(1) = imth 306 307 ! if ln_tint and if after is not the first record, we must (potentially again) update after data before the swap 308 IF( sdjf%ln_tint .AND. ja > 1 ) THEN 309 IF( sdjf%nrecsec(0) /= nflag ) THEN ! no trick used: after file is not the current file 310 sdjf%nrec_a(:) = (/ ja-1, sdjf%nrecsec(ja-1) /) ! update nrec_a with before information 311 CALL fld_get( sdjf, Kmm ) ! read after data that will be used as before data 312 ENDIF 528 313 ENDIF 529 sdjf%nrec_a(2) = nmonth_half( imth ) + nsec1jan000 ! swap at the middle of the month 530 ELSE ! no time interpolation 531 IF( sdjf%cltype == 'monthly' ) THEN ; sdjf%nrec_a(1) = 1 532 ELSE ; sdjf%nrec_a(1) = nmonth 533 ENDIF 534 sdjf%nrec_a(2) = nmonth_end(nmonth ) + nsec1jan000 ! swap at the end of the month 535 sdjf%nrec_b(2) = nmonth_end(nmonth-1) + nsec1jan000 ! beginning of the month (only for print) 536 ENDIF 537 ! 538 ! ! ================================ ! 539 ELSE ! higher frequency mean (in hours) 540 ! ! ================================ ! 541 ! 542 ifreq_sec = NINT( sdjf%freqh * 3600. ) ! frequency mean (in seconds) 543 IF( sdjf%cltype(1:4) == 'week' ) isec_week = ksec_week( sdjf%cltype(6:8) ) ! since the first day of the current week 544 ! number of second since the beginning of the file 545 IF( sdjf%cltype == 'monthly' ) THEN ; ztmp = REAL(nsec_month,wp) ! since the first day of the current month 546 ELSEIF( sdjf%cltype(1:4) == 'week' ) THEN ; ztmp = REAL(isec_week ,wp) ! since the first day of the current week 547 ELSEIF( sdjf%cltype == 'daily' ) THEN ; ztmp = REAL(nsec_day ,wp) ! since 00h of the current day 548 ELSE ; ztmp = REAL(nsec_year ,wp) ! since 00h on Jan 1 of the current year 549 ENDIF 550 ztmp = ztmp + 0.5 * REAL(kn_fsbc - 1, wp) * rdt + REAL( it_offset, wp ) ! centrered in the middle of sbc time step 551 ztmp = ztmp + 0.01 * rdt ! avoid truncation error 552 IF( sdjf%ln_tint ) THEN ! time interpolation, shift by 1/2 record 553 ! 554 ! INT( ztmp/ifreq_sec + 0.5 ) 555 ! /|\ 556 ! 2 | *-----( 557 ! 1 | *-----( 558 ! 0 |--( 559 ! |--+--|--+--|--+--|--> time 560 ! 0 /|\ 1 /|\ 2 /|\ 3 (ztmp/ifreq_sec) 561 ! | | | 562 ! | | | 563 ! forcing record : 1 2 3 564 ! 565 ztmp= ztmp / REAL(ifreq_sec, wp) + 0.5 566 ELSE ! no time interpolation 567 ! 568 ! INT( ztmp/ifreq_sec ) 569 ! /|\ 570 ! 2 | *-----( 571 ! 1 | *-----( 572 ! 0 |-----( 573 ! |--+--|--+--|--+--|--> time 574 ! 0 /|\ 1 /|\ 2 /|\ 3 (ztmp/ifreq_sec) 575 ! | | | 576 ! | | | 577 ! forcing record : 1 2 3 578 ! 579 ztmp= ztmp / REAL(ifreq_sec, wp) 580 ENDIF 581 sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/)) ! record number to be read 582 583 iendrec = ifreq_sec * sdjf%nrec_a(1) + nsec1jan000 ! end of this record (in second) 584 ! add the number of seconds between 00h Jan 1 and the end of previous month/week/day (ok if nmonth=1) 585 IF( sdjf%cltype == 'monthly' ) iendrec = iendrec + NINT(rday) * SUM(nmonth_len(1:nmonth -1)) 586 IF( sdjf%cltype(1:4) == 'week' ) iendrec = iendrec + ( nsec_year - isec_week ) 587 IF( sdjf%cltype == 'daily' ) iendrec = iendrec + NINT(rday) * ( nday_year - 1 ) 588 IF( sdjf%ln_tint ) THEN 589 sdjf%nrec_a(2) = iendrec - ifreq_sec / 2 ! swap at the middle of the record 314 315 ENDIF 316 317 IF( sdjf%ln_tint ) THEN 318 ! Swap data 319 sdjf%nrec_b(:) = sdjf%nrec_a(:) ! swap before record informations 320 sdjf%rotn(1) = sdjf%rotn(2) ! swap before rotate informations 321 sdjf%fdta(:,:,:,1) = sdjf%fdta(:,:,:,2) ! swap before record field 590 322 ELSE 591 sdjf%nrec_a(2) = iendrec ! swap at the end of the record 592 sdjf%nrec_b(2) = iendrec - ifreq_sec ! beginning of the record (only for print) 593 ENDIF 594 ! 595 ENDIF 596 ! 597 IF( .NOT. sdjf%ln_tint ) sdjf%nrec_a(2) = sdjf%nrec_a(2) - 1 ! last second belongs to bext record : *----( 598 ! 599 END SUBROUTINE fld_rec 323 sdjf%nrec_b(:) = (/ ja-1, sdjf%nrecsec(ja-1) /) ! only for print 324 ENDIF 325 326 ! read new after data 327 sdjf%nrec_a(:) = (/ ja, sdjf%nrecsec(ja) /) ! update nrec_a as it is used by fld_get 328 CALL fld_get( sdjf, Kmm ) ! read after data (with nrec_a informations) 329 330 ENDIF 331 ! 332 END SUBROUTINE fld_update 600 333 601 334 … … 606 339 !! ** Purpose : read the data 607 340 !!---------------------------------------------------------------------- 608 TYPE(FLD) ,INTENT(inout) :: sdjf ! input field related variables609 INTEGER , INTENT(in), OPTIONAL :: Kmm! ocean time level index341 TYPE(FLD), INTENT(inout) :: sdjf ! input field related variables 342 INTEGER , OPTIONAL, INTENT(in ) :: Kmm ! ocean time level index 610 343 ! 611 344 INTEGER :: ipk ! number of vertical levels of sdjf%fdta ( 2D: ipk=1 ; 3D: ipk=jpk ) … … 621 354 IF( ASSOCIATED(sdjf%imap) ) THEN 622 355 IF( sdjf%ln_tint ) THEN ; CALL fld_map( sdjf%num, sdjf%clvar, sdjf%fdta(:,:,:,2), sdjf%nrec_a(1), & 623 & sdjf%imap, sdjf%igrd, sdjf%ibdy, sdjf%ltotvel, sdjf%lzint )356 & sdjf%imap, sdjf%igrd, sdjf%ibdy, sdjf%ltotvel, sdjf%lzint, Kmm ) 624 357 ELSE ; CALL fld_map( sdjf%num, sdjf%clvar, sdjf%fnow(:,:,: ), sdjf%nrec_a(1), & 625 & sdjf%imap, sdjf%igrd, sdjf%ibdy, sdjf%ltotvel, sdjf%lzint )358 & sdjf%imap, sdjf%igrd, sdjf%ibdy, sdjf%ltotvel, sdjf%lzint, Kmm ) 626 359 ENDIF 627 360 ELSE IF( LEN(TRIM(sdjf%wgtname)) > 0 ) THEN … … 679 412 END SUBROUTINE fld_get 680 413 414 681 415 SUBROUTINE fld_map( knum, cdvar, pdta, krec, kmap, kgrd, kbdy, ldtotvel, ldzint, Kmm ) 682 416 !!--------------------------------------------------------------------- … … 761 495 762 496 CALL iom_getatt(knum, '_FillValue', zfv, cdvar=cdvar ) 763 CALL fld_bdy_interp(zdta_read, zdta_read_z, zdta_read_dz, pdta, kgrd, kbdy, zfv, ldtotvel )497 CALL fld_bdy_interp(zdta_read, zdta_read_z, zdta_read_dz, pdta, kgrd, kbdy, zfv, ldtotvel, Kmm) 764 498 DEALLOCATE( zdta_read, zdta_read_z, zdta_read_dz ) 765 499 … … 867 601 jj = idx_bdy(kbdy)%nbj(jb,kgrd) 868 602 zh = SUM(pdta_read_dz(jb,1,:) ) 869 !870 ! Warnings to flag differences in the input and model topgraphy - is this useful/necessary?871 SELECT CASE( kgrd )872 CASE(1)873 IF( ABS( (zh - ht(ji,jj)) / ht(ji,jj)) * tmask(ji,jj,1) > 0.01_wp ) THEN874 WRITE(ctmp1,"(I10.10)") jb875 CALL ctl_warn('fld_bdy_interp: T depths differ between grids at BDY point '//TRIM(ctmp1)//' by more than 1%')876 ! IF(lwp) WRITE(numout,*) 'DEPTHT', zh, sum(e3t(ji,jj,:,Kmm), mask=tmask(ji,jj,:)==1), ht(ji,jj), jb, jb, ji, jj877 ENDIF878 CASE(2)879 IF( ABS( (zh - hu(ji,jj,Kmm)) * r1_hu(ji,jj,Kmm)) * umask(ji,jj,1) > 0.01_wp ) THEN880 WRITE(ctmp1,"(I10.10)") jb881 CALL ctl_warn('fld_bdy_interp: U depths differ between grids at BDY point '//TRIM(ctmp1)//' by more than 1%')882 ! IF(lwp) WRITE(numout,*) 'DEPTHU', zh, SUM(e3u(ji,jj,:,Kmm), mask=umask(ji,jj,:)==1), SUM(umask(ji,jj,:)), &883 ! & hu(ji,jj,Kmm), jb, jb, ji, jj, narea-1, pdta_read(jb,1,:)884 ENDIF885 CASE(3)886 IF( ABS( (zh - hv(ji,jj,Kmm)) * r1_hv(ji,jj,Kmm)) * vmask(ji,jj,1) > 0.01_wp ) THEN887 WRITE(ctmp1,"(I10.10)") jb888 CALL ctl_warn('fld_bdy_interp: V depths differ between grids at BDY point '//TRIM(ctmp1)//' by more than 1%')889 ENDIF890 END SELECT891 603 ! 892 604 SELECT CASE( kgrd ) … … 955 667 ENDDO 956 668 DO jk = 1, jpk ! calculate transport on model grid 957 ztrans_new = ztrans_new + pdta(jb,1,jk ) * 669 ztrans_new = ztrans_new + pdta(jb,1,jk ) * e3u(ji,jj,jk,Kmm ) * umask(ji,jj,jk) 958 670 ENDDO 959 671 DO jk = 1, jpk ! make transport correction … … 1033 745 sd(ju)%fdta(:,:,jk,jn) = utmp(:,:) ; sd(iv)%fdta(:,:,jk,jn) = vtmp(:,:) 1034 746 ELSE 1035 CALL rot_rep( sd(ju)%fnow(:,:,jk ), sd(iv)%fnow(:,:,jk), 'T', 'en->i', utmp(:,:) )1036 CALL rot_rep( sd(ju)%fnow(:,:,jk ), sd(iv)%fnow(:,:,jk), 'T', 'en->j', vtmp(:,:) )747 CALL rot_rep( sd(ju)%fnow(:,:,jk ), sd(iv)%fnow(:,:,jk ), 'T', 'en->i', utmp(:,:) ) 748 CALL rot_rep( sd(ju)%fnow(:,:,jk ), sd(iv)%fnow(:,:,jk ), 'T', 'en->j', vtmp(:,:) ) 1037 749 sd(ju)%fnow(:,:,jk ) = utmp(:,:) ; sd(iv)%fnow(:,:,jk ) = vtmp(:,:) 1038 750 ENDIF … … 1050 762 1051 763 1052 SUBROUTINE fld_clopn( sdjf, kyear, kmonth, kday, ldstop ) 764 SUBROUTINE fld_def( sdjf, ldprev, ldnext ) 765 !!--------------------------------------------------------------------- 766 !! *** ROUTINE fld_def *** 767 !! 768 !! ** Purpose : define the record(s) of the file and its name 769 !!---------------------------------------------------------------------- 770 TYPE(FLD) , INTENT(inout) :: sdjf ! input field related variables 771 LOGICAL, OPTIONAL, INTENT(in ) :: ldprev ! 772 LOGICAL, OPTIONAL, INTENT(in ) :: ldnext ! 773 ! 774 INTEGER :: jt 775 INTEGER :: idaysec ! number of seconds in 1 day = NINT(rday) 776 INTEGER :: iyr, imt, idy, isecwk 777 INTEGER :: indexyr, indexmt 778 INTEGER :: ireclast 779 INTEGER :: ishift, istart 780 INTEGER, DIMENSION(2) :: isave 781 REAL(wp) :: zfreqs 782 LOGICAL :: llprev, llnext, llstop 783 LOGICAL :: llprevmt, llprevyr 784 LOGICAL :: llnextmt, llnextyr 785 !!---------------------------------------------------------------------- 786 idaysec = NINT(rday) 787 ! 788 IF( PRESENT(ldprev) ) THEN ; llprev = ldprev 789 ELSE ; llprev = .FALSE. 790 ENDIF 791 IF( PRESENT(ldnext) ) THEN ; llnext = ldnext 792 ELSE ; llnext = .FALSE. 793 ENDIF 794 795 ! current file parameters 796 IF( sdjf%cltype(1:4) == 'week' ) THEN ! find the day of the beginning of the current week 797 isecwk = ksec_week( sdjf%cltype(6:8) ) ! seconds between the beginning of the week and half of current time step 798 llprevmt = isecwk > nsec_month ! longer time since beginning of the current week than the current month 799 llprevyr = llprevmt .AND. nmonth == 1 800 iyr = nyear - COUNT((/llprevyr/)) 801 imt = nmonth - COUNT((/llprevmt/)) + 12 * COUNT((/llprevyr/)) 802 idy = nday + nmonth_len(nmonth-1) * COUNT((/llprevmt/)) - isecwk / idaysec 803 isecwk = nsec_year - isecwk ! seconds between 00h jan 1st of current year and current week beginning 804 ELSE 805 iyr = nyear 806 imt = nmonth 807 idy = nday 808 isecwk = 0 809 ENDIF 810 811 ! previous file parameters 812 IF( llprev ) THEN 813 IF( sdjf%cltype(1:4) == 'week' ) THEN ! find the day of the beginning of previous week 814 isecwk = isecwk + 7 * idaysec ! seconds between the beginning of previous week and half of the time step 815 llprevmt = isecwk > nsec_month ! longer time since beginning of the previous week than the current month 816 llprevyr = llprevmt .AND. nmonth == 1 817 iyr = nyear - COUNT((/llprevyr/)) 818 imt = nmonth - COUNT((/llprevmt/)) + 12 * COUNT((/llprevyr/)) 819 idy = nday + nmonth_len(nmonth-1) * COUNT((/llprevmt/)) - isecwk / idaysec 820 isecwk = nsec_year - isecwk ! seconds between 00h jan 1st of current year and previous week beginning 821 ELSE 822 idy = nday - COUNT((/ sdjf%cltype == 'daily' /)) 823 imt = nmonth - COUNT((/ sdjf%cltype == 'monthly' .OR. idy == 0 /)) 824 iyr = nyear - COUNT((/ sdjf%cltype == 'yearly' .OR. imt == 0 /)) 825 IF( idy == 0 ) idy = nmonth_len(imt) 826 IF( imt == 0 ) imt = 12 827 isecwk = 0 828 ENDIF 829 ENDIF 830 831 ! next file parameters 832 IF( llnext ) THEN 833 IF( sdjf%cltype(1:4) == 'week' ) THEN ! find the day of the beginning of next week 834 isecwk = 7 * idaysec - isecwk ! seconds between half of the time step and the beginning of next week 835 llnextmt = isecwk > ( nmonth_len(nmonth)*idaysec - nsec_month ) ! larger than the seconds to the end of the month 836 llnextyr = llnextmt .AND. nmonth == 12 837 iyr = nyear + COUNT((/llnextyr/)) 838 imt = nmonth + COUNT((/llnextmt/)) - 12 * COUNT((/llnextyr/)) 839 idy = nday - nmonth_len(nmonth) * COUNT((/llnextmt/)) + isecwk / idaysec + 1 840 isecwk = nsec_year + isecwk ! seconds between 00h jan 1st of current year and next week beginning 841 ELSE 842 idy = nday + COUNT((/ sdjf%cltype == 'daily' /)) 843 imt = nmonth + COUNT((/ sdjf%cltype == 'monthly' .OR. idy > nmonth_len(nmonth) /)) 844 iyr = nyear + COUNT((/ sdjf%cltype == 'yearly' .OR. imt == 13 /)) 845 IF( idy > nmonth_len(nmonth) ) idy = 1 846 IF( imt == 13 ) imt = 1 847 isecwk = 0 848 ENDIF 849 ENDIF 850 ! 851 ! find the last record to be read -> update sdjf%nreclast 852 indexyr = iyr - nyear + 1 ! which year are we looking for? previous(0), current(1) or next(2)? 853 indexmt = imt + 12 * ( indexyr - 1 ) ! which month are we looking for (relatively to current year)? 854 ! 855 ! Last record to be read in the current file 856 ! Predefine the number of record in the file according of its type. 857 ! We could compare this number with the number of records in the file and make a stop if the 2 numbers do not match... 858 ! However this would be much less fexible (e.g. for tests) and will force to rewite input files according to nleapy... 859 IF ( NINT(sdjf%freqh) == -12 ) THEN ; ireclast = 1 ! yearly mean: consider only 1 record 860 ELSEIF( NINT(sdjf%freqh) == -1 ) THEN ! monthly mean: 861 IF( sdjf%cltype == 'monthly' ) THEN ; ireclast = 1 ! consider that the file has 1 record 862 ELSE ; ireclast = 12 ! consider that the file has 12 record 863 ENDIF 864 ELSE ! higher frequency mean (in hours) 865 IF( sdjf%cltype == 'monthly' ) THEN ; ireclast = NINT( 24. * REAL(nmonth_len(indexmt), wp) / sdjf%freqh ) 866 ELSEIF( sdjf%cltype(1:4) == 'week' ) THEN ; ireclast = NINT( 24. * 7. / sdjf%freqh ) 867 ELSEIF( sdjf%cltype == 'daily' ) THEN ; ireclast = NINT( 24. / sdjf%freqh ) 868 ELSE ; ireclast = NINT( 24. * REAL( nyear_len(indexyr), wp) / sdjf%freqh ) 869 ENDIF 870 ENDIF 871 872 sdjf%nreclast = ireclast 873 ! Allocate arrays for beginning/middle/end of each record (seconds since Jan. 1st 00h of nit000 year) 874 IF( ALLOCATED(sdjf%nrecsec) ) DEALLOCATE( sdjf%nrecsec ) 875 ALLOCATE( sdjf%nrecsec( 0:ireclast ) ) 876 ! 877 IF ( NINT(sdjf%freqh) == -12 ) THEN ! yearly mean and yearly file 878 SELECT CASE( indexyr ) 879 CASE(0) ; sdjf%nrecsec(0) = nsec1jan000 - nyear_len( 0 ) * idaysec 880 CASE(1) ; sdjf%nrecsec(0) = nsec1jan000 881 CASE(2) ; sdjf%nrecsec(0) = nsec1jan000 + nyear_len( 1 ) * idaysec 882 ENDSELECT 883 sdjf%nrecsec(1) = sdjf%nrecsec(0) + nyear_len( indexyr ) * idaysec 884 ELSEIF( NINT(sdjf%freqh) == -1 ) THEN ! monthly mean: 885 IF( sdjf%cltype == 'monthly' ) THEN ! monthly file 886 sdjf%nrecsec(0 ) = nsec1jan000 + nmonth_beg(indexmt ) 887 sdjf%nrecsec(1 ) = nsec1jan000 + nmonth_beg(indexmt+1) 888 ELSE ! yearly file 889 ishift = 12 * ( indexyr - 1 ) 890 sdjf%nrecsec(0:12) = nsec1jan000 + nmonth_beg(1+ishift:13+ishift) 891 ENDIF 892 ELSE ! higher frequency mean (in hours) 893 IF( sdjf%cltype == 'monthly' ) THEN ; istart = nsec1jan000 + nmonth_beg(indexmt) 894 ELSEIF( sdjf%cltype(1:4) == 'week' ) THEN ; istart = nsec1jan000 + isecwk 895 ELSEIF( sdjf%cltype == 'daily' ) THEN ; istart = nsec1jan000 + nmonth_beg(indexmt) + ( idy - 1 ) * idaysec 896 ELSEIF( indexyr == 0 ) THEN ; istart = nsec1jan000 - nyear_len( 0 ) * idaysec 897 ELSEIF( indexyr == 2 ) THEN ; istart = nsec1jan000 + nyear_len( 1 ) * idaysec 898 ELSE ; istart = nsec1jan000 899 ENDIF 900 zfreqs = sdjf%freqh * rhhmm * rmmss 901 DO jt = 0, sdjf%nreclast 902 sdjf%nrecsec(jt) = istart + NINT( zfreqs * REAL(jt,wp) ) 903 END DO 904 ENDIF 905 ! 906 IF( sdjf%ln_tint ) THEN ! record time defined in the middle of the record 907 sdjf%nrecsec(1:sdjf%nreclast) = 0.5 * ( sdjf%nrecsec(0:sdjf%nreclast-1) + sdjf%nrecsec(1:sdjf%nreclast) ) 908 END IF 909 ! 910 sdjf%clname = fld_filename( sdjf, idy, imt, iyr ) 911 ! 912 END SUBROUTINE fld_def 913 914 915 SUBROUTINE fld_clopn( sdjf ) 1053 916 !!--------------------------------------------------------------------- 1054 917 !! *** ROUTINE fld_clopn *** 1055 918 !! 1056 !! ** Purpose : update the file name and close/open the files 1057 !!---------------------------------------------------------------------- 1058 TYPE(FLD) , INTENT(inout) :: sdjf ! input field related variables 1059 INTEGER, OPTIONAL, INTENT(in ) :: kyear ! year value 1060 INTEGER, OPTIONAL, INTENT(in ) :: kmonth ! month value 1061 INTEGER, OPTIONAL, INTENT(in ) :: kday ! day value 1062 LOGICAL, OPTIONAL, INTENT(in ) :: ldstop ! stop if open to read a non-existing file (default = .TRUE.) 1063 ! 1064 LOGICAL :: llprevyr ! are we reading previous year file? 1065 LOGICAL :: llprevmth ! are we reading previous month file? 1066 INTEGER :: iyear, imonth, iday ! first day of the current file in yyyy mm dd 1067 INTEGER :: isec_week ! number of seconds since start of the weekly file 1068 INTEGER :: indexyr ! year undex (O/1/2: previous/current/next) 1069 REAL(wp) :: zyear_len, zmonth_len ! length (days) of iyear and imonth ! 1070 CHARACTER(len = 256) :: clname ! temporary file name 1071 !!---------------------------------------------------------------------- 1072 IF( PRESENT(kyear) ) THEN ! use given values 1073 iyear = kyear 1074 imonth = kmonth 1075 iday = kday 1076 IF( sdjf%cltype(1:4) == 'week' ) THEN ! find the day of the beginning of the week 1077 isec_week = ksec_week( sdjf%cltype(6:8) )- (86400 * 8 ) 1078 llprevmth = isec_week > nsec_month ! longer time since beginning of the week than the month 1079 llprevyr = llprevmth .AND. nmonth == 1 1080 iyear = nyear - COUNT((/llprevyr /)) 1081 imonth = nmonth - COUNT((/llprevmth/)) + 12 * COUNT((/llprevyr /)) 1082 iday = nday + nmonth_len(nmonth-1) * COUNT((/llprevmth/)) - isec_week / NINT(rday) 1083 ENDIF 1084 ELSE ! use current day values 1085 IF( sdjf%cltype(1:4) == 'week' ) THEN ! find the day of the beginning of the week 1086 isec_week = ksec_week( sdjf%cltype(6:8) ) ! second since the beginning of the week 1087 llprevmth = isec_week > nsec_month ! longer time since beginning of the week than the month 1088 llprevyr = llprevmth .AND. nmonth == 1 1089 ELSE 1090 isec_week = 0 1091 llprevmth = .FALSE. 1092 llprevyr = .FALSE. 1093 ENDIF 1094 iyear = nyear - COUNT((/llprevyr /)) 1095 imonth = nmonth - COUNT((/llprevmth/)) + 12 * COUNT((/llprevyr /)) 1096 iday = nday + nmonth_len(nmonth-1) * COUNT((/llprevmth/)) - isec_week / NINT(rday) 1097 ENDIF 1098 1099 ! build the new filename if not climatological data 1100 clname=TRIM(sdjf%clrootname) 1101 ! 1102 ! note that sdjf%ln_clim is is only acting on the presence of the year in the file name 1103 IF( .NOT. sdjf%ln_clim ) THEN 1104 WRITE(clname, '(a,"_y",i4.4)' ) TRIM( sdjf%clrootname ), iyear ! add year 1105 IF( sdjf%cltype /= 'yearly' ) WRITE(clname, '(a,"m" ,i2.2)' ) TRIM( clname ), imonth ! add month 1106 ELSE 1107 ! build the new filename if climatological data 1108 IF( sdjf%cltype /= 'yearly' ) WRITE(clname, '(a,"_m",i2.2)' ) TRIM( sdjf%clrootname ), imonth ! add month 1109 ENDIF 1110 IF( sdjf%cltype == 'daily' .OR. sdjf%cltype(1:4) == 'week' ) & 1111 & WRITE(clname, '(a,"d" ,i2.2)' ) TRIM( clname ), iday ! add day 1112 ! 1113 IF( TRIM(clname) /= TRIM(sdjf%clname) .OR. sdjf%num == 0 ) THEN ! new file to be open 1114 ! 1115 sdjf%clname = TRIM(clname) 1116 IF( sdjf%num /= 0 ) CALL iom_close( sdjf%num ) ! close file if already open 1117 CALL iom_open( sdjf%clname, sdjf%num, ldstop = ldstop, ldiof = LEN(TRIM(sdjf%wgtname)) > 0 ) 1118 ! 1119 ! find the last record to be read -> update sdjf%nreclast 1120 indexyr = iyear - nyear + 1 1121 zyear_len = REAL(nyear_len( indexyr ), wp) 1122 SELECT CASE ( indexyr ) 1123 CASE ( 0 ) ; zmonth_len = 31. ! previous year -> imonth = 12 1124 CASE ( 1 ) ; zmonth_len = REAL(nmonth_len(imonth), wp) 1125 CASE ( 2 ) ; zmonth_len = 31. ! next year -> imonth = 1 1126 END SELECT 1127 ! 1128 ! last record to be read in the current file 1129 IF ( sdjf%freqh == -12. ) THEN ; sdjf%nreclast = 1 ! yearly mean 1130 ELSEIF( sdjf%freqh == -1. ) THEN ! monthly mean 1131 IF( sdjf%cltype == 'monthly' ) THEN ; sdjf%nreclast = 1 1132 ELSE ; sdjf%nreclast = 12 1133 ENDIF 1134 ELSE ! higher frequency mean (in hours) 1135 IF( sdjf%cltype == 'monthly' ) THEN ; sdjf%nreclast = NINT( 24. * zmonth_len / sdjf%freqh ) 1136 ELSEIF( sdjf%cltype(1:4) == 'week' ) THEN ; sdjf%nreclast = NINT( 24. * 7. / sdjf%freqh ) 1137 ELSEIF( sdjf%cltype == 'daily' ) THEN ; sdjf%nreclast = NINT( 24. / sdjf%freqh ) 1138 ELSE ; sdjf%nreclast = NINT( 24. * zyear_len / sdjf%freqh ) 1139 ENDIF 1140 ENDIF 919 !! ** Purpose : close/open the files 920 !!---------------------------------------------------------------------- 921 TYPE(FLD) , INTENT(inout) :: sdjf ! input field related variables 922 ! 923 INTEGER, DIMENSION(2) :: isave 924 LOGICAL :: llprev, llnext, llstop 925 !!---------------------------------------------------------------------- 926 ! 927 llprev = sdjf%nrecsec(sdjf%nreclast) < nsec000_1jan000 ! file ends before the beginning of the job -> file may not exist 928 llnext = sdjf%nrecsec( 0 ) > nsecend_1jan000 ! file begins after the end of the job -> file may not exist 929 930 llstop = sdjf%ln_clim .OR. .NOT. ( llprev .OR. llnext ) 931 932 IF( sdjf%num <= 0 .OR. .NOT. sdjf%ln_clim ) THEN 933 IF( sdjf%num > 0 ) CALL iom_close( sdjf%num ) ! close file if already open 934 CALL iom_open( sdjf%clname, sdjf%num, ldstop = llstop, ldiof = LEN(TRIM(sdjf%wgtname)) > 0 ) 935 ENDIF 936 ! 937 IF( sdjf%num <= 0 .AND. .NOT. llstop ) THEN ! file not found but we do accept this... 938 ! 939 IF( llprev ) THEN ! previous file does not exist : go back to current and accept to read only the first record 940 CALL ctl_warn('previous file: '//TRIM(sdjf%clname)//' not found -> go back to current year/month/week/day file') 941 isave(1:2) = sdjf%nrecsec(sdjf%nreclast-1:sdjf%nreclast) ! save previous file info 942 CALL fld_def( sdjf ) ! go back to current file 943 sdjf%nreclast = 1 ! force to use only the first record (do as if other were not existing...) 944 sdjf%nrecsec(0:1) = isave(1:2) 945 ENDIF 946 ! 947 IF( llnext ) THEN ! next file does not exist : go back to current and accept to read only the last record 948 CALL ctl_warn('next file: '//TRIM(sdjf%clname)//' not found -> go back to current year/month/week/day file') 949 isave(1:2) = sdjf%nrecsec(0:1) ! save next file info 950 CALL fld_def( sdjf ) ! go back to current file 951 ! -> read last record but keep record info from the first record of next file 952 sdjf%nrecsec(sdjf%nreclast-1:sdjf%nreclast) = isave(1:2) 953 sdjf%nrecsec(0:sdjf%nreclast-2) = nflag 954 ENDIF 955 ! 956 CALL iom_open( sdjf%clname, sdjf%num, ldiof = LEN(TRIM(sdjf%wgtname)) > 0 ) 1141 957 ! 1142 958 ENDIF … … 1320 1136 CALL iom_open( sd%clname, inum, ldiof = LEN(TRIM(sd%wgtname)) > 0 ) 1321 1137 1322 !! get dimensions 1323 !!GS: we consider 2D data as 3D data with vertical dim size = 1 1324 !IF( SIZE(sd%fnow, 3) > 1 ) THEN 1138 !! get dimensions: we consider 2D data as 3D data with vertical dim size = 1 1325 1139 IF( SIZE(sd%fnow, 3) > 0 ) THEN 1326 1140 ALLOCATE( ddims(4) ) … … 1645 1459 1646 1460 ref_wgts(kw)%fly_dta(:,:,:) = 0.0 1647 !!GS: we consider 2D data as 3D data with vertical dim size = 1 1648 !SELECT CASE( SIZE(ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:),3) ) 1649 !CASE(1) 1650 ! CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,1), nrec, rec1, recn) 1651 !CASE DEFAULT 1652 CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:), nrec, rec1, recn) 1653 !END SELECT 1461 CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:), nrec, rec1, recn) 1654 1462 ENDIF 1655 1463 … … 1695 1503 IF( jpi1 == 2 ) THEN 1696 1504 rec1(1) = ref_wgts(kw)%ddims(1) - ref_wgts(kw)%overlap 1697 !!GS: we consider 2D data as 3D data with vertical dim size = 1 1698 !SELECT CASE( SIZE( ref_wgts(kw)%col(:,jpj1:jpj2,:),3) ) 1699 !CASE(1) 1700 ! CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,1), nrec, rec1, recn) 1701 !CASE DEFAULT 1702 CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,:), nrec, rec1, recn) 1703 !END SELECT 1505 CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,:), nrec, rec1, recn) 1704 1506 ref_wgts(kw)%fly_dta(jpi1-1,jpj1:jpj2,:) = ref_wgts(kw)%col(1,jpj1:jpj2,:) 1705 1507 ENDIF 1706 1508 IF( jpi2 + jpimin - 1 == ref_wgts(kw)%ddims(1)+1 ) THEN 1707 1509 rec1(1) = 1 + ref_wgts(kw)%overlap 1708 !!GS: we consider 2D data as 3D data with vertical dim size = 1 1709 !SELECT CASE( SIZE( ref_wgts(kw)%col(:,jpj1:jpj2,:),3) ) 1710 !CASE(1) 1711 ! CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,1), nrec, rec1, recn) 1712 !CASE DEFAULT 1713 CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,:), nrec, rec1, recn) 1714 !END SELECT 1510 CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,:), nrec, rec1, recn) 1715 1511 ref_wgts(kw)%fly_dta(jpi2+1,jpj1:jpj2,:) = ref_wgts(kw)%col(1,jpj1:jpj2,:) 1716 1512 ENDIF … … 1759 1555 1760 1556 1557 FUNCTION fld_filename( sdjf, kday, kmonth, kyear ) 1558 !!--------------------------------------------------------------------- 1559 !! *** FUNCTION fld_filename *** 1560 !! 1561 !! ** Purpose : define the filename according to a given date 1562 !!--------------------------------------------------------------------- 1563 TYPE(FLD), INTENT(in) :: sdjf ! input field related variables 1564 INTEGER , INTENT(in) :: kday, kmonth, kyear 1565 ! 1566 CHARACTER(len = 256) :: clname, fld_filename 1567 !!--------------------------------------------------------------------- 1568 1569 1570 ! build the new filename if not climatological data 1571 clname=TRIM(sdjf%clrootname) 1572 ! 1573 ! note that sdjf%ln_clim is is only acting on the presence of the year in the file name 1574 IF( .NOT. sdjf%ln_clim ) THEN 1575 WRITE(clname, '(a,"_y",i4.4)' ) TRIM( sdjf%clrootname ), kyear ! add year 1576 IF( sdjf%cltype /= 'yearly' ) WRITE(clname, '(a, "m",i2.2)' ) TRIM( clname ), kmonth ! add month 1577 ELSE 1578 ! build the new filename if climatological data 1579 IF( sdjf%cltype /= 'yearly' ) WRITE(clname, '(a,"_m",i2.2)' ) TRIM( sdjf%clrootname ), kmonth ! add month 1580 ENDIF 1581 IF( sdjf%cltype == 'daily' .OR. sdjf%cltype(1:4) == 'week' ) & 1582 & WRITE(clname, '(a,"d" ,i2.2)' ) TRIM( clname ), kday ! add day 1583 1584 fld_filename = clname 1585 1586 END FUNCTION fld_filename 1587 1588 1761 1589 FUNCTION ksec_week( cdday ) 1762 1590 !!--------------------------------------------------------------------- 1763 !! *** FUNCTION ks hift_week ***1764 !! 1765 !! ** Purpose : return the first 3 letters of the first day of the weekly file1591 !! *** FUNCTION ksec_week *** 1592 !! 1593 !! ** Purpose : seconds between 00h of the beginning of the week and half of the current time step 1766 1594 !!--------------------------------------------------------------------- 1767 1595 CHARACTER(len=*), INTENT(in) :: cdday ! first 3 letters of the first day of the weekly file … … 1779 1607 ishift = ijul * NINT(rday) 1780 1608 ! 1781 ksec_week = nsec_ week+ ishift1609 ksec_week = nsec_monday + ishift 1782 1610 ksec_week = MOD( ksec_week, 7*NINT(rday) ) 1783 1611 ! -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/step.F90
r12205 r12250 121 121 IF( ln_tide ) CALL tide_update( kstp ) ! update tide potential 122 122 IF( ln_apr_dyn ) CALL sbc_apr ( kstp ) ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib) 123 IF( ln_bdy ) CALL bdy_dta ( kstp, Nnn, kt_offset = +1) ! update dynamic & tracer data at open boundaries123 IF( ln_bdy ) CALL bdy_dta ( kstp, Nnn, pt_offset = 1. ) ! update dynamic & tracer data at open boundaries 124 124 IF( ln_isf ) CALL isf_stp ( kstp, Nnn ) 125 125 CALL sbc ( kstp, Nbb, Nnn ) ! Sea Boundary Condition (including sea-ice) -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/OFF/dtadyn.F90
r12236 r12250 284 284 ! Open file for each variable to get his number of dimension 285 285 DO ifpr = 1, jfld 286 CALL fld_clopn( sf_dyn(ifpr), nyear, nmonth, nday ) 286 CALL fld_def( sf_dyn(ifpr) ) 287 CALL iom_open( sf_dyn(ifpr)%clname, sf_dyn(ifpr)%num ) 287 288 idv = iom_varid( sf_dyn(ifpr)%num , slf_d(ifpr)%clvar ) ! id of the variable sdjf%clvar 288 289 idimv = iom_file ( sf_dyn(ifpr)%num )%ndims(idv) ! number of dimension for variable sdjf%clvar 289 IF( sf_dyn(ifpr)%num /= 0 ) CALL iom_close( sf_dyn(ifpr)%num )! close file if already open290 CALL iom_close( sf_dyn(ifpr)%num ) ! close file if already open 290 291 ierr1=0 291 292 IF( idimv == 3 ) THEN ! 2D variable … … 512 513 ! Open file for each variable to get his number of dimension 513 514 DO ifpr = 1, jfld 514 CALL fld_clopn( sf_dyn(ifpr), nyear, nmonth, nday ) 515 CALL fld_def( sf_dyn(ifpr) ) 516 CALL iom_open( sf_dyn(ifpr)%clname, sf_dyn(ifpr)%num ) 515 517 idv = iom_varid( sf_dyn(ifpr)%num , slf_d(ifpr)%clvar ) ! id of the variable sdjf%clvar 516 518 idimv = iom_file ( sf_dyn(ifpr)%num )%ndims(idv) ! number of dimension for variable sdjf%clvar 517 IF( sf_dyn(ifpr)%num /= 0 ) CALL iom_close( sf_dyn(ifpr)%num )! close file if already open519 CALL iom_close( sf_dyn(ifpr)%num ) ! close file if already open 518 520 ierr1=0 519 521 IF( idimv == 3 ) THEN ! 2D variable -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/SAS/step.F90
r11949 r12250 102 102 ! This is not clean and should be changed in the future. 103 103 ! ==> 104 IF( ln_bdy ) CALL bdy_dta( kstp, Nnn, kt_offset=+1) ! update dynamic & tracer data at open boundaries104 IF( ln_bdy ) CALL bdy_dta( kstp, Nnn, pt_offset=1. ) ! update dynamic & tracer data at open boundaries 105 105 CALL sbc ( kstp, Nbb, Nnn ) ! Sea Boundary Condition (including sea-ice) 106 106 -
NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/trcbc.F90
r12193 r12250 367 367 IF( PRESENT(jit) ) THEN 368 368 ! 369 ! OPEN boundary conditions (use kt_offset=+1as they are applied at the end of the step)369 ! OPEN boundary conditions (use pt_offset=1. as they are applied at the end of the step) 370 370 IF( nb_trcobc > 0 ) THEN 371 371 if (lwp) write(numout,'(a,i5,a,i10)') ' reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 372 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kit=jit, kt_offset=+1)372 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kit=jit, pt_offset=1.) 373 373 ENDIF 374 374 ! … … 387 387 ELSE 388 388 ! 389 ! OPEN boundary conditions (use kt_offset=+1as they are applied at the end of the step)389 ! OPEN boundary conditions (use pt_offset=1. as they are applied at the end of the step) 390 390 IF( nb_trcobc > 0 ) THEN 391 391 if (lwp) write(numout,'(a,i5,a,i10)') ' reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 392 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kt_offset=+1)392 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, pt_offset=1.) 393 393 ENDIF 394 394 !
Note: See TracChangeset
for help on using the changeset viewer.