Changeset 10852
- Timestamp:
- 2019-04-08T19:03:04+02:00 (4 years ago)
- Location:
- NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE
- Files:
-
- 1 deleted
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/DYN/dynspg.F90
r10777 r10852 21 21 USE dynspg_exp ! surface pressure gradient (dyn_spg_exp routine) 22 22 USE dynspg_ts ! surface pressure gradient (dyn_spg_ts routine) 23 USE sbctide !24 23 USE tide_mod ! 25 24 USE trd_oce ! trends: ocean variables -
NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/DYN/dynspg_ts.F90
r10777 r10852 44 44 USE bdytides ! open boundary condition data 45 45 USE bdydyn2d ! open boundary conditions on barotropic variables 46 USE sbctide ! tides47 46 USE tide_mod ! 48 47 USE sbcwave ! surface wave -
NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/TDE/tide_mod.F90
r10840 r10852 20 20 21 21 PUBLIC tide_init 22 PUBLIC tide_ harmo ! called internally and by module sbdtide22 PUBLIC tide_update ! called by stp 23 23 PUBLIC tide_init_harmonics ! called internally and by module diaharm 24 PUBLIC tide_init_load25 PUBLIC tide_init_potential26 24 PUBLIC upd_tide ! called in dynspg_... modules 27 25 28 26 INTEGER, PUBLIC, PARAMETER :: jpmax_harmo = 64 !: maximum number of harmonic components 29 27 30 TYPE , PUBLIC:: tide28 TYPE :: tide 31 29 CHARACTER(LEN=4) :: cname_tide = '' 32 30 REAL(wp) :: equitide … … 37 35 END TYPE tide 38 36 39 TYPE(tide), PUBLIC,DIMENSION(:), POINTER :: tide_components !: Array of selected tidal component parameters37 TYPE(tide), DIMENSION(:), POINTER :: tide_components !: Array of selected tidal component parameters 40 38 41 39 TYPE, PUBLIC :: tide_harmonic !: Oscillation parameters of harmonic tidal components … … 52 50 LOGICAL , PUBLIC :: ln_tide !: 53 51 LOGICAL , PUBLIC :: ln_tide_pot !: 54 LOGICAL , PUBLIC:: ln_read_load !:52 LOGICAL :: ln_read_load !: 55 53 LOGICAL , PUBLIC :: ln_scal_load !: 56 54 LOGICAL , PUBLIC :: ln_tide_ramp !: … … 63 61 64 62 REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:) :: pot_astro !: tidal potential 65 REAL(wp), PUBLIC,ALLOCATABLE, DIMENSION(:,:,:) :: amp_pot, phi_pot66 REAL(wp), PUBLIC,ALLOCATABLE, DIMENSION(:,:,:) :: amp_load, phi_load63 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: amp_pot, phi_pot 64 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: amp_load, phi_load 67 65 68 66 … … 318 316 319 317 318 SUBROUTINE tide_update( kt ) 319 !!---------------------------------------------------------------------- 320 !! *** ROUTINE tide_update *** 321 !!---------------------------------------------------------------------- 322 INTEGER, INTENT( in ) :: kt ! ocean time-step 323 INTEGER :: jk ! dummy loop index 324 INTEGER :: nsec_day_orig ! Temporary variable 325 !!---------------------------------------------------------------------- 326 327 IF( nsec_day == NINT(0.5_wp * rdt) .OR. kt == nit000 ) THEN ! start a new day 328 ! 329 ! 330 IF( ln_read_load )THEN 331 IF ( kt == nit000 ) CALL tide_init_load 332 amp_pot(:,:,:) = amp_load(:,:,:) 333 phi_pot(:,:,:) = phi_load(:,:,:) 334 ELSE 335 amp_pot(:,:,:) = 0._wp 336 phi_pot(:,:,:) = 0._wp 337 ENDIF 338 pot_astro(:,:) = 0._wp 339 ! 340 ! If the run does not start from midnight then need to initialise tides 341 ! at the start of the current day (only occurs when kt==nit000) 342 ! Temporarily set nsec_day to beginning of day. 343 nsec_day_orig = nsec_day 344 IF ( nsec_day /= NINT(0.5_wp * rdt) ) THEN 345 kt_tide = kt - (nsec_day - 0.5_wp * rdt)/rdt 346 nsec_day = NINT(0.5_wp * rdt) 347 ELSE 348 kt_tide = kt 349 ENDIF 350 CALL tide_harmo(tide_components, tide_harmonics) ! Update oscillation parameters of tidal components 351 ! 352 ! 353 IF(lwp) THEN 354 WRITE(numout,*) 355 WRITE(numout,*) 'tide_update : Update of the components and (re)Init. the potential at kt=', kt 356 WRITE(numout,*) '~~~~~~~~~~~ ' 357 DO jk = 1, nb_harmo 358 WRITE(numout,*) tide_harmonics(jk)%cname_tide, tide_harmonics(jk)%u, & 359 & tide_harmonics(jk)%f,tide_harmonics(jk)%v0, tide_harmonics(jk)%omega 360 END DO 361 ENDIF 362 ! 363 IF( ln_tide_pot ) CALL tide_init_potential 364 ! 365 ! Reset nsec_day 366 nsec_day = nsec_day_orig 367 ENDIF 368 ! 369 END SUBROUTINE tide_update 370 371 320 372 SUBROUTINE tide_harmo( ptide_comp, ptide_harmo ) 321 373 ! -
NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/step.F90
r10364 r10852 110 110 ! Update external forcing (tides, open boundaries, and surface boundary condition (including sea-ice) 111 111 !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 112 IF( ln_tide ) CALL sbc_tide( kstp )! update tide potential112 IF( ln_tide ) CALL tide_update( kstp ) ! update tide potential 113 113 IF( ln_apr_dyn ) CALL sbc_apr ( kstp ) ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib) 114 114 IF( ln_bdy ) CALL bdy_dta ( kstp, time_offset=+1 ) ! update dynamic & tracer data at open boundaries -
NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/step_oce.F90
r10773 r10852 19 19 USE sbccpl ! surface boundary condition: coupled formulation (call send at end of step) 20 20 USE sbcapr ! surface boundary condition: atmospheric pressure 21 USE sbctide ! Tide initialisation 22 USE tide_mod, ONLY : ln_tide 21 USE tide_mod, ONLY : ln_tide, tide_update 23 22 USE sbcwave ! Wave intialisation 24 23
Note: See TracChangeset
for help on using the changeset viewer.