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

Last change on this file was 15062, checked in by jchanut, 3 years ago

Suppress time varying scale factors and depths declarations with key_qco and key_linssh. Remove spaces that preclude from correct replacement of some scale factor arrays during preprocessing stage (at least with Apple clang version 11.0.3, this is problem).

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