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.
dynnxt1d.F90 in tags/nemo_v1_01/NEMO/C1D_SRC – NEMO

source: tags/nemo_v1_01/NEMO/C1D_SRC/dynnxt1d.F90 @ 4294

Last change on this file since 4294 was 253, checked in by opalod, 19 years ago

nemo_v1_update_001 : Add the 1D configuration possibility

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.8 KB
Line 
1MODULE dynnxt1d
2   !!======================================================================
3   !!                       ***  MODULE  dynnxt1d  ***
4   !! Ocean dynamics: time stepping in 1D configuration
5   !!======================================================================
6#if defined key_cfg_1d
7   !!----------------------------------------------------------------------
8   !!   'key_cfg_1d'               1D Configuration
9   !!---------------------------------------------------------------------- 
10   !!----------------------------------------------------------------------
11   !!   dyn_nxt_1d   : update the horizontal velocity from the momentum trend
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE in_out_manager  ! I/O manager
17   USE lbclnk          ! lateral boundary condition (or mpp link)
18
19   IMPLICIT NONE
20   PRIVATE
21
22   !! * Accessibility
23   PUBLIC dyn_nxt_1d                ! routine called by step.F90
24   !!----------------------------------------------------------------------
25
26CONTAINS
27
28   SUBROUTINE dyn_nxt_1d ( kt )
29      !!----------------------------------------------------------------------
30      !!                  ***  ROUTINE dyn_nxt_1d  ***
31      !!                   
32      !! ** Purpose :   Compute the after horizontal velocity from the
33      !!      momentum trend.
34      !!
35      !! ** Method  :   Apply lateral boundary conditions on the trends (ua,va)
36      !!      through calls to routine lbc_lnk.
37      !!      After velocity is compute using a leap-frog scheme environment:
38      !!         (ua,va) = (ub,vb) + 2 rdt (ua,va)
39      !!      Time filter applied on now horizontal velocity to avoid the
40      !!      divergence of two consecutive time-steps and swap of dynamics
41      !!      arrays to start the next time step:
42      !!         (ub,vb) = (un,vn) + atfp [ (ub,vb) + (ua,va) - 2 (un,vn) ]
43      !!         (un,vn) = (ua,va)
44      !!
45      !! ** Action : - Update ub,vb arrays, the before horizontal velocity
46      !!             - Update un,vn arrays, the now horizontal velocity
47      !!
48      !! History :
49      !!        !  87-02  (P. Andrich, D. L Hostis)  Original code
50      !!        !  90-10  (C. Levy, G. Madec)
51      !!        !  93-03  (M. Guyon)  symetrical conditions
52      !!        !  97-02  (G. Madec & M. Imbard)  opa, release 8.0
53      !!        !  97-04  (A. Weaver)  Euler forward step
54      !!        !  97-06  (G. Madec)  lateral boudary cond., lbc routine
55      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
56      !!        !  04-10  (C. Ethe) 1D configuration
57      !!----------------------------------------------------------------------
58      !! * Arguments
59      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
60
61      !! * Local declarations
62      INTEGER  ::   ji, jj, jk   ! dummy loop indices
63      REAL(wp) ::   z2dt         ! temporary scalar
64      !!----------------------------------------------------------------------
65      !!  OPA 8.5, LODYC-IPSL (2002)
66      !!----------------------------------------------------------------------
67
68      IF( kt == nit000 ) THEN
69         IF(lwp) WRITE(numout,*)
70         IF(lwp) WRITE(numout,*) 'dyn_nxt_1d : time stepping on 1D configuation'
71         IF(lwp) WRITE(numout,*) '~~~~~~~'
72      ENDIF
73
74      ! Local constant initialization
75      z2dt = 2. * rdt
76      IF( neuler == 0 .AND. kt == nit000 )  z2dt = rdt
77
78      ! Lateral boundary conditions on ( ua, va )
79      CALL lbc_lnk( ua, 'U', -1. )
80      CALL lbc_lnk( va, 'V', -1. )
81
82      !                                                ! ===============
83      DO jk = 1, jpkm1                                 ! Horizontal slab
84         !                                             ! ===============
85         ! Next velocity
86         ! -------------
87         DO jj = 1, jpj                      ! caution: don't use (:,:) for this loop
88            DO ji = 1, jpi                   ! it causes optimization problems on NEC in auto-tasking
89               ! Leap-frog time stepping
90               ua(ji,jj,jk) = ( ub(ji,jj,jk) + z2dt * ua(ji,jj,jk) ) * umask(ji,jj,jk)
91               va(ji,jj,jk) = ( vb(ji,jj,jk) + z2dt * va(ji,jj,jk) ) * vmask(ji,jj,jk)
92            END DO
93         END DO
94         !                                             ! ===============
95      END DO                                           !   End of slab
96      !                                                ! ===============
97 
98     !                                                ! ===============
99      DO jk = 1, jpkm1                                 ! Horizontal slab
100         !                                             ! ===============
101         ! Time filter and swap of dynamics arrays
102         ! ------------------------------------------
103         IF( neuler == 0 .AND. kt == nit000 ) THEN
104            DO jj = 1, jpj                      ! caution: don't use (:,:) for this loop
105               DO ji = 1, jpi                   ! it causes optimization problems on NEC in auto-tasking
106                  ! Euler (forward) time stepping
107                  ub(ji,jj,jk) = un(ji,jj,jk)
108                  vb(ji,jj,jk) = vn(ji,jj,jk)
109                  un(ji,jj,jk) = ua(ji,jj,jk)
110                  vn(ji,jj,jk) = va(ji,jj,jk)
111               END DO
112            END DO
113         ELSE
114            DO jj = 1, jpj                      ! caution: don't use (:,:) for this loop
115               DO ji = 1, jpi                   ! it causes optimization problems on NEC in auto-tasking
116                  ! Leap-frog time stepping
117                  ub(ji,jj,jk) = atfp * ( ub(ji,jj,jk) + ua(ji,jj,jk) ) + atfp1 * un(ji,jj,jk)
118                  vb(ji,jj,jk) = atfp * ( vb(ji,jj,jk) + va(ji,jj,jk) ) + atfp1 * vn(ji,jj,jk)
119                  un(ji,jj,jk) = ua(ji,jj,jk)
120                  vn(ji,jj,jk) = va(ji,jj,jk)
121               END DO
122            END DO
123         ENDIF
124         !                                             ! ===============
125      END DO                                           !   End of slab
126      !                                                ! ===============
127
128      IF(l_ctl)   WRITE(numout,*) ' nxt  - Un: ', SUM(un(2:nictl,2:njctl,1:jpkm1)*umask(2:nictl,2:njctl,1:jpkm1)), &
129      &                                  ' Vn: ', SUM(vn(2:nictl,2:njctl,1:jpkm1)*vmask(2:nictl,2:njctl,1:jpkm1))
130
131   END SUBROUTINE dyn_nxt_1d
132#else
133   !!----------------------------------------------------------------------
134   !!   Default key                                     NO 1D Config
135   !!----------------------------------------------------------------------
136CONTAINS
137   SUBROUTINE dyn_nxt_1d ( kt )
138      WRITE(*,*) 'dyn_nxt_1d: You should not have seen this print! error?', kt
139   END SUBROUTINE dyn_nxt_1d
140#endif
141   !!======================================================================
142END MODULE dynnxt1d
Note: See TracBrowser for help on using the repository browser.