MODULE mod_tides ! !git $Id$ !svn $Id: mod_tides.F 1151 2023-02-09 03:08:53Z arango $ !================================================== Hernan G. Arango === ! Copyright (c) 2002-2023 The ROMS/TOMS Group ! ! Licensed under a MIT/X style license ! ! See License_ROMS.md ! !======================================================================= ! ! ! Tidal Components: ! ! ! ! Each of the following arrays has a dimension in tidal components ! ! classified by period: ! ! ! ! semi-diurnal: M2, S2, N2, K2 (12.42, 12.00, 12.66, 11.97h) ! ! diurnal: K1, O1, P1, Q1 (23.93, 25.82, 24.07, 26.87h) ! ! ! ! and other longer periods. The order of these tidal components is ! ! irrelevant here. The number of components to USE is depends on ! ! the regional application. ! ! ! ! CosOmega Cosine tidal harmonics for current omega(t). ! ! SinOmega Sine tidal harmonics for current omega(t). ! ! SSH_Tamp Tidal elevation amplitude (m) at RHO-points. ! ! SSH_Tphase Tidal elevation phase (degrees/360) at RHO-points. ! ! Tperiod Tidal period (s). ! ! UV_Tangle Tidal current angle (radians; counterclockwise ! ! from EAST and rotated to curvilinear grid) at ! ! RHO-points. ! ! UV_Tmajor Maximum tidal current: tidal ellipse major axis ! ! (m/s) at RHO-points. ! ! UV_Tminor Minimum tidal current: tidal ellipse minor axis ! ! (m/s) at RHO-points. ! ! UV_Tphase Tidal current phase (degrees/360) at RHO-points. ! ! ! !======================================================================= ! USE mod_kinds ! implicit none ! PUBLIC :: allocate_tides PUBLIC :: deallocate_tides PUBLIC :: initialize_tides ! !----------------------------------------------------------------------- ! Define T_TIDES structure. !----------------------------------------------------------------------- ! TYPE T_TIDES real(r8), pointer :: Tperiod(:) real(r8), pointer :: SSH_Tamp(:,:,:) real(r8), pointer :: SSH_Tphase(:,:,:) real(r8), pointer :: UV_Tangle(:,:,:) real(r8), pointer :: UV_Tmajor(:,:,:) real(r8), pointer :: UV_Tminor(:,:,:) real(r8), pointer :: UV_Tphase(:,:,:) END TYPE T_TIDES ! TYPE (T_TIDES), allocatable :: TIDES(:) ! CONTAINS ! SUBROUTINE allocate_tides (ng, LBi, UBi, LBj, UBj) ! !======================================================================= ! ! ! This routine allocates all variables in the module for all nested ! ! grids. ! ! ! !======================================================================= ! USE mod_param USE mod_parallel USE mod_iounits USE mod_ncparam USE mod_netcdf USE mod_scalars USE mod_stepping ! USE strings_mod, ONLY : FoundError ! ! Inported variable declarations. ! integer, intent(in) :: ng, LBi, UBi, LBj, UBj ! ! Local variable declarations. ! logical :: foundit integer :: Nfiles, Vid, i, ifile, mg, nvatt, nvdim real(r8) :: size2d ! character (len=*), parameter :: MyFile = & & "ROMS/Modules/mod_tides.F"//", allocate_tides" ! !----------------------------------------------------------------------- ! Allocate module variables. !----------------------------------------------------------------------- ! ! Inquire about the maximum number of tidal components. Notice that ! currently we only support nested applications where the tidal ! forcing is applied to the main coarser grid (RefineScale(ng)=0) ! and the other grids get the tidal forcing from the contact areas. ! IF (LprocessTides(ng)) THEN MTC=0 foundit=.FALSE. SELECT CASE (TIDE(ng)%IOtype) CASE (io_nf90) CALL netcdf_inq_var (ng, iNLM, TIDE(ng)%name, & & MyVarName = Vname(1,idTper), & & SearchVar = foundit, & & VarID = Vid, & & nVardim = nvdim, & & nVarAtt = nvatt) END SELECT IF (FoundError(exit_flag, NoError, 211, MyFile)) RETURN ! ! Set maximum number of tidal components. Allocate and initialize ! TIDE I/O structure. Notice that in nested applications, all the ! nested grids need to have the same number of tidal component. ! IF (foundit) THEN MTC=MAX(MTC,var_Dsize(1)) ! first dimension DO mg=1,Ngrids NTC(mg)=var_Dsize(1) END DO END IF END IF ! ! Allocate structure. ! IF (ng.eq.1) allocate ( TIDES(Ngrids) ) ! ! Set horizontal array size. ! size2d=REAL((UBi-LBi+1)*(UBj-LBj+1),r8) ! ! Allocate tidal forcing variables. ! allocate ( TIDES(ng) % Tperiod(MTC) ) Dmem(ng)=Dmem(ng)+REAL(MTC,r8) allocate ( TIDES(ng) % SSH_Tamp(LBi:UBi,LBj:UBj,MTC) ) Dmem(ng)=Dmem(ng)+REAL(MTC,r8)*size2d allocate ( TIDES(ng) % SSH_Tphase(LBi:UBi,LBj:UBj,MTC) ) Dmem(ng)=Dmem(ng)+REAL(MTC,r8)*size2d allocate ( TIDES(ng) % UV_Tangle(LBi:UBi,LBj:UBj,MTC) ) Dmem(ng)=Dmem(ng)+REAL(MTC,r8)*size2d allocate ( TIDES(ng) % UV_Tmajor(LBi:UBi,LBj:UBj,MTC) ) Dmem(ng)=Dmem(ng)+REAL(MTC,r8)*size2d allocate ( TIDES(ng) % UV_Tminor(LBi:UBi,LBj:UBj,MTC) ) Dmem(ng)=Dmem(ng)+REAL(MTC,r8)*size2d allocate ( TIDES(ng) % UV_Tphase(LBi:UBi,LBj:UBj,MTC) ) Dmem(ng)=Dmem(ng)+REAL(MTC,r8)*size2d ! RETURN END SUBROUTINE allocate_tides ! SUBROUTINE deallocate_tides (ng) ! !======================================================================= ! ! ! This routine allocates all variables in the module for all nested ! ! grids. ! ! ! !======================================================================= ! USE mod_param USE mod_ncparam ! ! Inported variable declarations. ! integer, intent(in) :: ng ! ! Local variable declarations. ! character (len=*), parameter :: MyFile = & & "ROMS/Modules/mod_tides.F"//", deallocate_tides" ! !----------------------------------------------------------------------- ! Deallocate derived-type TIDES structure. !----------------------------------------------------------------------- ! IF (ng.eq.Ngrids) THEN IF (allocated(TIDES)) deallocate ( TIDES ) END IF ! RETURN END SUBROUTINE deallocate_tides ! SUBROUTINE initialize_tides (ng, tile) ! !======================================================================= ! ! ! This routine initialize all variables in the module using first ! ! touch distribution policy. In shared-memory configuration, this ! ! operation actually performs propagation of the "shared arrays" ! ! across the cluster, unless another policy is specified to ! ! override the default. ! ! ! !======================================================================= ! USE mod_param USE mod_ncparam ! ! Imported variable declarations. ! integer, intent(in) :: ng, tile ! ! Local variable declarations. ! integer :: Imin, Imax, Jmin, Jmax integer :: i, itide, itrc, j, jtide, k real(r8), parameter :: IniVal = 0.0_r8 ! !----------------------------------------------------------------------- ! Set lower and upper tile bounds and staggered variables bounds for ! this horizontal domain partition. Notice that if tile=-1, it will ! set the values for the global grid. !----------------------------------------------------------------------- ! integer :: Istr, IstrB, IstrP, IstrR, IstrT, IstrM, IstrU integer :: Iend, IendB, IendP, IendR, IendT integer :: Jstr, JstrB, JstrP, JstrR, JstrT, JstrM, JstrV integer :: Jend, JendB, JendP, JendR, JendT integer :: Istrm3, Istrm2, Istrm1, IstrUm2, IstrUm1 integer :: Iendp1, Iendp2, Iendp2i, Iendp3 integer :: Jstrm3, Jstrm2, Jstrm1, JstrVm2, JstrVm1 integer :: Jendp1, Jendp2, Jendp2i, Jendp3 ! Istr =BOUNDS(ng) % Istr (tile) IstrB =BOUNDS(ng) % IstrB (tile) IstrM =BOUNDS(ng) % IstrM (tile) IstrP =BOUNDS(ng) % IstrP (tile) IstrR =BOUNDS(ng) % IstrR (tile) IstrT =BOUNDS(ng) % IstrT (tile) IstrU =BOUNDS(ng) % IstrU (tile) Iend =BOUNDS(ng) % Iend (tile) IendB =BOUNDS(ng) % IendB (tile) IendP =BOUNDS(ng) % IendP (tile) IendR =BOUNDS(ng) % IendR (tile) IendT =BOUNDS(ng) % IendT (tile) Jstr =BOUNDS(ng) % Jstr (tile) JstrB =BOUNDS(ng) % JstrB (tile) JstrM =BOUNDS(ng) % JstrM (tile) JstrP =BOUNDS(ng) % JstrP (tile) JstrR =BOUNDS(ng) % JstrR (tile) JstrT =BOUNDS(ng) % JstrT (tile) JstrV =BOUNDS(ng) % JstrV (tile) Jend =BOUNDS(ng) % Jend (tile) JendB =BOUNDS(ng) % JendB (tile) JendP =BOUNDS(ng) % JendP (tile) JendR =BOUNDS(ng) % JendR (tile) JendT =BOUNDS(ng) % JendT (tile) ! Istrm3 =BOUNDS(ng) % Istrm3 (tile) ! Istr-3 Istrm2 =BOUNDS(ng) % Istrm2 (tile) ! Istr-2 Istrm1 =BOUNDS(ng) % Istrm1 (tile) ! Istr-1 IstrUm2=BOUNDS(ng) % IstrUm2(tile) ! IstrU-2 IstrUm1=BOUNDS(ng) % IstrUm1(tile) ! IstrU-1 Iendp1 =BOUNDS(ng) % Iendp1 (tile) ! Iend+1 Iendp2 =BOUNDS(ng) % Iendp2 (tile) ! Iend+2 Iendp2i=BOUNDS(ng) % Iendp2i(tile) ! Iend+2 interior Iendp3 =BOUNDS(ng) % Iendp3 (tile) ! Iend+3 Jstrm3 =BOUNDS(ng) % Jstrm3 (tile) ! Jstr-3 Jstrm2 =BOUNDS(ng) % Jstrm2 (tile) ! Jstr-2 Jstrm1 =BOUNDS(ng) % Jstrm1 (tile) ! Jstr-1 JstrVm2=BOUNDS(ng) % JstrVm2(tile) ! JstrV-2 JstrVm1=BOUNDS(ng) % JstrVm1(tile) ! JstrV-1 Jendp1 =BOUNDS(ng) % Jendp1 (tile) ! Jend+1 Jendp2 =BOUNDS(ng) % Jendp2 (tile) ! Jend+2 Jendp2i=BOUNDS(ng) % Jendp2i(tile) ! Jend+2 interior Jendp3 =BOUNDS(ng) % Jendp3 (tile) ! Jend+3 ! ! Set array initialization range. ! Imin=BOUNDS(ng)%LBi(tile) Imax=BOUNDS(ng)%UBi(tile) Jmin=BOUNDS(ng)%LBj(tile) Jmax=BOUNDS(ng)%UBj(tile) ! !----------------------------------------------------------------------- ! Initialize module variables. !----------------------------------------------------------------------- ! ! Initialize tidal forcing variables. ! IF (DOMAIN(ng)%SouthWest_Test(tile)) THEN DO itide=1,MTC TIDES(ng) % Tperiod(itide) = IniVal END DO END IF DO itide=1,MTC DO j=Jmin,Jmax DO i=Imin,Imax TIDES(ng) % SSH_Tamp(i,j,itide) = IniVal TIDES(ng) % SSH_Tphase(i,j,itide) = IniVal END DO END DO DO j=Jmin,Jmax DO i=Imin,Imax TIDES(ng) % UV_Tangle(i,j,itide) = IniVal TIDES(ng) % UV_Tmajor(i,j,itide) = IniVal TIDES(ng) % UV_Tminor(i,j,itide) = IniVal TIDES(ng) % UV_Tphase(i,j,itide) = IniVal END DO END DO END DO ! RETURN END SUBROUTINE initialize_tides END MODULE mod_tides