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 2093 for branches/DEV_r1986_BDY_updates/NEMO/OPA_SRC/BDY/bdytides.F90 – NEMO

Ignore:
Timestamp:
2010-09-15T09:39:38+02:00 (14 years ago)
Author:
davestorkey
Message:

Main change set.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r1986_BDY_updates/NEMO/OPA_SRC/BDY/bdytides.F90

    r1715 r2093  
    77   !!            2.3  !  2008-01  (J.Holt)  Add date correction. Origins POLCOMS v6.3 2007 
    88   !!            3.0  !  2008-04  (NEMO team)  add in the reference version 
     9   !!            3.3  !  2010-09  (D.Storkey and E.O'Dea)  bug fixes 
    910   !!---------------------------------------------------------------------- 
    1011#if defined key_bdy 
     
    3132   USE bdy_par         ! Unstructured boundary parameters 
    3233   USE bdy_oce         ! ocean open boundary conditions 
     34   USE daymod          ! calendar 
    3335 
    3436   IMPLICIT NONE 
     
    4143   LOGICAL, PUBLIC            ::   ln_tide_date            !: =T correct tide phases and amplitude for model start date 
    4244 
    43    INTEGER, PARAMETER ::   jptides_max = 15      !: Max number of tidal contituents 
    44    INTEGER            ::   ntide                 !: Actual number of tidal constituents 
     45   INTEGER, PARAMETER,PUBLIC ::   jptides_max = 15      !: Max number of tidal contituents 
     46   INTEGER, PUBLIC            ::   ntide                 !: Actual number of tidal constituents 
    4547 
    4648   CHARACTER(len=80), PUBLIC                         ::   filtide    !: Filename root for tidal input files 
    4749   CHARACTER(len= 4), PUBLIC, DIMENSION(jptides_max) ::   tide_cpt   !: Names of tidal components used. 
    4850 
    49    INTEGER , DIMENSION(jptides_max) ::   nindx        !: ??? 
    50    REAL(wp), DIMENSION(jptides_max) ::   tide_speed   !: Phase speed of tidal constituent (deg/hr) 
     51   INTEGER , DIMENSION(jptides_max), PUBLIC ::   nindx        !: ??? 
     52   REAL(wp), DIMENSION(jptides_max), PUBLIC ::   tide_speed   !: Phase speed of tidal constituent (deg/hr) 
    5153    
    5254   REAL(wp), DIMENSION(jpbdim,jptides_max)  ::   ssh1, ssh2   !: Tidal constituents : SSH 
     
    8688      READ  ( numnam, nambdy_tide ) 
    8789      !                                               ! Count number of components specified 
    88       ntide = jptides_max 
    89       itide = 1 
    90       DO WHILE( tide_cpt(itide) /= '' ) 
    91          ntide = itide 
    92          itide = itide + 1 
    93       END DO 
     90      ntide=jptides_max 
     91      do itide = 1, jptides_max 
     92        if ( tide_cpt(itide) == '' ) then 
     93           ntide = itide-1 
     94           exit 
     95        endif 
     96      enddo 
     97 
    9498      !                                               ! find constituents in standard list 
    9599      DO itide = 1, ntide 
     
    145149      CHARACTER(len=80) :: clfile         ! full file name for tidal input file  
    146150      INTEGER ::   ipi, ipj, inum, idvar  ! temporary integers (netcdf read) 
    147       INTEGER, DIMENSION(3) :: lendta=0   ! length of data in the file (note may be different from nblendta!) 
     151      INTEGER, DIMENSION(6) :: lendta=0   ! length of data in the file (note may be different from nblendta!) 
    148152      REAL(wp) ::  z_arg, z_atde, z_btde, z1t, z2t            
    149153      REAL(wp), DIMENSION(jpbdta,1) ::   zdta   ! temporary array for data fields 
     
    161165         IF(lwp) WRITE(numout,*) 'Reading data from file ', clfile 
    162166         CALL iom_open( clfile, inum ) 
    163          igrd = 1 
     167         igrd = 4 
    164168         IF( nblendta(igrd) <= 0 ) THEN  
    165169            idvar = iom_varid( inum,'z1' ) 
     
    183187         IF(lwp) WRITE(numout,*) 'Reading data from file ', clfile 
    184188         CALL iom_open( clfile, inum ) 
    185          igrd = 2 
     189         igrd = 5 
    186190         IF( lendta(igrd) <= 0 ) THEN  
    187191            idvar = iom_varid( inum,'u1' ) 
     
    204208         if(lwp) write(numout,*) 'Reading data from file ', clfile 
    205209         CALL iom_open( clfile, inum ) 
    206          igrd = 3 
     210         igrd = 6 
    207211         IF( lendta(igrd) <= 0 ) THEN  
    208212            idvar = iom_varid( inum,'v1' ) 
     
    252256            ENDIF 
    253257            !                                         !  elevation          
    254             igrd = 1 
     258            igrd = 4 
    255259            DO ib = 1, nblenrim(igrd)                 
    256260               z1t = z_atde * ssh1(ib,itide) + z_btde * ssh2(ib,itide) 
     
    260264            END DO 
    261265            !                                         !  u        
    262             igrd = 2 
     266            igrd = 5 
    263267            DO ib = 1, nblenrim(igrd)                 
    264268               z1t = z_atde * u1(ib,itide) + z_btde * u2(ib,itide) 
     
    268272            END DO 
    269273            !                                         !  v        
    270             igrd = 3 
     274            igrd = 6 
    271275            DO ib = 1, nblenrim(igrd)                 
    272276               z1t = z_atde * v1(ib,itide) + z_btde * v2(ib,itide) 
     
    320324      ! 
    321325      DO itide = 1, ntide 
    322          igrd=1                              ! SSH on tracer grid. 
     326         igrd=4                              ! SSH on tracer grid. 
    323327         DO ib = 1, nblenrim(igrd) 
    324328            sshtide(ib) =sshtide(ib)+ ssh1(ib,itide)*z_cost(itide) + ssh2(ib,itide)*z_sist(itide) 
    325329            !    if(lwp) write(numout,*) 'z',ib,itide,sshtide(ib), ssh1(ib,itide),ssh2(ib,itide) 
    326330         END DO 
    327          igrd=2                              ! U grid 
     331         igrd=5                              ! U grid 
    328332         DO ib=1, nblenrim(igrd) 
    329333            utide(ib) = utide(ib)+ u1(ib,itide)*z_cost(itide) + u2(ib,itide)*z_sist(itide) 
    330334            !    if(lwp) write(numout,*) 'u',ib,itide,utide(ib), u1(ib,itide),u2(ib,itide) 
    331335         END DO 
    332          igrd=3                              ! V grid 
     336         igrd=6                              ! V grid 
    333337         DO ib=1, nblenrim(igrd) 
    334338            vtide(ib) = vtide(ib)+ v1(ib,itide)*z_cost(itide) + v2(ib,itide)*z_sist(itide) 
Note: See TracChangeset for help on using the changeset viewer.