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.
lib_cray.f90 in trunk/NEMO/OFF_SRC – NEMO

source: trunk/NEMO/OFF_SRC/lib_cray.f90 @ 941

Last change on this file since 941 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.8 KB
Line 
1!  Cray subroutines or functions used by OPA model and possibly
2!  not found on other platforms.
3!
4!  check their existence
5
6!  sdot
7!  wheneq
8!  saxpy
9!  isrchne
10!!----------------------------------------------------------------------
11!!  OPA 9.0 , LOCEAN-IPSL (2005)
12!! $Header$
13!! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
14!!----------------------------------------------------------------------
15     FUNCTION sdot( I, X, J, Y, K )
16        DIMENSION X(1), Y(1)
17        SDOT = 0.
18        DO N = 1, I
19        SDOT = SDOT + X(1+(N-1)*J) * Y(1+(N-1)*K)
20        END DO
21     END FUNCTION sdot
22!---------------------------------------------------------
23     SUBROUTINE wheneq ( i, x, j, t, ind, nn )
24        IMPLICIT NONE
25
26        INTEGER , INTENT (  in ) :: i, j
27        INTEGER , INTENT ( out ) :: nn
28        REAL    , INTENT (  in ), DIMENSION (1+(i-1)*j) :: x
29        REAL    , INTENT (  in ) :: t
30        INTEGER , INTENT ( out ), DIMENSION (1+(i-1)*j) :: ind
31        INTEGER :: n, k
32        nn = 0
33        DO n = 1, i
34          k = 1 + (n-1) * j
35          IF ( x ( k) == t ) THEN
36              nn = nn + 1
37              ind (nn) = k
38          ENDIF
39        END DO
40
41     END SUBROUTINE wheneq
42!---------------------------------------------------------
43     SUBROUTINE saxpy( I, A, X, J, Y, K )
44        DIMENSION X(1),Y(1)
45        DO N = 1, I
46           Y(1+(N-1)*K)=A*X(1+(N-1)*J)+Y(1+(N-1)*K)
47        END DO
48     END SUBROUTINE saxpy
49!---------------------------------------------------------
50     FUNCTION isrchne( K, X, I, B )
51        DIMENSION X(1)
52        DO N = 1, K
53           IF( X(1+(N-1)*I) /= B ) THEN
54              ISRCHNE = N
55              RETURN
56           ELSE
57              ISRCHNE = N + 1
58           ENDIF
59        END DO
60     END FUNCTION isrchne
Note: See TracBrowser for help on using the repository browser.