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/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/DOM – NEMO

source: NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/DOM/iscplini.F90 @ 11671

Last change on this file since 11671 was 11671, checked in by acc, 5 years ago

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Final, non-substantive changes to complete this branch. These changes remove all REWIND statements on the old namelist fortran units (now character variables for internal files). These changes have been left until last since they are easily repeated via a script and it may be preferable to use the previous revision for merge purposes and reapply these last changes separately. This branch has been fully SETTE tested.

  • Property svn:keywords set to Id
File size: 3.9 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   
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
37   !!----------------------------------------------------------------------
38   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
39   !! $Id$
40   !! Software governed by the CeCILL license (see ./LICENSE)
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         !
50      CALL mpp_sum ( 'iscplini', iscpl_alloc )
51      IF( iscpl_alloc > 0 )   CALL ctl_warn('iscpl_alloc: allocation of arrays failed')
52   END FUNCTION iscpl_alloc
53
54
55   SUBROUTINE iscpl_init()
56      !!----------------------------------------------------------------------
57      !!----------------------------------------------------------------------
58      INTEGER ::   ios           ! Local integer output status for namelist read
59      NAMELIST/namsbc_iscpl/ nn_fiscpl, ln_hsb, nn_drown
60      !!----------------------------------------------------------------------
61      !
62      nn_fiscpl = 0
63      ln_hsb    = .FALSE.
64      READ  ( numnam_ref, namsbc_iscpl, IOSTAT = ios, ERR = 901)
65901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_iscpl in reference namelist' )
66      READ  ( numnam_cfg, namsbc_iscpl, IOSTAT = ios, ERR = 902 )
67902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_iscpl in configuration namelist' )
68      IF(lwm) WRITE ( numond, namsbc_iscpl )
69      !
70      nstp_iscpl=MIN( nn_fiscpl, nitend-nit000+1 ) ! the coupling period have to be less or egal than the total number of time step
71      rdt_iscpl = nstp_iscpl * rn_rdt
72      !
73      IF (lwp) THEN
74         WRITE(numout,*) 'iscpl_rst:'
75         WRITE(numout,*) '~~~~~~~~~'
76         WRITE(numout,*) ' coupling     flag (ln_iscpl )            = ', ln_iscpl
77         WRITE(numout,*) ' conservation flag (ln_hsb   )            = ', ln_hsb
78         WRITE(numout,*) ' nb of stp for cons (rn_fiscpl)           = ', nstp_iscpl
79         IF (nstp_iscpl .NE. nn_fiscpl) WRITE(numout,*) 'W A R N I N G: nb of stp for cons has been modified &
80            &                                           (larger than run length)'
81         WRITE(numout,*) ' coupling time step                       = ', rdt_iscpl
82         WRITE(numout,*) ' number of call of the extrapolation loop = ', nn_drown
83      ENDIF
84      !
85   END SUBROUTINE iscpl_init
86
87   !!======================================================================
88END MODULE iscplini
Note: See TracBrowser for help on using the repository browser.