lib_cray.f90 1.1 KB

12345678910111213141516171819202122232425262728293031323334
  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
  7. !!----------------------------------------------------------------------
  8. !! OPA 9.0 , LOCEAN-IPSL (2005)
  9. !! $Id: lib_cray.f90 3680 2012-11-27 14:42:24Z rblod $
  10. !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
  11. !!----------------------------------------------------------------------
  12. SUBROUTINE lib_cray
  13. WRITE(*,*) 'lib_cray: You should not have seen this print! error?'
  14. END SUBROUTINE lib_cray
  15. SUBROUTINE wheneq ( i, x, j, t, ind, nn )
  16. IMPLICIT NONE
  17. INTEGER , INTENT ( in ) :: i, j
  18. INTEGER , INTENT ( out ) :: nn
  19. REAL , INTENT ( in ), DIMENSION (1+(i-1)*j) :: x
  20. REAL , INTENT ( in ) :: t
  21. INTEGER , INTENT ( out ), DIMENSION (1+(i-1)*j) :: ind
  22. INTEGER :: n, k
  23. nn = 0
  24. DO n = 1, i
  25. k = 1 + (n-1) * j
  26. IF ( x ( k) == t ) THEN
  27. nn = nn + 1
  28. ind (nn) = k
  29. ENDIF
  30. END DO
  31. END SUBROUTINE wheneq