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 NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/iscplini.F90 @ 11395

Last change on this file since 11395 was 11395, checked in by mathiot, 5 years ago

ENHANCE-02_ISF_nemo : Initial commit isf simplification (add ISF directory, moved isf routine in and split isf cavity and isf parametrisation, ...) (ticket #2142)

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