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

Changeset 79


Ignore:
Timestamp:
2004-04-22T14:57:11+02:00 (20 years ago)
Author:
opalod
Message:

CT : UPDATE053 : Use logical key "lk_isl" instead of "l_isl"

Location:
trunk/NEMO/OPA_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/SOL/solver.F90

    r41 r79  
    2121   USE dynspg_rl        
    2222   USE dynspg_fsc       
    23    USE dynspg_fsc_atsk  
     23   USE dynspg_fsc_atsk       
    2424 
    2525   IMPLICIT NONE 
     
    3737      !! ** Purpose :   Initialization for the solver of the elliptic equation: 
    3838      !!       * default option: barotropic stream function system 
    39       !!         and islands initialization (if l_isl=T) 
     39      !!         and islands initialization (if lk_isl=T) 
    4040      !!       * lk_dynspg_fsc = T : transport divergence system. No specific 
    4141      !!         treatment of islands. 
     
    5151      !!       - Construct the matrix of the elliptic system by a call to 
    5252      !!      solmat.F routine. 
    53       !!       - island (if l_isl=T) 
     53      !!       - island (if lk_isl=T) 
    5454      !!            isl_dom: find islands from the bathymetry file 
    5555      !!            isl_bsf: compute the island barotropic stream function 
     
    8383 
    8484      IF(lwp) WRITE(numout,*) 
    85       IF(lwp) WRITE(numout,*) 'ini_sol : solver to compute the surface pressure gradient' 
    86       IF(lwp) WRITE(numout,*) '~~~~~~~' 
     85      IF(lwp) WRITE(numout,*) 'solver_init : solver to compute the surface pressure gradient' 
     86      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    8787 
    8888      ! open elliptic solver statistics file 
     
    110110 
    111111      IF(lwp) THEN 
    112          WRITE(numout,*) 
    113112         WRITE(numout,*) '             type of elliptic solver        nsolv  = ', nsolv 
    114113         WRITE(numout,*) '             maximum iterations for solver  nmax   = ', nmax 
    115114         WRITE(numout,*) '             absolute precision of solver   eps    = ', eps 
    116115         WRITE(numout,*) '             optimal coefficient of sor     sor    = ', sor 
    117          IF(l_isl) WRITE(numout,*) '             absolute precision stream fct  epsisl = ', epsisl 
    118          IF(l_isl) WRITE(numout,*) '             maximum pcg iterations island  nmisl  = ', nmisl 
     116         IF(lk_isl) WRITE(numout,*) '             absolute precision stream fct  epsisl = ', epsisl 
     117         IF(lk_isl) WRITE(numout,*) '             maximum pcg iterations island  nmisl  = ', nmisl 
    119118         WRITE(numout,*) '             free surface parameter         rnu    = ', rnu 
    120119         WRITE(numout,*) 
     
    123122      IF( lk_dynspg_fsc .OR. lk_dynspg_fsc_tsk ) THEN 
    124123         IF(lwp) WRITE(numout,*) 
    125          IF(lwp) WRITE(numout,*) '          *** free surface formulation' 
    126          IF( l_isl ) THEN 
     124         IF(lwp) WRITE(numout,*) '          free surface formulation' 
     125         IF( lk_isl ) THEN 
    127126            IF(lwp) WRITE(numout,cform_err) 
    128127            IF(lwp) WRITE(numout,*) ' key_islands inconsistent with key_dynspg_fsc' 
     
    131130      ELSEIF( lk_dynspg_rl ) THEN 
    132131         IF(lwp) WRITE(numout,*) 
    133          IF(lwp) WRITE(numout,*) '          *** Rigid lid formulation' 
     132         IF(lwp) WRITE(numout,*) '          Rigid lid formulation' 
    134133      ELSE 
    135134         IF(lwp) WRITE(numout,cform_err) 
     
    137136         nstop = nstop + 1 
    138137      ENDIF 
    139       IF( lk_dynspg_fsc .AND. lk_dynspg_rl ) THEN 
     138      IF( ( lk_dynspg_fsc .OR. lk_dynspg_fsc_tsk ) .AND. lk_dynspg_rl ) THEN 
    140139         IF(lwp) WRITE(numout,cform_err) 
    141140         IF(lwp) WRITE(numout,*) '          Chose between free surface or rigid-lid, not both' 
     
    146145 
    147146      CASE ( 1 )                ! preconditioned conjugate gradient solver 
    148          IF(lwp) WRITE(numout,*) '          use a preconditioned conjugate gradient solver' 
     147         IF(lwp) WRITE(numout,*) '          a preconditioned conjugate gradient solver is used' 
    149148 
    150149      CASE ( 2 )                ! successive-over-relaxation solver 
    151          IF(lwp) WRITE(numout,*) '          use a successive-over-relaxation solver' 
     150         IF(lwp) WRITE(numout,*) '          a successive-over-relaxation solver is used' 
    152151 
    153152      CASE ( 3 )                ! FETI solver 
    154          IF(lwp) WRITE(numout,*) '          use the FETI solver' 
     153         IF(lwp) WRITE(numout,*) '          the FETI solver is used' 
    155154         IF( .NOT.lk_mpp ) THEN 
     155            IF(lwp) WRITE(numout,cform_err) 
    156156            IF(lwp) WRITE(numout,*) ' The FETI algorithm is used only with the key_mpp_... option' 
    157157            nstop = nstop + 1 
    158158         ELSE 
    159159            IF( jpnij == 1 ) THEN 
     160               IF(lwp) WRITE(numout,cform_err) 
    160161               IF(lwp) WRITE(numout,*) ' The FETI algorithm needs more than one processor' 
    161162               nstop = nstop + 1 
     
    194195 
    195196 
    196       IF( l_isl ) THEN 
     197      IF( lk_isl ) THEN 
    197198       
    198199         ! Islands in the domain 
  • trunk/NEMO/OPA_SRC/istate.F90

    r15 r79  
    166166      END DO 
    167167 
    168       ! Print 
    169       IF(lwp) CALL prizre(tn,jpi,jpj,jpk,jpj/2,1,jpi,5,1,jpk,1,1.,numout) 
     168      IF(lwp) CALL prizre( tn    , jpi   , jpj   , jpk   , jpj/2 ,   & 
     169         &                 1     , jpi   , 5     , 1     , jpk   ,   & 
     170         &                 1     , 1.    , numout                  ) 
    170171 
    171172   END SUBROUTINE istate_tem 
     
    355356 
    356357 
    357             IF( l_isl ) THEN 
     358            IF( lk_isl ) THEN 
    358359               ! Horizontal velocity : start from geostrophy (EEL config) 
    359360               CALL eos( tn, sn, rhd )     ! now in situ density 
     
    506507      vn(:,:,:) = vb(:,:,:) 
    507508        
    508 #if ! defined key_dynspg_fsc 
    509       IF( l_isl )   bsfb(:,:) = bsfn(:,:)          ! Put bsfb to zero 
     509#if defined key_dynspg_rl 
     510      IF( lk_isl )   bsfb(:,:) = bsfn(:,:)          ! Put bsfb to zero 
    510511#endif 
    511512 
  • trunk/NEMO/OPA_SRC/stpctl.F90

    r15 r79  
    6262         WRITE(numout,*) 
    6363         WRITE(numout,*) 'stp_ctl : time-stepping control' 
    64          WRITE(numout,*) '~~~' 
     64         WRITE(numout,*) '~~~~~~~' 
    6565         ! open time.step file 
    6666         CALL ctlopn( numstp, 'time.step', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, 1 ) 
     
    8181 
    8282      ! Islands (if exist) 
    83       IF( l_isl )   CALL isl_stp_ctl( kt, kindic ) 
     83      IF( lk_isl )   CALL isl_stp_ctl( kt, kindic ) 
    8484 
    8585 
     
    103103      ! ------------------------ 
    104104      !! zumax = MAXVAL( ABS( un(:,:,:) ) )   ! slower than the following loop on NEC SX5 
    105       zumax = 0.0 
     105      zumax = 0.e0 
    106106      DO jk = 1, jpk 
    107107         DO jj = 1, jpj 
     
    144144      !! zsmin = MINVAL( sn(:,:,1), mask = tmask(:,:,1) == 1.e0 )     
    145145      !                slower than the following loop on NEC SX5 
    146       zsmin = 100.0 
     146      zsmin = 100.e0 
    147147      DO jj = 2, jpjm1 
    148148         DO ji = 1, jpi 
Note: See TracChangeset for help on using the changeset viewer.