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 branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC/DIU – NEMO

source: branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC/DIU/step_diu.F90 @ 9499

Last change on this file since 9499 was 9499, checked in by davestorkey, 6 years ago

branches/UKMO/dev_merge_2017_CICE_interface : clear SVN keywords.

File size: 4.1 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 diurnal_bulk    ! diurnal SST bulk routines  (diurnal_sst_takaya routine)
9   USE cool_skin       ! diurnal cool skin correction (diurnal_sst_coolskin routine)   
10   USE iom
11   USE sbc_oce
12   USE sbcmod           ! surface boundary condition       (sbc     routine)
13   USE diaobs           ! Observation operator
14   USE oce
15   USE daymod
16   USE restart          ! ocean restart                    (rst_wri routine)
17   USE timing           ! Timing
18   
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   stp_diurnal   ! called by nemogcm.F90 or step.F90
23
24   !!----------------------------------------------------------------------
25   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
26   !! $Id$
27   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
28   !!----------------------------------------------------------------------
29
30   CONTAINS
31
32   SUBROUTINE stp_diurnal( kstp ) 
33      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
34      !!----------------------------------------------------------------------
35      !!                     ***  ROUTINE stp_diurnal  ***
36      !!                       
37      !! ** Purpose : - Time stepping of diurnal SST model only
38      !!   
39      !! ** Method  : -1- Update forcings and data   
40      !!              -2- Update ocean physics   
41      !!              -3- Compute the t and s trends   
42      !!              -4- Update t and s   
43      !!              -5- Compute the momentum trends
44      !!              -6- Update the horizontal velocity
45      !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w)
46      !!              -8- Outputs and diagnostics
47      !!----------------------------------------------------------------------
48      INTEGER ::   jk       ! dummy loop indices
49      INTEGER ::   indic    ! error indicator if < 0
50      REAL(wp), DIMENSION(jpi,jpj) :: z_fvel_bkginc, z_hflux_bkginc     
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 )                      ! Sea Boundary Conditions
63      ENDIF
64     
65      ! Cool skin
66      IF( .NOT.ln_diurnal )   CALL ctl_stop( "stp_diurnal: ln_diurnal not set" )
67         
68      IF( .NOT. ln_blk    )   CALL ctl_stop( "stp_diurnal: diurnal flux processing only implemented for bulk forcing" ) 
69
70      CALL diurnal_sst_coolskin_step( qns, taum, rhop(:,:,1), rdt)
71
72      CALL iom_put( "sst_wl"   , x_dsst               )    ! warm layer (write out before update below).
73      CALL iom_put( "sst_cs"   , x_csdsst             )    ! cool skin
74
75      ! Diurnal warm layer model       
76      CALL diurnal_sst_takaya_step( kstp, & 
77      &    qsr, qns, taum, rhop(:,:,1), rdt) 
78
79      IF( ln_diurnal_only ) THEN
80         IF( ln_diaobs )         CALL dia_obs( kstp )         ! obs-minus-model (assimilation) diagnostics (call after dynamics update)
81     
82         !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
83         ! Control and restarts
84         !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
85         IF( kstp == nit000   )   CALL iom_close( numror )     ! close input  ocean restart file
86         IF( lrst_oce         )   CALL rst_write    ( kstp )   ! write output ocean restart file
87     
88         IF( ln_timing .AND.  kstp == nit000  )   CALL timing_reset 
89      ENDIF
90       
91   END SUBROUTINE stp_diurnal 
92   
93END MODULE step_diu
Note: See TracBrowser for help on using the repository browser.