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.
trcbc.F90 in branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/trcbc.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 16.5 KB
Line 
1MODULE trcbc
2   !!======================================================================
3   !!                     ***  MODULE  trcdta  ***
4   !! TOP :  module for passive tracer boundary conditions
5   !!=====================================================================
6   !!----------------------------------------------------------------------
7#if  defined key_top 
8   !!----------------------------------------------------------------------
9   !!   'key_top'                                                TOP model
10   !!----------------------------------------------------------------------
11   !!   trc_dta    : read and time interpolated passive tracer data
12   !!----------------------------------------------------------------------
13   USE par_trc       !  passive tracers parameters
14   USE oce_trc       !  shared variables between ocean and passive tracers
15   USE trc           !  passive tracers common variables
16   USE iom           !  I/O manager
17   USE lib_mpp       !  MPP library
18   USE fldread       !  read input fields
19
20   USE yomhook, ONLY: lhook, dr_hook
21   USE parkind1, ONLY: jprb, jpim
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   trc_bc_init    ! called in trcini.F90
27   PUBLIC   trc_bc_read    ! called in trcstp.F90 or within
28
29   INTEGER  , SAVE, PUBLIC                             :: nb_trcobc   ! number of tracers with open BC
30   INTEGER  , SAVE, PUBLIC                             :: nb_trcsbc   ! number of tracers with surface BC
31   INTEGER  , SAVE, PUBLIC                             :: nb_trccbc   ! number of tracers with coastal BC
32   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indobc ! index of tracer with OBC data
33   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indsbc ! index of tracer with SBC data
34   INTEGER  , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: n_trc_indcbc ! index of tracer with CBC data
35   INTEGER  , SAVE, PUBLIC                             :: ntra_obc     ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking
36   INTEGER  , SAVE, PUBLIC                             :: ntra_sbc     ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking
37   INTEGER  , SAVE, PUBLIC                             :: ntra_cbc     ! MAX( 1, nb_trcxxx ) to avoid compilation error with bounds checking
38   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trofac   ! multiplicative factor for OBCtracer values
39   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trcobc   ! structure of data input OBC (file informations, fields read)
40   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trsfac   ! multiplicative factor for SBC tracer values
41   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trcsbc   ! structure of data input SBC (file informations, fields read)
42   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trcfac   ! multiplicative factor for CBC tracer values
43   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trccbc   ! structure of data input CBC (file informations, fields read)
44
45   !! * Substitutions
46#  include "domzgr_substitute.h90"
47   !!----------------------------------------------------------------------
48   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
49   !! $Id$
50   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
51   !!----------------------------------------------------------------------
52CONTAINS
53
54   SUBROUTINE trc_bc_init(ntrc)
55      !!----------------------------------------------------------------------
56      !!                   ***  ROUTINE trc_bc_init  ***
57      !!                   
58      !! ** Purpose :   initialisation of passive tracer BC data
59      !!
60      !! ** Method  : - Read namtsd namelist
61      !!              - allocates passive tracer BC data structure
62      !!----------------------------------------------------------------------
63      !
64      INTEGER,INTENT(IN) :: ntrc                           ! number of tracers
65      INTEGER            :: jl, jn                         ! dummy loop indices
66      INTEGER            :: ierr0, ierr1, ierr2, ierr3     ! temporary integers
67      INTEGER            ::  ios                           ! Local integer output status for namelist read
68      CHARACTER(len=100) :: clndta, clntrc
69      !
70      CHARACTER(len=100) :: cn_dir
71      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_i  ! local array of namelist informations on the fields to read
72      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcobc    ! open
73      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcsbc    ! surface
74      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trccbc    ! coastal
75      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trofac    ! multiplicative factor for tracer values
76      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trsfac    ! multiplicative factor for tracer values
77      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trcfac    ! multiplicative factor for tracer values
78      !!
79      NAMELIST/namtrc_bc/ cn_dir, sn_trcobc, rn_trofac, sn_trcsbc, rn_trsfac, sn_trccbc, rn_trcfac 
80      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
81      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
82      REAL(KIND=jprb)               :: zhook_handle
83
84      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_BC_INIT'
85
86      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
87
88      !!----------------------------------------------------------------------
89      IF( nn_timing == 1 )  CALL timing_start('trc_bc_init')
90      !
91      !  Initialisation and local array allocation
92      ierr0 = 0  ;  ierr1 = 0  ;  ierr2 = 0  ;  ierr3 = 0 
93      ALLOCATE( slf_i(ntrc), STAT=ierr0 )
94      IF( ierr0 > 0 ) THEN
95         CALL ctl_stop( 'trc_bc_init: unable to allocate local slf_i' )   ;   RETURN
96      ENDIF
97
98      ! Compute the number of tracers to be initialised with open, surface and boundary data
99      ALLOCATE( n_trc_indobc(ntrc), STAT=ierr0 )
100      IF( ierr0 > 0 ) THEN
101         CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indobc' )   ;   RETURN
102      ENDIF
103      nb_trcobc      = 0
104      n_trc_indobc(:) = 0
105      !
106      ALLOCATE( n_trc_indsbc(ntrc), STAT=ierr0 )
107      IF( ierr0 > 0 ) THEN
108         CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indsbc' )   ;   RETURN
109      ENDIF
110      nb_trcsbc      = 0
111      n_trc_indsbc(:) = 0
112      !
113      ALLOCATE( n_trc_indcbc(ntrc), STAT=ierr0 )
114      IF( ierr0 > 0 ) THEN
115         CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indcbc' )   ;   RETURN
116      ENDIF
117      nb_trccbc      = 0
118      n_trc_indcbc(:) = 0
119      !
120      DO jn = 1, ntrc
121         IF( ln_trc_obc(jn) ) THEN
122             nb_trcobc       = nb_trcobc + 1 
123             n_trc_indobc(jn) = nb_trcobc 
124         ENDIF
125         IF( ln_trc_sbc(jn) ) THEN
126             nb_trcsbc       = nb_trcsbc + 1
127             n_trc_indsbc(jn) = nb_trcsbc
128         ENDIF
129         IF( ln_trc_cbc(jn) ) THEN
130             nb_trccbc       = nb_trccbc + 1
131             n_trc_indcbc(jn) = nb_trccbc
132         ENDIF
133      ENDDO
134      ntra_obc = MAX( 1, nb_trcobc )   ! To avoid compilation error with bounds checking
135      IF( lwp ) WRITE(numout,*) ' '
136      IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with open boundary data :', nb_trcobc
137      IF( lwp ) WRITE(numout,*) ' '
138      ntra_sbc = MAX( 1, nb_trcsbc )   ! To avoid compilation error with bounds checking
139      IF( lwp ) WRITE(numout,*) ' '
140      IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with surface boundary data :', nb_trcsbc
141      IF( lwp ) WRITE(numout,*) ' '
142      ntra_cbc = MAX( 1, nb_trccbc )   ! To avoid compilation error with bounds checking
143      IF( lwp ) WRITE(numout,*) ' '
144      IF( lwp ) WRITE(numout,*) ' Number of passive tracers to be initialized with coastal boundary data :', nb_trccbc
145      IF( lwp ) WRITE(numout,*) ' '
146
147      REWIND( numnat_ref )              ! Namelist namtrc_bc in reference namelist : Passive tracer data structure
148      READ  ( numnat_ref, namtrc_bc, IOSTAT = ios, ERR = 901)
149901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in reference namelist', lwp )
150
151      REWIND( numnat_cfg )              ! Namelist namtrc_bc in configuration namelist : Passive tracer data structure
152      READ  ( numnat_cfg, namtrc_bc, IOSTAT = ios, ERR = 902 )
153902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in configuration namelist', lwp )
154      IF(lwm) WRITE ( numont, namtrc_bc )
155
156      ! print some information for each
157      IF( lwp ) THEN
158         DO jn = 1, ntrc
159            IF( ln_trc_obc(jn) )  THEN   
160               clndta = TRIM( sn_trcobc(jn)%clvar ) 
161               IF(lwp) WRITE(numout,*) 'Preparing to read OBC data file for passive tracer number :', jn, ' name : ', clndta, & 
162               &               ' multiplicative factor : ', rn_trofac(jn)
163            ENDIF
164            IF( ln_trc_sbc(jn) )  THEN   
165               clndta = TRIM( sn_trcsbc(jn)%clvar ) 
166               IF(lwp) WRITE(numout,*) 'Preparing to read SBC data file for passive tracer number :', jn, ' name : ', clndta, & 
167               &               ' multiplicative factor : ', rn_trsfac(jn)
168            ENDIF
169            IF( ln_trc_cbc(jn) )  THEN   
170               clndta = TRIM( sn_trccbc(jn)%clvar ) 
171               IF(lwp) WRITE(numout,*) 'Preparing to read CBC data file for passive tracer number :', jn, ' name : ', clndta, & 
172               &               ' multiplicative factor : ', rn_trcfac(jn)
173            ENDIF
174         END DO
175      ENDIF
176      !
177      ! The following code is written this way to reduce memory usage and repeated for each boundary data
178      ! MAV: note that this is just a placeholder and the dimensions must be changed according to
179      !      what will be done with BDY. A new structure will probably need to be included
180      !
181      ! OPEN Lateral boundary conditions
182      IF( nb_trcobc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero
183         ALLOCATE( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), STAT=ierr1 )
184         IF( ierr1 > 0 ) THEN
185            CALL ctl_stop( 'trc_bc_init: unable to allocate  sf_trcobc structure' )   ;   RETURN
186         ENDIF
187         !
188         DO jn = 1, ntrc
189            IF( ln_trc_obc(jn) ) THEN      ! update passive tracers arrays with input data read from file
190               jl = n_trc_indobc(jn)
191               slf_i(jl)    = sn_trcobc(jn)
192               rf_trofac(jl) = rn_trofac(jn)
193                                            ALLOCATE( sf_trcobc(jl)%fnow(jpi,jpj,jpk)   , STAT=ierr2 )
194               IF( sn_trcobc(jn)%ln_tint )  ALLOCATE( sf_trcobc(jl)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 )
195               IF( ierr2 + ierr3 > 0 ) THEN
196                 CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' )   ;   RETURN
197               ENDIF
198            ENDIF
199            !   
200         ENDDO
201         !                         ! fill sf_trcdta with slf_i and control print
202         CALL fld_fill( sf_trcobc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' )
203         !
204      ENDIF
205      !
206      ! SURFACE Boundary conditions
207      IF( nb_trcsbc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero
208         ALLOCATE( sf_trcsbc(nb_trcsbc), rf_trsfac(nb_trcsbc), STAT=ierr1 )
209         IF( ierr1 > 0 ) THEN
210            CALL ctl_stop( 'trc_bc_init: unable to allocate  sf_trcsbc structure' )   ;   RETURN
211         ENDIF
212         !
213         DO jn = 1, ntrc
214            IF( ln_trc_sbc(jn) ) THEN      ! update passive tracers arrays with input data read from file
215               jl = n_trc_indsbc(jn)
216               slf_i(jl)    = sn_trcsbc(jn)
217               rf_trsfac(jl) = rn_trsfac(jn)
218                                            ALLOCATE( sf_trcsbc(jl)%fnow(jpi,jpj,1)   , STAT=ierr2 )
219               IF( sn_trcsbc(jn)%ln_tint )  ALLOCATE( sf_trcsbc(jl)%fdta(jpi,jpj,1,2) , STAT=ierr3 )
220               IF( ierr2 + ierr3 > 0 ) THEN
221                 CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer SBC data arrays' )   ;   RETURN
222               ENDIF
223            ENDIF
224            !   
225         ENDDO
226         !                         ! fill sf_trcsbc with slf_i and control print
227         CALL fld_fill( sf_trcsbc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer SBC data', 'namtrc_bc' )
228         !
229      ENDIF
230      !
231      ! COSTAL Boundary conditions
232      IF( nb_trccbc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero
233         ALLOCATE( sf_trccbc(nb_trccbc), rf_trcfac(nb_trccbc), STAT=ierr1 )
234         IF( ierr1 > 0 ) THEN
235            CALL ctl_stop( 'trc_bc_ini: unable to allocate  sf_trccbc structure' )   ;   RETURN
236         ENDIF
237         !
238         DO jn = 1, ntrc
239            IF( ln_trc_cbc(jn) ) THEN      ! update passive tracers arrays with input data read from file
240               jl = n_trc_indcbc(jn)
241               slf_i(jl)    = sn_trccbc(jn)
242               rf_trcfac(jl) = rn_trcfac(jn)
243                                            ALLOCATE( sf_trccbc(jl)%fnow(jpi,jpj,1)   , STAT=ierr2 )
244               IF( sn_trccbc(jn)%ln_tint )  ALLOCATE( sf_trccbc(jl)%fdta(jpi,jpj,1,2) , STAT=ierr3 )
245               IF( ierr2 + ierr3 > 0 ) THEN
246                 CALL ctl_stop( 'trc_bc_ini : unable to allocate passive tracer CBC data arrays' )   ;   RETURN
247               ENDIF
248            ENDIF
249            !   
250         ENDDO
251         !                         ! fill sf_trccbc with slf_i and control print
252         CALL fld_fill( sf_trccbc, slf_i, cn_dir, 'trc_bc_init', 'Passive tracer CBC data', 'namtrc_bc' )
253         !
254      ENDIF
255 
256      DEALLOCATE( slf_i )          ! deallocate local field structure
257      IF( nn_timing == 1 )  CALL timing_stop('trc_bc_init')
258
259      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
260   END SUBROUTINE trc_bc_init
261
262
263   SUBROUTINE trc_bc_read(kt)
264      !!----------------------------------------------------------------------
265      !!                   ***  ROUTINE trc_bc_init  ***
266      !!
267      !! ** Purpose :  Read passive tracer Boundary Conditions data
268      !!
269      !! ** Method  :  Read BC inputs and update data structures using fldread
270      !!             
271      !!----------------------------------------------------------------------
272   
273      ! NEMO
274      USE fldread
275     
276      !! * Arguments
277      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
278      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
279      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
280      REAL(KIND=jprb)               :: zhook_handle
281
282      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_BC_READ'
283
284      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
285
286
287      !!---------------------------------------------------------------------
288      !
289      IF( nn_timing == 1 )  CALL timing_start('trc_bc_read')
290
291      IF( kt == nit000 ) THEN
292         IF(lwp) WRITE(numout,*)
293         IF(lwp) WRITE(numout,*) 'trc_bc_read : Surface boundary conditions for passive tracers.'
294         IF(lwp) WRITE(numout,*) '~~~~~~~ '
295      ENDIF
296
297      ! OPEN boundary conditions: DOES NOT WORK. Waiting for stable BDY
298      IF( nb_trcobc > 0 ) THEN
299        if (lwp) write(numout,'(a,i5,a,i5)') '   reading OBC data for ', nb_trcobc ,' variables at step ', kt
300        CALL fld_read(kt,1,sf_trcobc)
301        ! vertical interpolation on s-grid and partial step to be added
302      ENDIF
303
304      ! SURFACE boundary conditions       
305      IF( nb_trcsbc > 0 ) THEN
306        if (lwp) write(numout,'(a,i5,a,i5)') '   reading SBC data for ', nb_trcsbc ,' variables at step ', kt
307        CALL fld_read(kt,1,sf_trcsbc)
308      ENDIF
309
310      ! COASTAL boundary conditions       
311      IF( nb_trccbc > 0 ) THEN
312        if (lwp) write(numout,'(a,i5,a,i5)') '   reading CBC data for ', nb_trccbc ,' variables at step ', kt
313        CALL fld_read(kt,1,sf_trccbc)
314      ENDIF   
315      !
316      IF( nn_timing == 1 )  CALL timing_stop('trc_bc_read')
317      !       
318
319      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
320   END SUBROUTINE trc_bc_read
321#else
322   !!----------------------------------------------------------------------
323   !!   Dummy module                              NO 3D passive tracer data
324   !!----------------------------------------------------------------------
325CONTAINS
326   SUBROUTINE trc_bc_read( kt )        ! Empty routine
327   INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
328   INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
329   REAL(KIND=jprb)               :: zhook_handle
330
331   CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_BC_READ'
332
333   IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
334
335      WRITE(*,*) 'trc_bc_read: You should not have seen this print! error?', kt
336   IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
337   END SUBROUTINE trc_bc_read
338#endif
339
340   !!======================================================================
341END MODULE trcbc
Note: See TracBrowser for help on using the repository browser.