New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 6004 for branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90 – NEMO

Ignore:
Timestamp:
2015-12-04T17:05:58+01:00 (8 years ago)
Author:
gm
Message:

#1613: vvl by default, step III: Merge with the trunk (free surface simplification) (see wiki)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r5845 r6004  
    1515   !!   'key_bdy'     Open Boundary Condition 
    1616   !!---------------------------------------------------------------------- 
    17    !!   PUBLIC 
    18    !!      bdytide_init     : read of namelist and initialisation of tidal harmonics data 
    19    !!      tide_update   : calculation of tidal forcing at each timestep 
    20    !!---------------------------------------------------------------------- 
    21    USE timing          ! Timing 
    22    USE oce             ! ocean dynamics and tracers  
    23    USE dom_oce         ! ocean space and time domain 
    24    USE iom 
    25    USE in_out_manager  ! I/O units 
    26    USE phycst          ! physical constants 
    27    USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    28    USE bdy_par         ! Unstructured boundary parameters 
    29    USE bdy_oce         ! ocean open boundary conditions 
    30    USE daymod          ! calendar 
    31    USE wrk_nemo        ! Memory allocation 
    32    USE tideini 
    33 !   USE tide_mod       ! Useless ?? 
    34    USE fldread 
    35    USE dynspg_oce, ONLY: lk_dynspg_ts 
     17   !!   bdytide_init  : read of namelist and initialisation of tidal harmonics data 
     18   !!   tide_update   : calculation of tidal forcing at each timestep 
     19   !!---------------------------------------------------------------------- 
     20   USE oce            ! ocean dynamics and tracers  
     21   USE dom_oce        ! ocean space and time domain 
     22   USE phycst         ! physical constants 
     23   USE bdy_par        ! Unstructured boundary parameters 
     24   USE bdy_oce        ! ocean open boundary conditions 
     25   USE tideini        !  
     26   USE daymod         ! calendar 
     27   ! 
     28   USE in_out_manager ! I/O units 
     29   USE iom            ! xIO server 
     30   USE fldread        ! 
     31   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
     32   USE wrk_nemo       ! Memory allocation 
     33   USE timing         ! timing 
    3634 
    3735   IMPLICIT NONE 
     
    4341 
    4442   TYPE, PUBLIC ::   TIDES_DATA     !: Storage for external tidal harmonics data 
    45       REAL(wp), POINTER, DIMENSION(:,:,:)    ::   ssh0       !: Tidal constituents : SSH0 (read in file) 
    46       REAL(wp), POINTER, DIMENSION(:,:,:)    ::   u0         !: Tidal constituents : U0   (read in file) 
    47       REAL(wp), POINTER, DIMENSION(:,:,:)    ::   v0         !: Tidal constituents : V0   (read in file) 
    48       REAL(wp), POINTER, DIMENSION(:,:,:)    ::   ssh        !: Tidal constituents : SSH  (after nodal cor.) 
    49       REAL(wp), POINTER, DIMENSION(:,:,:)    ::   u          !: Tidal constituents : U    (after nodal cor.) 
    50       REAL(wp), POINTER, DIMENSION(:,:,:)    ::   v          !: Tidal constituents : V    (after nodal cor.) 
     43      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   ssh0     !: Tidal constituents : SSH0   (read in file) 
     44      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   u0, v0   !: Tidal constituents : U0, V0 (read in file) 
     45      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   ssh      !: Tidal constituents : SSH    (after nodal cor.) 
     46      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   u , v    !: Tidal constituents : U , V  (after nodal cor.) 
    5147   END TYPE TIDES_DATA 
    5248 
     
    5450   TYPE(TIDES_DATA), PUBLIC, DIMENSION(jp_bdy), TARGET :: tides  !: External tidal harmonics data 
    5551!$AGRIF_END_DO_NOT_TREAT 
    56    TYPE(OBC_DATA)  , PRIVATE, DIMENSION(jp_bdy) :: dta_bdy_s  !: bdy external data (slow component) 
     52   TYPE(OBC_DATA)  , PUBLIC, DIMENSION(jp_bdy) :: dta_bdy_s  !: bdy external data (slow component) 
    5753 
    5854   !!---------------------------------------------------------------------- 
     
    9288      NAMELIST/nambdy_tide/filtide, ln_bdytide_2ddta, ln_bdytide_conj 
    9389      !!---------------------------------------------------------------------- 
    94  
    95       IF( nn_timing == 1 ) CALL timing_start('bdytide_init') 
    96  
     90      ! 
     91      IF( nn_timing == 1 )   CALL timing_start('bdytide_init') 
     92      ! 
    9793      IF (nb_bdy>0) THEN 
    9894         IF(lwp) WRITE(numout,*) 
     
    264260            ENDIF ! ln_bdytide_2ddta=.true. 
    265261            ! 
    266             IF ( ln_bdytide_conj ) THEN ! assume complex conjugate in data files 
     262            IF( ln_bdytide_conj ) THEN    ! assume complex conjugate in data files 
    267263               td%ssh0(:,:,2) = - td%ssh0(:,:,2) 
    268264               td%u0  (:,:,2) = - td%u0  (:,:,2) 
     
    270266            ENDIF 
    271267            ! 
    272             IF ( lk_dynspg_ts ) THEN ! Allocate arrays to save slowly varying boundary data during 
    273                                      ! time splitting integration 
    274                ALLOCATE( dta_bdy_s(ib_bdy)%ssh ( ilen0(1) ) ) 
    275                ALLOCATE( dta_bdy_s(ib_bdy)%u2d ( ilen0(2) ) ) 
    276                ALLOCATE( dta_bdy_s(ib_bdy)%v2d ( ilen0(3) ) ) 
    277                dta_bdy_s(ib_bdy)%ssh(:) = 0.e0 
    278                dta_bdy_s(ib_bdy)%u2d(:) = 0.e0 
    279                dta_bdy_s(ib_bdy)%v2d(:) = 0.e0 
    280             ENDIF 
     268            ! Allocate slow varying data in the case of time splitting: 
     269            ! Do it anyway because at this stage knowledge of free surface scheme is unknown 
     270            ALLOCATE( dta_bdy_s(ib_bdy)%ssh ( ilen0(1) ) ) 
     271            ALLOCATE( dta_bdy_s(ib_bdy)%u2d ( ilen0(2) ) ) 
     272            ALLOCATE( dta_bdy_s(ib_bdy)%v2d ( ilen0(3) ) ) 
     273            dta_bdy_s(ib_bdy)%ssh(:) = 0._wp 
     274            dta_bdy_s(ib_bdy)%u2d(:) = 0._wp 
     275            dta_bdy_s(ib_bdy)%v2d(:) = 0._wp 
    281276            ! 
    282277         ENDIF ! nn_dyn2d_dta(ib_bdy) .ge. 2 
    283278         ! 
    284279      END DO ! loop on ib_bdy 
    285  
    286       IF( nn_timing == 1 ) CALL timing_stop('bdytide_init') 
    287  
     280      ! 
     281      IF( nn_timing == 1 )   CALL timing_stop('bdytide_init') 
     282      ! 
    288283   END SUBROUTINE bdytide_init 
    289284 
    290285 
    291    SUBROUTINE bdytide_update ( kt, idx, dta, td, jit, time_offset ) 
     286   SUBROUTINE bdytide_update( kt, idx, dta, td, jit, time_offset ) 
    292287      !!---------------------------------------------------------------------- 
    293288      !!                 ***  SUBROUTINE bdytide_update  *** 
     
    308303      !                                                 ! etc. 
    309304      ! 
    310       INTEGER                          :: itide, igrd, ib   ! dummy loop indices 
    311       INTEGER                          :: time_add          ! time offset in units of timesteps 
    312       INTEGER, DIMENSION(3)            ::   ilen0       !: length of boundary data (from OBC arrays) 
    313       REAL(wp)                         :: z_arg, z_sarg, zflag, zramp       
     305      INTEGER  ::   itide, igrd, ib       ! dummy loop indices 
     306      INTEGER  ::   time_add              ! time offset in units of timesteps 
     307      INTEGER, DIMENSION(3) ::   ilen0    ! length of boundary data (from OBC arrays) 
     308      REAL(wp) ::   z_arg, z_sarg, zflag, zramp   ! local scalars     
    314309      REAL(wp), DIMENSION(jpmax_harmo) :: z_sist, z_cost 
    315310      !!---------------------------------------------------------------------- 
    316  
    317       IF( nn_timing == 1 ) CALL timing_start('bdytide_update') 
    318  
     311      ! 
     312      IF( nn_timing == 1 )   CALL timing_start('bdytide_update') 
     313      ! 
    319314      ilen0(1) =  SIZE(td%ssh(:,1,1)) 
    320315      ilen0(2) =  SIZE(td%u(:,1,1)) 
     
    377372      END DO 
    378373      ! 
    379       IF( nn_timing == 1 ) CALL timing_stop('bdytide_update') 
     374      IF( nn_timing == 1 )   CALL timing_stop('bdytide_update') 
    380375      ! 
    381376   END SUBROUTINE bdytide_update 
     
    398393      !                                              ! etc. 
    399394      ! 
    400       LOGICAL  :: lk_first_btstp            ! =.TRUE. if time splitting and first barotropic step 
    401       INTEGER  :: itide, ib_bdy, ib, igrd   ! loop indices 
    402       INTEGER  :: time_add                  ! time offset in units of timesteps 
    403       INTEGER, DIMENSION(jpbgrd) :: ilen0  
    404       INTEGER, DIMENSION(1:jpbgrd) :: nblen, nblenrim  ! short cuts 
    405       REAL(wp) :: z_arg, z_sarg, zramp, zoff, z_cost, z_sist       
    406       !!---------------------------------------------------------------------- 
    407  
    408       IF( nn_timing == 1 ) CALL timing_start('bdy_dta_tides') 
    409  
     395      LOGICAL  ::   lk_first_btstp            ! =.TRUE. if time splitting and first barotropic step 
     396      INTEGER  ::   itide, ib_bdy, ib, igrd   ! loop indices 
     397      INTEGER  ::   time_add                  ! time offset in units of timesteps 
     398      INTEGER, DIMENSION(jpbgrd)   ::  ilen0  
     399      INTEGER, DIMENSION(1:jpbgrd) ::   nblen, nblenrim  ! short cuts 
     400      REAL(wp) ::   z_arg, z_sarg, zramp, zoff, z_cost, z_sist       
     401      !!---------------------------------------------------------------------- 
     402      ! 
     403      IF( nn_timing == 1 )   CALL timing_start('bdy_dta_tides') 
     404      ! 
    410405      lk_first_btstp=.TRUE. 
    411406      IF ( PRESENT(kit).AND.( kit /= 1 ) ) THEN ; lk_first_btstp=.FALSE. ; ENDIF 
     
    418413      ! Absolute time from model initialization:    
    419414      IF( PRESENT(kit) ) THEN   
    420          z_arg = ( kt + (kit+0.5_wp*(time_add-1)) / REAL(nn_baro,wp) ) * rdt 
     415         z_arg = ( kt + (kit+time_add-1) / REAL(nn_baro,wp) ) * rdt 
    421416      ELSE                               
    422417         z_arg = ( kt + time_add ) * rdt 
     
    458453            zoff = -kt_tide * rdt ! time offset relative to nodal factor computation time 
    459454            ! 
    460             ! If time splitting, save data at first barotropic iteration 
    461             IF ( PRESENT(kit) ) THEN 
    462                IF ( lk_first_btstp ) THEN ! Save slow varying open boundary data: 
    463                   IF ( dta_bdy(ib_bdy)%ll_ssh ) dta_bdy_s(ib_bdy)%ssh(1:ilen0(1)) = dta_bdy(ib_bdy)%ssh(1:ilen0(1)) 
    464                   IF ( dta_bdy(ib_bdy)%ll_u2d ) dta_bdy_s(ib_bdy)%u2d(1:ilen0(2)) = dta_bdy(ib_bdy)%u2d(1:ilen0(2)) 
    465                   IF ( dta_bdy(ib_bdy)%ll_v2d ) dta_bdy_s(ib_bdy)%v2d(1:ilen0(3)) = dta_bdy(ib_bdy)%v2d(1:ilen0(3)) 
    466  
    467                ELSE ! Initialize arrays from slow varying open boundary data:             
    468                   IF ( dta_bdy(ib_bdy)%ll_ssh ) dta_bdy(ib_bdy)%ssh(1:ilen0(1)) = dta_bdy_s(ib_bdy)%ssh(1:ilen0(1)) 
    469                   IF ( dta_bdy(ib_bdy)%ll_u2d ) dta_bdy(ib_bdy)%u2d(1:ilen0(2)) = dta_bdy_s(ib_bdy)%u2d(1:ilen0(2)) 
    470                   IF ( dta_bdy(ib_bdy)%ll_v2d ) dta_bdy(ib_bdy)%v2d(1:ilen0(3)) = dta_bdy_s(ib_bdy)%v2d(1:ilen0(3)) 
    471                ENDIF 
     455            ! If time splitting, initialize arrays from slow varying open boundary data: 
     456            IF ( PRESENT(kit) ) THEN            
     457               IF ( dta_bdy(ib_bdy)%ll_ssh ) dta_bdy(ib_bdy)%ssh(1:ilen0(1)) = dta_bdy_s(ib_bdy)%ssh(1:ilen0(1)) 
     458               IF ( dta_bdy(ib_bdy)%ll_u2d ) dta_bdy(ib_bdy)%u2d(1:ilen0(2)) = dta_bdy_s(ib_bdy)%u2d(1:ilen0(2)) 
     459               IF ( dta_bdy(ib_bdy)%ll_v2d ) dta_bdy(ib_bdy)%v2d(1:ilen0(3)) = dta_bdy_s(ib_bdy)%v2d(1:ilen0(3)) 
    472460            ENDIF 
    473461            ! 
     
    525513      REAL(wp),ALLOCATABLE, DIMENSION(:) ::   mod_tide, phi_tide 
    526514      !!---------------------------------------------------------------------- 
    527  
     515      ! 
    528516      igrd=1    
    529517                              ! SSH on tracer grid. 
    530     
    531518      ilen0(1) =  SIZE(td%ssh0(:,1,1)) 
    532  
    533       ALLOCATE(mod_tide(ilen0(igrd)),phi_tide(ilen0(igrd))) 
    534  
     519      ! 
     520      ALLOCATE( mod_tide(ilen0(igrd)), phi_tide(ilen0(igrd)) ) 
     521      ! 
    535522      DO itide = 1, nb_harmo 
    536523         DO ib = 1, ilen0(igrd) 
     
    547534         ENDDO 
    548535      END DO 
    549  
     536      ! 
    550537      DEALLOCATE( mod_tide, phi_tide ) 
    551538      ! 
     
    564551      REAL(wp),ALLOCATABLE, DIMENSION(:) ::   mod_tide, phi_tide 
    565552      !!---------------------------------------------------------------------- 
    566  
     553      ! 
    567554      ilen0(2) =  SIZE(td%u0(:,1,1)) 
    568555      ilen0(3) =  SIZE(td%v0(:,1,1)) 
    569  
     556      ! 
    570557      igrd=2                                 ! U grid. 
    571  
     558      ! 
    572559      ALLOCATE( mod_tide(ilen0(igrd)) , phi_tide(ilen0(igrd)) ) 
    573  
     560      ! 
    574561      DO itide = 1, nb_harmo 
    575562         DO ib = 1, ilen0(igrd) 
     
    586573         ENDDO 
    587574      END DO 
    588  
     575      ! 
    589576      DEALLOCATE( mod_tide , phi_tide ) 
    590  
     577      ! 
    591578      igrd=3                                 ! V grid. 
    592  
     579      ! 
    593580      ALLOCATE( mod_tide(ilen0(igrd)) , phi_tide(ilen0(igrd)) ) 
    594581 
     
    608595      END DO 
    609596      ! 
    610       DEALLOCATE(mod_tide,phi_tide) 
     597      DEALLOCATE( mod_tide, phi_tide ) 
    611598      ! 
    612599  END SUBROUTINE tide_init_velocities 
Note: See TracChangeset for help on using the changeset viewer.