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/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIU – NEMO

source: branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIU/step_diu.F90 @ 6010

Last change on this file since 6010 was 6010, checked in by timgraham, 8 years ago

Tidying of DIU code

File size: 3.8 KB
RevLine 
[6010]1MODULE stp_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 step_oce         ! time stepping definition modules
9   USE iom
10
11   PUBLIC   stp_diurnal   ! called by nemogcm.F90 or step.F90
12
13   IMPLICIT NONE
14   PRIVATE
15   !!----------------------------------------------------------------------
16   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
17   !! $Id:$
18   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
19   !!----------------------------------------------------------------------
20
21   CONTAINS
22
23   SUBROUTINE stp_diurnal( kstp ) 
24      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index
25      !!----------------------------------------------------------------------
26      !!                     ***  ROUTINE stp_diurnal  ***
27      !!                       
28      !! ** Purpose : - Time stepping of diurnal SST model only
29      !!   
30      !! ** Method  : -1- Update forcings and data   
31      !!              -2- Update ocean physics   
32      !!              -3- Compute the t and s trends   
33      !!              -4- Update t and s   
34      !!              -5- Compute the momentum trends
35      !!              -6- Update the horizontal velocity
36      !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w)
37      !!              -8- Outputs and diagnostics
38      !!----------------------------------------------------------------------
39      INTEGER ::   jk       ! dummy loop indices
40      INTEGER ::   indic    ! error indicator if < 0
41      REAL(wp), DIMENSION(jpi,jpj) :: z_fvel_bkginc, z_hflux_bkginc     
42      !! ---------------------------------------------------------------------
43     
44      IF(ln_diurnal_only) THEN
45         indic = 0                                 ! reset to no error condition
46         IF( kstp /= nit000 )   CALL day( kstp )   ! Calendar (day was already called at nit000 in day_init)
47 
48         CALL iom_setkt( kstp - nit000 + 1, cxios_context )   ! tell iom we are at time step kstp
49         IF( ln_crs ) THEN
50            CALL iom_setkt( kstp - nit000 + 1, TRIM(cxios_context)//"_crs" ) ! tell iom we are at time step kstp
51         ENDIF
52       
53            CALL sbc    ( kstp )                      ! Sea Boundary Conditions
54      ENDIF
55     
56      ! Cool skin
57      IF ( .NOT.ln_diurnal ) CALL ctl_stop(  "stp_diurnal: ln_diurnal not set"  )
58         
59      IF ( .NOT. ln_blk_core ) THEN
60         CALL ctl_stop("step.f90: diurnal flux processing only implemented"//&
61         &             " for core forcing") 
62      ENDIF
63
64      CALL diurnal_sst_coolskin_step( qns, taum, rhop(:,:,1), rdt)
65
66      CALL iom_put( "sst_wl"   , x_dsst               )    ! warm layer (write out before update below).
67      CALL iom_put( "sst_cs"   , x_csdsst             )    ! cool skin
68
69      ! Diurnal warm layer model       
70      CALL diurnal_sst_takaya_step( kstp, & 
71      &    qsr, qns, taum, rhop(:,:,1), rdt) 
72
73      IF(ln_diurnal_only) THEN
74         IF( ln_diaobs )         CALL dia_obs( kstp )         ! obs-minus-model (assimilation) diagnostics (call after dynamics update)
75     
76         !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
77         ! Control and restarts
78         !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
79         IF( kstp == nit000   )   CALL iom_close( numror )     ! close input  ocean restart file
80         IF( lrst_oce         )   CALL rst_write    ( kstp )   ! write output ocean restart file
81     
82         IF( nn_timing == 1 .AND.  kstp == nit000  )   CALL timing_reset 
83      ENDIF
84       
85   END SUBROUTINE stp_diurnal 
86   
87END MODULE stp_diu
Note: See TracBrowser for help on using the repository browser.