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.
dynnxt_c1d.F90 in trunk/NEMO/C1D_SRC – NEMO

source: trunk/NEMO/C1D_SRC/dynnxt_c1d.F90 @ 900

Last change on this file since 900 was 900, checked in by rblod, 16 years ago

Update 1D configuration according to SBC and LIM3, see ticket #117

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.8 KB
RevLine 
[900]1MODULE dynnxt_c1d
[253]2   !!======================================================================
[900]3   !!                       ***  MODULE  dynnxt_c1d  ***
[253]4   !! Ocean dynamics: time stepping in 1D configuration
5   !!======================================================================
[900]6   !! History :  2.0  !  2004-10  (C. Ethe)  Original code from dynnxt.F90
7   !!            3.0  !  2008-04  (G.madec)  Style only
8   !!----------------------------------------------------------------------
[899]9#if defined key_c1d
[253]10   !!----------------------------------------------------------------------
[900]11   !!   'key_c1d'                                          1D Configuration
[253]12   !!---------------------------------------------------------------------- 
13   !!----------------------------------------------------------------------
[900]14   !!   dyn_nxt_c1d : update the horizontal velocity from the momentum trend
[253]15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE in_out_manager  ! I/O manager
19   USE lbclnk          ! lateral boundary condition (or mpp link)
[321]20   USE prtctl          ! Print control
[253]21
22   IMPLICIT NONE
23   PRIVATE
24
[900]25   PUBLIC dyn_nxt_c1d                ! routine called by step.F90
[253]26   !!----------------------------------------------------------------------
[900]27   !! NEMO/C1D  3.0 , LOCEAN-IPSL (2008)
28   !! $Id:$
29   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
30   !!----------------------------------------------------------------------
[253]31
32CONTAINS
33
[900]34   SUBROUTINE dyn_nxt_c1d ( kt )
[253]35      !!----------------------------------------------------------------------
[900]36      !!                  ***  ROUTINE dyn_nxt_c1d  ***
[253]37      !!                   
38      !! ** Purpose :   Compute the after horizontal velocity from the
39      !!      momentum trend.
40      !!
41      !! ** Method  :   Apply lateral boundary conditions on the trends (ua,va)
42      !!      through calls to routine lbc_lnk.
43      !!      After velocity is compute using a leap-frog scheme environment:
44      !!         (ua,va) = (ub,vb) + 2 rdt (ua,va)
45      !!      Time filter applied on now horizontal velocity to avoid the
46      !!      divergence of two consecutive time-steps and swap of dynamics
47      !!      arrays to start the next time step:
48      !!         (ub,vb) = (un,vn) + atfp [ (ub,vb) + (ua,va) - 2 (un,vn) ]
49      !!         (un,vn) = (ua,va)
50      !!
51      !! ** Action : - Update ub,vb arrays, the before horizontal velocity
52      !!             - Update un,vn arrays, the now horizontal velocity
53      !!----------------------------------------------------------------------
54      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
[900]55      !!
56      INTEGER  ::   jk           ! dummy loop indices
[253]57      REAL(wp) ::   z2dt         ! temporary scalar
58      !!----------------------------------------------------------------------
59
60      IF( kt == nit000 ) THEN
61         IF(lwp) WRITE(numout,*)
[900]62         IF(lwp) WRITE(numout,*) 'dyn_nxt_c1d : time stepping on 1D configuation'
[253]63         IF(lwp) WRITE(numout,*) '~~~~~~~'
64      ENDIF
65
66      ! Local constant initialization
67      z2dt = 2. * rdt
68      IF( neuler == 0 .AND. kt == nit000 )  z2dt = rdt
69
70      ! Lateral boundary conditions on ( ua, va )
71      CALL lbc_lnk( ua, 'U', -1. )
72      CALL lbc_lnk( va, 'V', -1. )
73
[900]74      DO jk = 1, jpkm1      ! Next Velocity
75         ua(:,:,jk) = ( ub(:,:,jk) + z2dt * ua(:,:,jk) ) * umask(:,:,jk)
76         va(:,:,jk) = ( vb(:,:,jk) + z2dt * va(:,:,jk) ) * vmask(:,:,jk)
77      END DO
[253]78 
[900]79      DO jk = 1, jpkm1      ! Time filter and swap of dynamics arrays
80         IF( neuler == 0 .AND. kt == nit000 ) THEN      ! Euler (forward) time stepping
81             ub(:,:,:) = un(:,:,:)
82             vb(:,:,:) = vn(:,:,:)
83             un(:,:,:) = ua(:,:,:)
84             vn(:,:,:) = va(:,:,:)
85         ELSE                                           ! Leap-frog time stepping
86             ub(:,:,:) = atfp * ( ub(:,:,:) + ua(:,:,:) ) + atfp1 * un(:,:,:)
87             vb(:,:,:) = atfp * ( vb(:,:,:) + va(:,:,:) ) + atfp1 * vn(:,:,:)
88             un(:,:,:) = ua(:,:,:)
89             vn(:,:,:) = va(:,:,:)
[253]90         ENDIF
[900]91      END DO
[253]92
[900]93      IF(ln_ctl)   CALL prt_ctl( tab3d_1=un, clinfo1=' nxt_c1d  - Un: ', mask1=umask,   &
94         &                       tab3d_2=vn, clinfo2=' Vn: '           , mask2=vmask )
95      !
96   END SUBROUTINE dyn_nxt_c1d
[253]97
98#else
99   !!----------------------------------------------------------------------
100   !!   Default key                                     NO 1D Config
101   !!----------------------------------------------------------------------
102CONTAINS
[900]103   SUBROUTINE dyn_nxt_c1d ( kt )
104      WRITE(*,*) 'dyn_nxt_c1d: You should not have seen this print! error?', kt
105   END SUBROUTINE dyn_nxt_c1d
[253]106#endif
[900]107
[253]108   !!======================================================================
[900]109END MODULE dynnxt_c1d
Note: See TracBrowser for help on using the repository browser.