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/UKMO/dev_isf_divg_corr_GO6_package_r9385/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/UKMO/dev_isf_divg_corr_GO6_package_r9385/NEMOGCM/NEMO/OPA_SRC/DOM/iscplini.F90

Last change on this file was 9813, checked in by antsia, 6 years ago

delete iscplhsb, add iscpldiv and make the code readable

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