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

Ignore:
Timestamp:
2010-10-12T20:49:32+02:00 (14 years ago)
Author:
cetlod
Message:

First guess of NEMO_v3.3

File:
1 edited

Legend:

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

    • Property svn:executable deleted
    r1715 r2236  
    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 
     
    3941   PUBLIC   tide_update   ! routine called in bdydyn 
    4042 
    41    LOGICAL, PUBLIC            ::   ln_tide_date            !: =T correct tide phases and amplitude for model start date 
    42  
    43    INTEGER, PARAMETER ::   jptides_max = 15      !: Max number of tidal contituents 
    44    INTEGER            ::   ntide                 !: Actual number of tidal constituents 
     43   LOGICAL, PUBLIC            ::   ln_tide_date          !: =T correct tide phases and amplitude for model start date 
     44   INTEGER, PUBLIC, PARAMETER ::   jptides_max = 15      !: Max number of tidal contituents 
     45   INTEGER, PUBLIC            ::   ntide                 !: Actual number of tidal constituents 
    4546 
    4647   CHARACTER(len=80), PUBLIC                         ::   filtide    !: Filename root for tidal input files 
    4748   CHARACTER(len= 4), PUBLIC, DIMENSION(jptides_max) ::   tide_cpt   !: Names of tidal components used. 
    4849 
    49    INTEGER , DIMENSION(jptides_max) ::   nindx        !: ??? 
    50    REAL(wp), DIMENSION(jptides_max) ::   tide_speed   !: Phase speed of tidal constituent (deg/hr) 
     50   INTEGER , PUBLIC, DIMENSION(jptides_max) ::   nindx        !: ??? 
     51   REAL(wp), PUBLIC, DIMENSION(jptides_max) ::   tide_speed   !: Phase speed of tidal constituent (deg/hr) 
    5152    
    52    REAL(wp), DIMENSION(jpbdim,jptides_max)  ::   ssh1, ssh2   !: Tidal constituents : SSH 
    53    REAL(wp), DIMENSION(jpbdim,jptides_max)  ::   u1  , u2     !: Tidal constituents : U 
    54    REAL(wp), DIMENSION(jpbdim,jptides_max)  ::   v1  , v2     !: Tidal constituents : V 
     53   REAL(wp), DIMENSION(jpbdim,jptides_max)  ::   ssh1, ssh2   ! Tidal constituents : SSH 
     54   REAL(wp), DIMENSION(jpbdim,jptides_max)  ::   u1  , u2     ! Tidal constituents : U 
     55   REAL(wp), DIMENSION(jpbdim,jptides_max)  ::   v1  , v2     ! Tidal constituents : V 
    5556    
    5657   !!---------------------------------------------------------------------- 
    57    !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
     58   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    5859   !! $Id$  
    59    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     60   !! Software governed by the CeCILL licence  (NEMOGCM/License_CeCILL.txt) 
    6061   !!---------------------------------------------------------------------- 
    61  
    6262CONTAINS 
    6363 
     
    8787      !                                               ! Count number of components specified 
    8888      ntide = jptides_max 
    89       itide = 1 
    90       DO WHILE( tide_cpt(itide) /= '' ) 
    91          ntide = itide 
    92          itide = itide + 1 
     89      DO itide = 1, jptides_max 
     90        IF( tide_cpt(itide) == '' ) THEN 
     91           ntide = itide-1 
     92           exit 
     93        ENDIF 
    9394      END DO 
     95 
    9496      !                                               ! find constituents in standard list 
    9597      DO itide = 1, ntide 
     
    145147      CHARACTER(len=80) :: clfile         ! full file name for tidal input file  
    146148      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!) 
     149      INTEGER, DIMENSION(6) :: lendta=0   ! length of data in the file (note may be different from nblendta!) 
    148150      REAL(wp) ::  z_arg, z_atde, z_btde, z1t, z2t            
    149151      REAL(wp), DIMENSION(jpbdta,1) ::   zdta   ! temporary array for data fields 
     
    161163         IF(lwp) WRITE(numout,*) 'Reading data from file ', clfile 
    162164         CALL iom_open( clfile, inum ) 
    163          igrd = 1 
     165         igrd = 4 
    164166         IF( nblendta(igrd) <= 0 ) THEN  
    165167            idvar = iom_varid( inum,'z1' ) 
     
    183185         IF(lwp) WRITE(numout,*) 'Reading data from file ', clfile 
    184186         CALL iom_open( clfile, inum ) 
    185          igrd = 2 
     187         igrd = 5 
    186188         IF( lendta(igrd) <= 0 ) THEN  
    187189            idvar = iom_varid( inum,'u1' ) 
     
    204206         if(lwp) write(numout,*) 'Reading data from file ', clfile 
    205207         CALL iom_open( clfile, inum ) 
    206          igrd = 3 
     208         igrd = 6 
    207209         IF( lendta(igrd) <= 0 ) THEN  
    208210            idvar = iom_varid( inum,'v1' ) 
     
    252254            ENDIF 
    253255            !                                         !  elevation          
    254             igrd = 1 
     256            igrd = 4 
    255257            DO ib = 1, nblenrim(igrd)                 
    256258               z1t = z_atde * ssh1(ib,itide) + z_btde * ssh2(ib,itide) 
     
    260262            END DO 
    261263            !                                         !  u        
    262             igrd = 2 
     264            igrd = 5 
    263265            DO ib = 1, nblenrim(igrd)                 
    264266               z1t = z_atde * u1(ib,itide) + z_btde * u2(ib,itide) 
     
    268270            END DO 
    269271            !                                         !  v        
    270             igrd = 3 
     272            igrd = 6 
    271273            DO ib = 1, nblenrim(igrd)                 
    272274               z1t = z_atde * v1(ib,itide) + z_btde * v2(ib,itide) 
     
    320322      ! 
    321323      DO itide = 1, ntide 
    322          igrd=1                              ! SSH on tracer grid. 
     324         igrd=4                              ! SSH on tracer grid. 
    323325         DO ib = 1, nblenrim(igrd) 
    324326            sshtide(ib) =sshtide(ib)+ ssh1(ib,itide)*z_cost(itide) + ssh2(ib,itide)*z_sist(itide) 
    325327            !    if(lwp) write(numout,*) 'z',ib,itide,sshtide(ib), ssh1(ib,itide),ssh2(ib,itide) 
    326328         END DO 
    327          igrd=2                              ! U grid 
     329         igrd=5                              ! U grid 
    328330         DO ib=1, nblenrim(igrd) 
    329331            utide(ib) = utide(ib)+ u1(ib,itide)*z_cost(itide) + u2(ib,itide)*z_sist(itide) 
    330332            !    if(lwp) write(numout,*) 'u',ib,itide,utide(ib), u1(ib,itide),u2(ib,itide) 
    331333         END DO 
    332          igrd=3                              ! V grid 
     334         igrd=6                              ! V grid 
    333335         DO ib=1, nblenrim(igrd) 
    334336            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.