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.
iscplini.F90 in branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/iscplini.F90 @ 9168

Last change on this file since 9168 was 9168, checked in by gm, 6 years ago

dev_merge_2017: OPA_SRC & CONFIG: remove useless warning when reading namelist_cfg

File size: 4.2 KB
RevLine 
[5790]1MODULE iscplini
2   !!======================================================================
[7646]3   !!                       ***  MODULE  sbciscpl  ***
[9168]4   !! Ocean forcing:  ?????
[5790]5   !!=====================================================================
6   !! History :  NEMO  ! 2015-01 P. Mathiot: original
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
[5835]10   !!   iscpl_init     : initialisation routine (namelist)
11   !!   iscpl_alloc    : allocation of correction variables
[5790]12   !!----------------------------------------------------------------------
[9019]13   USE oce             ! global tra/dyn variable
[5790]14   USE dom_oce         ! ocean space and time domain
[9019]15   !
[5790]16   USE lib_mpp         ! MPP library
17   USE lib_fortran     ! MPP library
[5823]18   USE in_out_manager  ! I/O manager
[5790]19
20   IMPLICIT NONE
21   PRIVATE
22   
23   PUBLIC   iscpl_init     
24   PUBLIC   iscpl_alloc 
[9168]25   
26   !                                 !!* namsbc_iscpl namelist *
27   LOGICAL , PUBLIC ::   ln_hsb       !:
28   INTEGER , PUBLIC ::   nn_fiscpl    !:
29   INTEGER , PUBLIC ::   nn_drown     !:
30   
31   INTEGER , PUBLIC ::   nstp_iscpl   !:
32   REAL(wp), PUBLIC ::   rdt_iscpl    !:
33   !
34   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   hdiv_iscpl   !:
35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   htsc_iscpl   !:
36
[5790]37   !!----------------------------------------------------------------------
[9168]38   !! NEMO/OPA 4.0 , NEMO Consortium (2017)
39   !! $Id:$
[5790]40   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   INTEGER FUNCTION iscpl_alloc()
45      !!----------------------------------------------------------------------
46      !!                ***  ROUTINE sbc_iscpl_alloc  ***
47      !!----------------------------------------------------------------------
48      ALLOCATE( htsc_iscpl(jpi,jpj,jpk,jpts) , hdiv_iscpl(jpi,jpj,jpk) , STAT=iscpl_alloc )
49         !
[5823]50      IF( lk_mpp          )   CALL mpp_sum ( iscpl_alloc )
[5790]51      IF( iscpl_alloc > 0 )   CALL ctl_warn('iscpl_alloc: allocation of arrays failed')
52   END FUNCTION iscpl_alloc
53
[9019]54
[5790]55   SUBROUTINE iscpl_init()
[9019]56      !!----------------------------------------------------------------------
[9168]57      !!----------------------------------------------------------------------
[5790]58      INTEGER ::   ios           ! Local integer output status for namelist read
[9019]59      NAMELIST/namsbc_iscpl/ nn_fiscpl, ln_hsb, nn_drown
[5790]60      !!----------------------------------------------------------------------
61      !
[5920]62      nn_fiscpl = 0
[5790]63      ln_hsb    = .FALSE.
64      REWIND( numnam_ref )              ! Namelist namsbc_iscpl in reference namelist : Ice sheet coupling
65      READ  ( numnam_ref, namsbc_iscpl, IOSTAT = ios, ERR = 901)
[9168]66901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_iscpl in reference namelist', lwp )
[5790]67      REWIND( numnam_cfg )              ! Namelist namsbc_iscpl in configuration namelist : Ice Sheet coupling
68      READ  ( numnam_cfg, namsbc_iscpl, IOSTAT = ios, ERR = 902 )
[9168]69902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_iscpl in configuration namelist', lwp )
[5790]70      IF(lwm) WRITE ( numond, namsbc_iscpl )
71      !
[9168]72      nstp_iscpl=MIN( nn_fiscpl, nitend-nit000+1 ) ! the coupling period have to be less or egal than the total number of time step
[5920]73      rdt_iscpl = nstp_iscpl * rn_rdt
[5790]74      !
75      IF (lwp) THEN
76         WRITE(numout,*) 'iscpl_rst:'
77         WRITE(numout,*) '~~~~~~~~~'
[5920]78         WRITE(numout,*) ' coupling     flag (ln_iscpl )            = ', ln_iscpl
79         WRITE(numout,*) ' conservation flag (ln_hsb   )            = ', ln_hsb
80         WRITE(numout,*) ' nb of stp for cons (rn_fiscpl)           = ', nstp_iscpl
81         IF (nstp_iscpl .NE. nn_fiscpl) WRITE(numout,*) 'W A R N I N G: nb of stp for cons has been modified &
82            &                                           (larger than run length)'
83         WRITE(numout,*) ' coupling time step                       = ', rdt_iscpl
84         WRITE(numout,*) ' number of call of the extrapolation loop = ', nn_drown
[9019]85      ENDIF
86      !
[5790]87   END SUBROUTINE iscpl_init
88
[9019]89   !!======================================================================
[5790]90END MODULE iscplini
Note: See TracBrowser for help on using the repository browser.