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.
dtauvd.F90 in NEMO/trunk/src/OCE/C1D – NEMO

source: NEMO/trunk/src/OCE/C1D/dtauvd.F90 @ 13286

Last change on this file since 13286 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1MODULE dtauvd
2   !!======================================================================
3   !!                     ***  MODULE  dtauvd  ***
4   !! Ocean data  :  read ocean U & V current data from gridded data
5   !!======================================================================
6   !! History :  3.5  ! 2013-08  (D. Calvert)  Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   dta_uvd_init  : read namelist and allocate data structures
11   !!   dta_uvd       : read and time-interpolate ocean U & V current data
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean dynamics and tracers
14   USE phycst         ! physical constants
15   USE dom_oce        ! ocean space and time domain
16   !
17   USE in_out_manager ! I/O manager
18   USE fldread        ! read input fields
19   USE lib_mpp        ! MPP library
20   USE timing         ! Timing
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   dta_uvd_init   ! called by nemogcm.F90
26   PUBLIC   dta_uvd        ! called by istate.F90 and dyndmp.90
27
28   LOGICAL , PUBLIC ::   ln_uvd_init     ! Flag to initialise with U & V current data
29   LOGICAL , PUBLIC ::   ln_uvd_dyndmp   ! Flag for Newtonian damping toward U & V current data
30
31   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_uvd   ! structure for input U & V current (file information and data)
32
33   !! * Substitutions
34#  include "do_loop_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
37   !! $Id$
38   !! Software governed by the CeCILL license (see ./LICENSE)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE dta_uvd_init( ld_dyndmp )
43      !!----------------------------------------------------------------------
44      !!                   ***  ROUTINE dta_uvd_init  ***
45      !!                   
46      !! ** Purpose :   initialization of U & V current input data
47      !!
48      !! ** Method  : - read namc1d_uvd namelist
49      !!              - allocate U & V current data structure
50      !!              - fld_fill data structure with namelist information
51      !!----------------------------------------------------------------------
52      LOGICAL, INTENT(in), OPTIONAL ::   ld_dyndmp   ! force the initialization when dyndmp is used
53      !
54      INTEGER ::   ios, ierr0, ierr1, ierr2, ierr3     ! local integers
55      CHARACTER(len=100)        ::   cn_dir            ! Root directory for location of files to be used
56      TYPE(FLD_N), DIMENSION(2) ::   suv_i             ! Combined U & V namelist information
57      TYPE(FLD_N)               ::   sn_ucur, sn_vcur  ! U & V data namelist information
58      !!
59      NAMELIST/namc1d_uvd/ ln_uvd_init, ln_uvd_dyndmp, cn_dir, sn_ucur, sn_vcur
60      !!----------------------------------------------------------------------
61      !
62      ierr0 = 0   ;   ierr1 = 0   ;   ierr2 = 0  ;   ierr3 = 0
63
64      READ  ( numnam_ref, namc1d_uvd, IOSTAT = ios, ERR = 901)
65901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namc1d_uvd in reference namelist' )
66      !
67      READ  ( numnam_cfg, namc1d_uvd, IOSTAT = ios, ERR = 902 )
68902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namc1d_uvd in configuration namelist' )
69      IF(lwm) WRITE ( numond, namc1d_uvd )
70
71      !                             ! force the initialization when dyndmp is used
72      IF( PRESENT( ld_dyndmp ) )   ln_uvd_dyndmp = .TRUE.
73     
74      IF(lwp) THEN                  ! control print
75         WRITE(numout,*)
76         WRITE(numout,*) 'dta_uvd_init : U & V current data '
77         WRITE(numout,*) '~~~~~~~~~~~~ '
78         WRITE(numout,*) '   Namelist namc1d_uvd : Set flags'
79         WRITE(numout,*) '      Initialization of ocean U & V current with input data   ln_uvd_init   = ', ln_uvd_init
80         WRITE(numout,*) '      Damping of ocean U & V current toward input data        ln_uvd_dyndmp = ', ln_uvd_dyndmp
81         WRITE(numout,*)
82         IF( .NOT. ln_uvd_init .AND. .NOT. ln_uvd_dyndmp ) THEN
83            WRITE(numout,*)
84            WRITE(numout,*) '   U & V current data not used'
85         ENDIF
86      ENDIF
87      !                             ! no initialization when restarting
88      IF( ln_rstart .AND. ln_uvd_init ) THEN
89         CALL ctl_warn( 'dta_uvd_init: ocean restart and U & V current data initialization, ',   &
90            &           'we keep the restart U & V current values and set ln_uvd_init to FALSE' )
91         ln_uvd_init = .FALSE.
92      ENDIF
93
94      !
95      IF(  ln_uvd_init .OR. ln_uvd_dyndmp  ) THEN
96         !                          !==   allocate the data arrays   ==!
97         ALLOCATE( sf_uvd(2), STAT=ierr0 )
98         IF( ierr0 > 0 ) THEN
99            CALL ctl_stop( 'dta_uvd_init: unable to allocate sf_uvd structure' )             ;   RETURN
100         ENDIF
101         !
102                                 ALLOCATE( sf_uvd(1)%fnow(jpi,jpj,jpk)   , STAT=ierr0 )
103         IF( sn_ucur%ln_tint )   ALLOCATE( sf_uvd(1)%fdta(jpi,jpj,jpk,2) , STAT=ierr1 )
104                                 ALLOCATE( sf_uvd(2)%fnow(jpi,jpj,jpk)   , STAT=ierr2 )
105         IF( sn_vcur%ln_tint )   ALLOCATE( sf_uvd(2)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 )
106         !
107         IF( ierr0 + ierr1 + ierr2 + ierr3 > 0 ) THEN
108            CALL ctl_stop( 'dta_uvd_init : unable to allocate U & V current data arrays' )   ;   RETURN
109         ENDIF
110         !                          !==   fill sf_uvd with sn_ucur, sn_vcur and control print   ==!
111         suv_i(1) = sn_ucur   ;   suv_i(2) = sn_vcur
112         CALL fld_fill( sf_uvd, suv_i, cn_dir, 'dta_uvd', 'U & V current data', 'namc1d_uvd' )
113         !
114      ENDIF
115      !
116   END SUBROUTINE dta_uvd_init
117
118
119   SUBROUTINE dta_uvd( kt, Kmm, puvd )
120      !!----------------------------------------------------------------------
121      !!                   ***  ROUTINE dta_uvd  ***
122      !!                   
123      !! ** Purpose :   provides U & V current data at time step kt
124      !!
125      !! ** Method  : - call fldread routine
126      !!              - ORCA_R2: make some hand made alterations to the data (EMPTY)
127      !!              - s- or mixed s-zps coordinate: vertical interpolation onto model mesh
128      !!              - zps coordinate: vertical interpolation onto last partial level
129      !!              - ln_uvd_dyndmp=False: deallocate the U & V current data structure,
130      !!                                     as the data is no longer used
131      !!
132      !! ** Action  :   puvd,  U & V current data interpolated onto model mesh at time-step kt
133      !!----------------------------------------------------------------------
134      INTEGER                           , INTENT(in   ) ::   kt     ! ocean time-step
135      INTEGER                           , INTENT(in   ) ::   Kmm    ! time level index
136      REAL(wp), DIMENSION(jpi,jpj,jpk,2), INTENT(  out) ::   puvd   ! U & V current data
137      !
138      INTEGER ::   ji, jj, jk, jl, jkk               ! dummy loop indicies
139      INTEGER ::   ik, il0, il1, ii0, ii1, ij0, ij1  ! local integers
140      REAL(wp)::   zl, zi                            ! local floats
141      REAL(wp), ALLOCATABLE, DIMENSION(:) ::  zup, zvp   ! 1D workspace
142      !!----------------------------------------------------------------------
143      !
144      IF( ln_timing )   CALL timing_start('dta_uvd')
145      !
146      CALL fld_read( kt, 1, sf_uvd )      !==   read U & V current data at time step kt   ==!
147      !
148      puvd(:,:,:,1) = sf_uvd(1)%fnow(:,:,:)                 ! NO mask
149      puvd(:,:,:,2) = sf_uvd(2)%fnow(:,:,:) 
150      !
151      IF( ln_sco ) THEN                   !==   s- or mixed s-zps-coordinate   ==!
152         !
153         ALLOCATE( zup(jpk), zvp(jpk) )
154         !
155         IF( kt == nit000 .AND. lwp )THEN
156            WRITE(numout,*)
157            WRITE(numout,*) 'dta_uvd: interpolate U & V current data onto the s- or mixed s-z-coordinate mesh'
158         ENDIF
159         !
160         DO_2D_11_11
161            DO jk = 1, jpk
162               zl = gdept(ji,jj,jk,Kmm)
163               IF    ( zl < gdept_1d(1  ) ) THEN          ! extrapolate above the first level of data
164                  zup(jk) =  puvd(ji,jj,1    ,1)
165                  zvp(jk) =  puvd(ji,jj,1    ,2)
166               ELSEIF( zl > gdept_1d(jpk) ) THEN          ! extrapolate below the last level of data
167                  zup(jk) =  puvd(ji,jj,jpkm1,1)
168                  zvp(jk) =  puvd(ji,jj,jpkm1,2)
169               ELSE                                      ! inbetween : vertical interpolation between jkk & jkk+1
170                  DO jkk = 1, jpkm1                      ! when  gdept(jkk) < zl < gdept(jkk+1)
171                     IF( (zl-gdept_1d(jkk)) * (zl-gdept_1d(jkk+1)) <= 0._wp ) THEN
172                        zi = ( zl - gdept_1d(jkk) ) / (gdept_1d(jkk+1)-gdept_1d(jkk))
173                        zup(jk) = puvd(ji,jj,jkk,1) + ( puvd(ji,jj,jkk+1,1 ) - puvd(ji,jj,jkk,1) ) * zi 
174                        zvp(jk) = puvd(ji,jj,jkk,2) + ( puvd(ji,jj,jkk+1,2 ) - puvd(ji,jj,jkk,2) ) * zi
175                     ENDIF
176                  END DO
177               ENDIF
178            END DO
179            DO jk = 1, jpkm1           ! apply mask
180               puvd(ji,jj,jk,1) = zup(jk) * umask(ji,jj,jk)
181               puvd(ji,jj,jk,2) = zvp(jk) * vmask(ji,jj,jk)
182            END DO
183            puvd(ji,jj,jpk,1) = 0._wp
184            puvd(ji,jj,jpk,2) = 0._wp
185         END_2D
186         !
187         DEALLOCATE( zup, zvp )
188         !
189      ELSE                                !==   z- or zps- coordinate   ==!
190         !                             
191         puvd(:,:,:,1) = puvd(:,:,:,1) * umask(:,:,:)       ! apply mask
192         puvd(:,:,:,2) = puvd(:,:,:,2) * vmask(:,:,:)
193         !
194         IF( ln_zps ) THEN                ! zps-coordinate (partial steps) interpolation at the last ocean level
195            DO_2D_11_11
196               ik = mbkt(ji,jj) 
197               IF( ik > 1 ) THEN
198                  zl = ( gdept_1d(ik) - gdept_0(ji,jj,ik) ) / ( gdept_1d(ik) - gdept_1d(ik-1) )
199                  puvd(ji,jj,ik,1) = (1.-zl) * puvd(ji,jj,ik,1) + zl * puvd(ji,jj,ik-1,1)
200                  puvd(ji,jj,ik,2) = (1.-zl) * puvd(ji,jj,ik,2) + zl * puvd(ji,jj,ik-1,2)
201               ENDIF
202            END_2D
203         ENDIF
204         !
205      ENDIF
206      !
207      IF( .NOT. ln_uvd_dyndmp    ) THEN   !==   deallocate U & V current structure   ==!
208         !                                !==   (data used only for initialization)  ==!
209         IF(lwp) WRITE(numout,*) 'dta_uvd: deallocate U & V current arrays as they are only used to initialize the run'
210                                   DEALLOCATE( sf_uvd(1)%fnow )     ! U current arrays in the structure
211         IF( sf_uvd(1)%ln_tint )   DEALLOCATE( sf_uvd(1)%fdta )
212                                   DEALLOCATE( sf_uvd(2)%fnow )     ! V current arrays in the structure
213         IF( sf_uvd(2)%ln_tint )   DEALLOCATE( sf_uvd(2)%fdta )
214                                   DEALLOCATE( sf_uvd         )     ! the structure itself
215      ENDIF
216      !
217      IF( ln_timing )   CALL timing_stop('dta_uvd')
218      !
219   END SUBROUTINE dta_uvd
220
221   !!======================================================================
222END MODULE dtauvd
Note: See TracBrowser for help on using the repository browser.