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.
step_diu.F90 in NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/DIU – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/DIU/step_diu.F90 @ 10927

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

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Tidy up the diurnal cycle code (DIU) to separate its stand-alone functionality from the cool skin and warm layer calculations. The latter can be called from step; the former needs to be kept out of step so that it can implement its own time-level indices.
The stand-alone functionality will need to be revisited once the new timestepping is finalised. SETTE tested (ORCA2_ICE and SAS).

  • Property svn:keywords set to Id
File size: 3.7 KB
Line 
1MODULE step_diu
2   !!======================================================================
3   !!                       ***  MODULE stp_diu  ***
4   !! Time-stepping of diurnal cycle models
5   !!======================================================================
6   !! History :  3.7  ! 2015-11  (J. While)  Original code
7
8   USE diu_layers      ! diurnal SST bulk and coolskin routines
9   USE iom
10   USE sbc_oce
11   USE sbcmod           ! surface boundary condition       (sbc     routine)
12   USE diaobs           ! Observation operator
13   USE oce
14   USE daymod
15   USE restart          ! ocean restart                    (rst_wri routine)
16   USE timing           ! Timing
17   
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC   stp_diurnal   ! called by nemogcm.F90 or step.F90
22
23   !!----------------------------------------------------------------------
24   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
25   !! $Id$
26   !! Software governed by the CeCILL license (see ./LICENSE)
27   !!----------------------------------------------------------------------
28
29   CONTAINS
30
31   SUBROUTINE stp_diurnal( kstp ) 
32      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
33      !!----------------------------------------------------------------------
34      !!                     ***  ROUTINE stp_diurnal  ***
35      !!                       
36      !! ** Purpose : - Time stepping of diurnal SST model only
37      !!   
38      !! ** Method  : -1- Update forcings and data   
39      !!              -2- Update ocean physics   
40      !!              -3- Compute the t and s trends   
41      !!              -4- Update t and s   
42      !!              -5- Compute the momentum trends
43      !!              -6- Update the horizontal velocity
44      !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w)
45      !!              -8- Outputs and diagnostics
46      !!----------------------------------------------------------------------
47      INTEGER ::   jk       ! dummy loop indices
48      INTEGER ::   indic    ! error indicator if < 0
49      REAL(wp), DIMENSION(jpi,jpj) :: z_fvel_bkginc, z_hflux_bkginc     
50      INTEGER :: Nbb, Nnn, Naa, Nrhs    ! local definitions as placeholders for now
51      !! ---------------------------------------------------------------------
52     
53      IF(ln_diurnal_only) THEN
54         indic = 0                                 ! reset to no error condition
55         IF( kstp /= nit000 )   CALL day( kstp )   ! Calendar (day was already called at nit000 in day_init)
56 
57         CALL iom_setkt( kstp - nit000 + 1, cxios_context )   ! tell iom we are at time step kstp
58         IF( ln_crs ) THEN
59            CALL iom_setkt( kstp - nit000 + 1, TRIM(cxios_context)//"_crs" ) ! tell iom we are at time step kstp
60         ENDIF
61       
62            CALL sbc    ( kstp, Nbb, Nnn )            ! Sea Boundary Conditions
63      ENDIF
64     
65      call diurnal_layers( kstp )                     ! coolskin and warm layer calculations
66
67      IF( ln_diurnal_only ) THEN
68         ! WILL HAVE TO INCREMENT Nbb and Nnn here in ln_diurnal_only case !
69         IF( ln_diaobs )         CALL dia_obs( kstp, Nnn )    ! obs-minus-model (assimilation) diagnostics (call after dynamics update)
70     
71         !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
72         ! Control and restarts
73         !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
74         IF( kstp == nit000   )   CALL iom_close( numror )     ! close input  ocean restart file
75         IF( lrst_oce         )   CALL rst_write    ( kstp, Nbb, Nnn )   ! write output ocean restart file
76     
77         IF( ln_timing .AND.  kstp == nit000  )   CALL timing_reset 
78      ENDIF
79       
80   END SUBROUTINE stp_diurnal 
81   
82END MODULE step_diu
Note: See TracBrowser for help on using the repository browser.