Last change
on this file since 12165 was
10070,
checked in by nicolasmartin, 2 years ago
|
Fix wrong SVN property svn:executable on routines
|
-
Property svn:keywords set to
Id
|
File size:
1.0 KB
|
Rev | Line | |
---|
[3] | 1 | ! Cray subroutines or functions used by OPA model and possibly |
---|
| 2 | ! not found on other platforms. |
---|
| 3 | ! |
---|
| 4 | ! check their existence |
---|
| 5 | ! |
---|
| 6 | ! wheneq |
---|
[10068] | 7 | !!---------------------------------------------------------------------- |
---|
[10070] | 8 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
[10068] | 9 | !! $Id$ |
---|
| 10 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
| 11 | !!---------------------------------------------------------------------- |
---|
[3680] | 12 | SUBROUTINE lib_cray |
---|
| 13 | WRITE(*,*) 'lib_cray: You should not have seen this print! error?' |
---|
| 14 | END SUBROUTINE lib_cray |
---|
| 15 | |
---|
[2528] | 16 | SUBROUTINE wheneq ( i, x, j, t, ind, nn ) |
---|
[3] | 17 | IMPLICIT NONE |
---|
| 18 | |
---|
| 19 | INTEGER , INTENT ( in ) :: i, j |
---|
| 20 | INTEGER , INTENT ( out ) :: nn |
---|
| 21 | REAL , INTENT ( in ), DIMENSION (1+(i-1)*j) :: x |
---|
| 22 | REAL , INTENT ( in ) :: t |
---|
| 23 | INTEGER , INTENT ( out ), DIMENSION (1+(i-1)*j) :: ind |
---|
| 24 | INTEGER :: n, k |
---|
| 25 | nn = 0 |
---|
| 26 | DO n = 1, i |
---|
| 27 | k = 1 + (n-1) * j |
---|
| 28 | IF ( x ( k) == t ) THEN |
---|
| 29 | nn = nn + 1 |
---|
| 30 | ind (nn) = k |
---|
| 31 | ENDIF |
---|
| 32 | END DO |
---|
| 33 | |
---|
[2528] | 34 | END SUBROUTINE wheneq |
---|
Note: See
TracBrowser
for help on using the repository browser.