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 1056 – NEMO

Changeset 1056


Ignore:
Timestamp:
2008-06-04T18:43:38+02:00 (16 years ago)
Author:
ctlod
Message:

trunk: solve one compilation error and one warning message when key_noslip_accurate is active, see ticket: #187

Location:
trunk/NEMO/OPA_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/DOM/dommsk.F90

    r896 r1056  
    497497      !!---------------------------------------------------------------------- 
    498498      INTEGER  :: ji, jj, jk, jl      ! dummy loop indices 
    499       INTEGER ::   ine, inw, ins, inn, itest, ierror, iind, ijnd, ii 
     499      INTEGER ::   ine, inw, ins, inn, itest, ierror, iind, ijnd 
    500500      INTEGER, DIMENSION(jpi*jpj*jpk,3) ::  icoord 
    501501      REAL(wp) ::   zaa 
  • trunk/NEMO/OPA_SRC/DYN/divcur.F90

    r911 r1056  
    8787      INTEGER ::   ii, ij, jl     ! temporary integer 
    8888      INTEGER ::   ijt, iju       ! temporary integer 
    89       REAL(wp) ::   zdiv, zdju 
    9089      REAL(wp), DIMENSION(   jpi  ,1:jpj+2) ::   zwu   ! workspace 
    9190      REAL(wp), DIMENSION(-1:jpi+2,  jpj  ) ::   zwv   ! workspace 
  • trunk/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r719 r1056  
    55   !!                 turbulent closure parameterization 
    66   !!===================================================================== 
    7    !! History :   8.5  !  02-06  (G. Madec)  original code 
    8    !!             9.0  !  06-07  (S. Masson)  iom, add ctl_stop, ctl_warn 
     7   !! History :   1.0  !  2002-06  (G. Madec)  original code 
     8   !!             2.0  !  2006-07  (S. Masson)  iom, add ctl_stop, ctl_warn 
     9   !!             3.0  !  2008-06  (G. Madec)  add ctmp4 to ctmp10 
    910   !!---------------------------------------------------------------------- 
    1011 
     
    1213   !!   ctl_stop   : update momentum and tracer Kz from a tke scheme 
    1314   !!   ctl_warn   : initialization, namelist read, and parameters control 
     15   !!   getunit    : give the index of an unused logical unit 
    1416   !!---------------------------------------------------------------------- 
    15    USE par_kind 
    16    USE par_oce 
    17    USE lib_print         ! formated print library 
     17   USE par_kind        ! kind definition 
     18   USE par_oce         ! ocean parameter 
     19   USE lib_print       ! formated print library 
    1820 
    1921   IMPLICIT NONE 
     
    7779   INTEGER            ::   nstop = 0                !: error flag (=number of reason for a premature stop run) 
    7880   INTEGER            ::   nwarn = 0                !: warning flag (=number of warning found during the run) 
    79    CHARACTER(len=200) ::   ctmp1, ctmp2, ctmp3      !: temporary character 
     81   CHARACTER(len=200) ::   ctmp1, ctmp2, ctmp3      !: temporary characters 1 to 3 
     82   CHARACTER(len=200) ::   ctmp4, ctmp5, ctmp6      !: temporary characters 4 to 6 
     83   CHARACTER(len=200) ::   ctmp7, ctmp8, ctmp9      !: temporary characters 7 to 9 
     84   CHARACTER(len=200) ::   ctmp10                   !: temporary character 10 
    8085   CHARACTER (len=64) ::   cform_err = "(/,' ===>>> : E R R O R',     /,'         ===========',/)"       !: 
    8186   CHARACTER (len=64) ::   cform_war = "(/,' ===>>> : W A R N I N G', /,'         ===============',/)"   !: 
     
    8388   LOGICAL            ::   lsp_area = .TRUE.        !: to make a control print over a specific area 
    8489   !!---------------------------------------------------------------------- 
    85    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    86    !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/in_out_manager.F90,v 1.11 2007/03/02 16:37:06 opalod Exp $  
     90   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
     91   !! $Id:$ 
    8792   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    8893   !!---------------------------------------------------------------------- 
     
    9297   SUBROUTINE ctl_stop( cd1, cd2, cd3, cd4, cd5,   & 
    9398      &                 cd6, cd7, cd8, cd9, cd10 ) 
    94       !!----------------------------------------------------------------------- 
     99      !!---------------------------------------------------------------------- 
    95100      !!                  ***  ROUTINE  stop_opa  *** 
    96101      !! 
    97       !! ** Purpose : ??? blah blah.... 
    98       !!----------------------------------------------------------------------- 
     102      !! ** Purpose :   print in ocean.outpput file a error message and  
     103      !!                increment the error number (nstop) by one. 
     104      !!---------------------------------------------------------------------- 
    99105      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5 
    100106      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10 
    101       !!----------------------------------------------------------------------- 
     107      !!---------------------------------------------------------------------- 
    102108      ! 
    103109      nstop = nstop + 1  
     
    122128   SUBROUTINE ctl_warn( cd1, cd2, cd3, cd4, cd5,   & 
    123129      &                 cd6, cd7, cd8, cd9, cd10 ) 
    124       !!----------------------------------------------------------------------- 
     130      !!---------------------------------------------------------------------- 
    125131      !!                  ***  ROUTINE  stop_warn  *** 
    126132      !! 
    127       !! ** Purpose : ???  blah blah.... 
    128       !!----------------------------------------------------------------------- 
     133      !! ** Purpose :   print in ocean.outpput file a error message and  
     134      !!                increment the warning number (nwarn) by one. 
     135      !!---------------------------------------------------------------------- 
    129136      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5 
    130137      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10 
    131       !!----------------------------------------------------------------------- 
     138      !!---------------------------------------------------------------------- 
    132139      !  
    133140      nwarn = nwarn + 1  
     
    151158 
    152159   FUNCTION getunit() 
    153      !!----------------------------------------------------------------------- 
    154      !!                  ***  FUNCTION  getunit  *** 
    155      !! 
    156      !! ** Purpose : ???  blah blah.... 
    157      !!----------------------------------------------------------------------- 
    158      INTEGER :: getunit 
    159      LOGICAL :: llopn  
    160      !--------------------------------------------------------------------- 
    161      getunit = 15   ! choose a unit that is big enough then it is 
    162                     !  not already used in OPA 
    163      llopn = .TRUE. 
    164      DO WHILE( (getunit < 998) .AND. llopn ) 
    165         getunit = getunit + 1 
    166         INQUIRE( unit = getunit, opened = llopn ) 
    167      END DO 
    168      IF( (getunit == 999) .AND. llopn ) THEN 
    169         CALL ctl_stop( 'getunit: All logical units until 999 are used...' ) 
    170         getunit = -1 
    171      ENDIF 
    172  
     160      !!---------------------------------------------------------------------- 
     161      !!                  ***  FUNCTION  getunit  *** 
     162      !! 
     163      !! ** Purpose :   return the index of an unused logical unit 
     164      !!---------------------------------------------------------------------- 
     165      INTEGER :: getunit 
     166      LOGICAL :: llopn  
     167      !!---------------------------------------------------------------------- 
     168      ! 
     169      getunit = 15   ! choose a unit that is big enough then it is not already used in NEMO 
     170      llopn = .TRUE. 
     171      DO WHILE( (getunit < 998) .AND. llopn ) 
     172         getunit = getunit + 1 
     173         INQUIRE( unit = getunit, opened = llopn ) 
     174      END DO 
     175      IF( (getunit == 999) .AND. llopn ) THEN 
     176         CALL ctl_stop( 'getunit: All logical units until 999 are used...' ) 
     177         getunit = -1 
     178      ENDIF 
     179      ! 
    173180   END FUNCTION getunit 
    174181 
Note: See TracChangeset for help on using the changeset viewer.