Changeset 11224
- Timestamp:
- 2019-07-08T11:19:12+02:00 (6 years ago)
- Location:
- NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/BDY/bdydta.F90
r11223 r11224 54 54 INTEGER , PARAMETER :: jp_bdyh_i = 9 ! 55 55 INTEGER , PARAMETER :: jp_bdyh_S = 10 ! 56 ! =F => baroclinic velocities in 3D boundary conditions 56 #if ! defined key_si3 57 INTEGER , PARAMETER :: jpl = 1 58 #endif 59 ! =F => baroclinic velocities in 3D boundary conditions 57 60 !$AGRIF_DO_NOT_TREAT 58 61 TYPE(FLD), PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET :: bf ! structure of input fields (file informations, fields read) -
NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/BDY/bdydyn2d.F90
r11210 r11224 14 14 !! bdy_ssh : Duplicate sea level across open boundaries 15 15 !!---------------------------------------------------------------------- 16 USE oce, only : sshdta => spgu ! ocean dynamics and tracers17 16 USE dom_oce ! ocean space and time domain 18 17 USE bdy_oce ! ocean open boundary conditions … … 186 185 REAL(wp) :: zfla ! Flather correction 187 186 REAL(wp) :: z1_2 ! 187 REAL(wp), DIMENSION(jpi,jpj) :: sshdta ! 2D version of dta%ssh 188 188 !!---------------------------------------------------------------------- 189 189 … … 203 203 ii = idx%nbi(jb,igrd) 204 204 ij = idx%nbj(jb,igrd) 205 IF( ll_wd ) THEN 206 sshdta(ii, ij) = dta%ssh(jb) - ssh_ref 207 ELSE 208 sshdta(ii, ij) = dta%ssh(jb) 205 IF( ll_wd ) THEN ; sshdta(ii, ij) = dta%ssh(jb) - ssh_ref 206 ELSE ; sshdta(ii, ij) = dta%ssh(jb) 209 207 ENDIF 210 208 END DO -
NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/SAS/step.F90
r10425 r11224 96 96 ! From SAS: ocean bdy data are wrong (but we do not care) and ice bdy data are OK. 97 97 ! This is not clean and should be changed in the future. 98 IF( ln_bdy ) CALL bdy_dta ( kstp, time_offset=+1 ) ! update dynamic & tracer data at open boundaries98 IF( ln_bdy ) CALL bdy_dta ( kstp, kt_offset=+1 ) ! update dynamic & tracer data at open boundaries 99 99 ! ==> 100 100 CALL sbc ( kstp ) ! Sea Boundary Condition (including sea-ice) -
NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/TOP/trcbc.F90
r10068 r11224 44 44 TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:), TARGET :: sf_trcobc 45 45 #endif 46 TYPE(MAP_POINTER), ALLOCATABLE, DIMENSION(:) :: nbmap_ptr ! array of pointers to nbmap47 46 48 47 !! * Substitutions … … 133 132 READ ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 134 133 903 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 135 134 ! make sur that all elements of the namelist variables have a default definition from namelist_ref 135 cn_trc (2:jp_bdy) = cn_trc (1) 136 cn_trc_dflt(2:jp_bdy) = cn_trc_dflt(1) 136 137 REWIND( numnat_cfg ) ! Namelist namtrc_bdy in configuration namelist : Passive tracer data structure 137 138 READ ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) … … 234 235 ! OPEN Lateral boundary conditions 235 236 IF( ln_bdy .AND. nb_trcobc > 0 ) THEN 236 ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), nbmap_ptr(nb_trcobc),STAT=ierr1 )237 ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), STAT=ierr1 ) 237 238 IF( ierr1 > 0 ) THEN 238 239 CALL ctl_stop( 'trc_bc_ini: unable to allocate sf_trcobc structure' ) ; RETURN … … 257 258 trcdta_bdy(jn,ib)%trc => sf_trcobc(jl)%fnow(:,1,:) 258 259 trcdta_bdy(jn,ib)%rn_fac = rf_trofac(jl) 259 ! create OBC mapping array260 nbmap_ptr(jl)%ptr => idx_bdy(ib)%nbmap(:,igrd)261 nbmap_ptr(jl)%ll_unstruc = ln_coords_file(igrd)262 !263 260 ELSE !* Initialise obc arrays from initial conditions *! 264 261 ALLOCATE ( trcdta_bdy(jn,ib)%trc(nblen,jpk) ) … … 276 273 ! 277 274 CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_ini', 'Passive tracer OBC data', 'namtrc_bc' ) 275 DO jn = 1, ntrc ! define imap pointer, must be done after the call to fld_fill 276 DO ib = 1, nb_bdy 277 IF( ln_trc_obc(jn) ) THEN !* Initialise from external data *! 278 jl = n_trc_indobc(jn) 279 sf_trcobc(jl)%imap => idx_bdy(ib)%nbmap(1:idx_bdy(ib)%nblen(igrd),igrd) 280 ENDIF 281 END DO 282 END DO 283 ! 278 284 ENDIF 279 285 … … 362 368 IF( PRESENT(jit) ) THEN 363 369 ! 364 ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step)370 ! OPEN boundary conditions (use kt_offset=+1 as they are applied at the end of the step) 365 371 IF( nb_trcobc > 0 ) THEN 366 372 if (lwp) write(numout,'(a,i5,a,i10)') ' reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 367 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, map=nbmap_ptr,kit=jit, kt_offset=+1)373 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kit=jit, kt_offset=+1) 368 374 ENDIF 369 375 ! … … 382 388 ELSE 383 389 ! 384 ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step)390 ! OPEN boundary conditions (use kt_offset=+1 as they are applied at the end of the step) 385 391 IF( nb_trcobc > 0 ) THEN 386 392 if (lwp) write(numout,'(a,i5,a,i10)') ' reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt 387 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, map=nbmap_ptr,kt_offset=+1)393 CALL fld_read( kt=kt, kn_fsbc=1, sd=sf_trcobc, kt_offset=+1) 388 394 ENDIF 389 395 ! -
NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/TOP/trcbdy.F90
r11210 r11224 46 46 INTEGER, INTENT( in ) :: kt ! Main time step counter 47 47 !! 48 INTEGER :: ib_bdy , jn ,igrd ! Loop indices48 INTEGER :: ib_bdy ,ir, jn ,igrd ! Loop indices 49 49 REAL(wp), POINTER, DIMENSION(:,:) :: ztrc 50 50 REAL(wp), POINTER :: zfac
Note: See TracChangeset
for help on using the changeset viewer.