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 1601 for trunk/NEMO/OPA_SRC/lib_cray.f90 – NEMO

Ignore:
Timestamp:
2009-08-11T12:09:19+02:00 (15 years ago)
Author:
ctlod
Message:

Doctor naming of OPA namelist variables , see ticket: #526

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/lib_cray.f90

    r1152 r1601  
    44!  check their existence 
    55 
    6 !  sdot 
    76!  wheneq 
    8 !  saxpy 
    9 !  isrchne 
    10    !!---------------------------------------------------------------------- 
    11    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    12    !! $Id$  
    13    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    14    !!---------------------------------------------------------------------- 
    15 !--------------------------------------------------------- 
    16      FUNCTION sdot( I, X, J, Y, K ) 
    17         DIMENSION X(1), Y(1) 
    18         SDOT = 0. 
    19         DO N = 1, I 
    20         SDOT = SDOT + X(1+(N-1)*J) * Y(1+(N-1)*K) 
    21         END DO 
    22      END FUNCTION sdot 
    23 !--------------------------------------------------------- 
     7!!---------------------------------------------------------------------- 
     8!!  OPA 9.0 , LOCEAN-IPSL (2005)  
     9!! $Id$  
     10!! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     11!!---------------------------------------------------------------------- 
    2412     SUBROUTINE wheneq ( i, x, j, t, ind, nn ) 
    2513        IMPLICIT NONE 
     
    4129 
    4230     END SUBROUTINE wheneq 
    43 !--------------------------------------------------------- 
    44      SUBROUTINE saxpy( I, A, X, J, Y, K ) 
    45         DIMENSION X(1),Y(1) 
    46         DO N = 1, I 
    47            Y(1+(N-1)*K)=A*X(1+(N-1)*J)+Y(1+(N-1)*K) 
    48         END DO 
    49      END SUBROUTINE saxpy 
    50 !--------------------------------------------------------- 
    51      FUNCTION isrchne( K, X, I, B ) 
    52         DIMENSION X(1) 
    53         DO N = 1, K 
    54            IF( X(1+(N-1)*I) /= B ) THEN 
    55               ISRCHNE = N 
    56               RETURN 
    57            ELSE 
    58               ISRCHNE = N + 1 
    59            ENDIF 
    60         END DO 
    61      END FUNCTION isrchne 
Note: See TracChangeset for help on using the changeset viewer.