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/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC/trcbc.F90 @ 6862

Last change on this file since 6862 was 6862, checked in by lovato, 8 years ago

#1729 - trunk: removed key_bdy from the code and set usage of ln_bdy. Tested with SETTE.

  • Property svn:keywords set to Id
File size: 20.2 KB
Line 
1MODULE trcbc
2   !!======================================================================
3   !!                     ***  MODULE  trcbc  ***
4   !! TOP :  module for passive tracer boundary conditions
5   !!=====================================================================
6   !! History :  3.5 !  2014-04  (M. Vichi, T. Lovato)  Original
7   !!            3.6 !  2015-03  (T . Lovato) Revision and BDY support
8   !!----------------------------------------------------------------------
9#if defined key_top
10   !!----------------------------------------------------------------------
11   !!   'key_top'                                                TOP model
12   !!----------------------------------------------------------------------
13   !!   trc_bc       : read and time interpolated tracer Boundary Conditions
14   !!----------------------------------------------------------------------
15   USE par_trc       !  passive tracers parameters
16   USE oce_trc       !  shared variables between ocean and passive tracers
17   USE trc           !  passive tracers common variables
18   USE iom           !  I/O manager
19   USE lib_mpp       !  MPP library
20   USE fldread       !  read input fields
21   USE bdy_oce,  ONLY: ln_bdy, nb_bdy , idx_bdy, ln_coords_file, rn_time_dmp, rn_time_dmp_out
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   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trsfac    ! multiplicative factor for SBC tracer values
36   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trcsbc    ! structure of data input SBC (file informations, fields read)
37   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trcfac    ! multiplicative factor for CBC tracer values
38   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: sf_trccbc    ! structure of data input CBC (file informations, fields read)
39   REAL(wp) , SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:)  :: rf_trofac    ! multiplicative factor for OBCtracer values
40   TYPE(FLD), SAVE, PUBLIC, ALLOCATABLE, DIMENSION(:), TARGET  :: sf_trcobc    ! structure of data input OBC (file informations, fields read)
41   TYPE(MAP_POINTER), ALLOCATABLE, DIMENSION(:) :: nbmap_ptr   ! array of pointers to nbmap
42
43   !!----------------------------------------------------------------------
44   !! NEMO/OPA 3.6 , NEMO Consortium (2015)
45   !! $Id$
46   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48CONTAINS
49
50   SUBROUTINE trc_bc_init( ntrc )
51      !!----------------------------------------------------------------------
52      !!                   ***  ROUTINE trc_bc_init  ***
53      !!                   
54      !! ** Purpose :   initialisation of passive tracer BC data
55      !!
56      !! ** Method  : - Read namtsd namelist
57      !!              - allocates passive tracer BC data structure
58      !!----------------------------------------------------------------------
59      !
60      INTEGER,INTENT(IN) :: ntrc                           ! number of tracers
61      INTEGER            :: jl, jn , ib, ibd, ii, ij, ik   ! dummy loop indices
62      INTEGER            :: ierr0, ierr1, ierr2, ierr3     ! temporary integers
63      INTEGER            :: ios                            ! Local integer output status for namelist read
64      INTEGER            :: nblen, igrd                    ! support arrays for BDY
65      CHARACTER(len=100) :: clndta, clntrc
66      !
67      CHARACTER(len=100) :: cn_dir_sbc, cn_dir_cbc, cn_dir_obc
68
69      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) :: slf_i  ! local array of namelist informations on the fields to read
70      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcobc    ! open
71      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trcsbc    ! surface
72      TYPE(FLD_N), DIMENSION(jpmaxtrc) :: sn_trccbc    ! coastal
73      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trofac    ! multiplicative factor for tracer values
74      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trsfac    ! multiplicative factor for tracer values
75      REAL(wp)   , DIMENSION(jpmaxtrc) :: rn_trcfac    ! multiplicative factor for tracer values
76      !!
77      NAMELIST/namtrc_bc/ cn_dir_sbc, cn_dir_cbc, cn_dir_obc, sn_trcobc, rn_trofac, sn_trcsbc, rn_trsfac, sn_trccbc, rn_trcfac
78      NAMELIST/namtrc_bdy/ cn_trc_dflt, cn_trc, nn_trcdmp_bdy
79
80      !!----------------------------------------------------------------------
81      IF( nn_timing == 1 )  CALL timing_start('trc_bc_init')
82      !
83      IF( lwp ) THEN
84         WRITE(numout,*) ' '
85         WRITE(numout,*) 'trc_bc_init : Tracers Boundary Conditions (BC)'
86         WRITE(numout,*) '~~~~~~~~~~~ '
87      ENDIF
88      !  Initialisation and local array allocation
89      ierr0 = 0  ;  ierr1 = 0  ;  ierr2 = 0  ;  ierr3 = 0 
90      ALLOCATE( slf_i(ntrc), STAT=ierr0 )
91      IF( ierr0 > 0 ) THEN
92         CALL ctl_stop( 'trc_bc_init: unable to allocate local slf_i' )   ;   RETURN
93      ENDIF
94
95      ! Compute the number of tracers to be initialised with open, surface and boundary data
96      ALLOCATE( n_trc_indobc(ntrc), STAT=ierr0 )
97      IF( ierr0 > 0 ) THEN
98         CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indobc' )   ;   RETURN
99      ENDIF
100      nb_trcobc      = 0
101      n_trc_indobc(:) = 0
102      !
103      ALLOCATE( n_trc_indsbc(ntrc), STAT=ierr0 )
104      IF( ierr0 > 0 ) THEN
105         CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indsbc' )   ;   RETURN
106      ENDIF
107      nb_trcsbc      = 0
108      n_trc_indsbc(:) = 0
109      !
110      ALLOCATE( n_trc_indcbc(ntrc), STAT=ierr0 )
111      IF( ierr0 > 0 ) THEN
112         CALL ctl_stop( 'trc_bc_init: unable to allocate n_trc_indcbc' )   ;   RETURN
113      ENDIF
114      nb_trccbc      = 0
115      n_trc_indcbc(:) = 0
116      !
117      ! Read Boundary Conditions Namelists
118      REWIND( numnat_ref )              ! Namelist namtrc_bc in reference namelist : Passive tracer data structure
119      READ  ( numnat_ref, namtrc_bc, IOSTAT = ios, ERR = 901)
120901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in reference namelist', lwp )
121
122      REWIND( numnat_cfg )              ! Namelist namtrc_bc in configuration namelist : Passive tracer data structure
123      READ  ( numnat_cfg, namtrc_bc, IOSTAT = ios, ERR = 902 )
124902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bc in configuration namelist', lwp )
125      IF(lwm) WRITE ( numont, namtrc_bc )
126
127      IF ( ln_bdy ) THEN
128         REWIND( numnat_ref )              ! Namelist namtrc_bdy in reference namelist : Passive tracer data structure
129         READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903)
130903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp )
131
132         REWIND( numnat_cfg )              ! Namelist namtrc_bdy in configuration namelist : Passive tracer data structure
133         READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 )
134904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp )
135         IF(lwm) WRITE ( numont, namtrc_bdy )
136     
137         ! setup up preliminary informations for BDY structure
138         DO jn = 1, ntrc
139            DO ib = 1, nb_bdy
140               ! Set type of obc in BDY data structure (around here we may plug user override of obc type from nml)
141               IF ( ln_trc_obc(jn) ) THEN
142                  trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) )
143               ELSE
144                  trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc_dflt(ib) )
145               ENDIF
146               ! set damping use in BDY data structure
147               trcdta_bdy(jn,ib)%dmp = .false.
148               IF(nn_trcdmp_bdy(ib) .EQ. 1 .AND. ln_trc_obc(jn) ) trcdta_bdy(jn,ib)%dmp = .true.
149               IF(nn_trcdmp_bdy(ib) .EQ. 2 ) trcdta_bdy(jn,ib)%dmp = .true.
150               IF(trcdta_bdy(jn,ib)%cn_obc == 'frs' .AND. nn_trcdmp_bdy(ib) .NE. 0 )  &
151                   & CALL ctl_stop( 'Use FRS OR relaxation' )
152               IF (nn_trcdmp_bdy(ib) .LT. 0 .OR. nn_trcdmp_bdy(ib) .GT. 2)            &
153                   & CALL ctl_stop( 'Not a valid option for nn_trcdmp_bdy. Allowed: 0,1,2.' )
154            ENDDO
155         ENDDO
156      ELSE
157         ! Force all tracers OBC to false if bdy not used
158         ln_trc_obc = .false.
159      ENDIF
160
161      ! compose BC data indexes
162      DO jn = 1, ntrc
163         IF( ln_trc_obc(jn) ) THEN
164             nb_trcobc       = nb_trcobc + 1  ; n_trc_indobc(jn) = nb_trcobc
165         ENDIF
166         IF( ln_trc_sbc(jn) ) THEN
167             nb_trcsbc       = nb_trcsbc + 1  ; n_trc_indsbc(jn) = nb_trcsbc
168         ENDIF
169         IF( ln_trc_cbc(jn) ) THEN
170             nb_trccbc       = nb_trccbc + 1  ; n_trc_indcbc(jn) = nb_trccbc
171         ENDIF
172      ENDDO
173
174      ! Print summmary of Boundary Conditions
175      IF( lwp ) THEN
176         WRITE(numout,*) ' '
177         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with SURFACE BCs data:', nb_trcsbc
178         IF ( nb_trcsbc > 0 ) THEN
179            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact. '
180            DO jn = 1, ntrc
181               IF ( ln_trc_sbc(jn) ) WRITE(numout,9001) jn, TRIM( sn_trcsbc(jn)%clvar ), 'SBC', rn_trsfac(jn)
182            ENDDO
183         ENDIF
184         WRITE(numout,'(2a)') '   SURFACE BC data repository : ', TRIM(cn_dir_sbc)
185
186         WRITE(numout,*) ' '
187         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with COASTAL BCs data:', nb_trccbc
188         IF ( nb_trccbc > 0 ) THEN
189            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact. '
190            DO jn = 1, ntrc
191               IF ( ln_trc_cbc(jn) ) WRITE(numout, 9001) jn, TRIM( sn_trccbc(jn)%clvar ), 'CBC', rn_trcfac(jn)
192            ENDDO
193         ENDIF
194         WRITE(numout,'(2a)') '   COASTAL BC data repository : ', TRIM(cn_dir_cbc)
195
196         WRITE(numout,*) ' '
197         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with OPEN BCs data:', nb_trcobc
198
199         IF ( ln_bdy .AND. nb_trcobc > 0 ) THEN
200            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact.   OBC Settings'
201            DO jn = 1, ntrc
202               IF ( ln_trc_obc(jn) )  WRITE(numout, 9001) jn, TRIM( sn_trcobc(jn)%clvar ), 'OBC', rn_trofac(jn), (trcdta_bdy(jn,ib)%cn_obc,ib=1,nb_bdy)
203               IF ( .NOT. ln_trc_obc(jn) )  WRITE(numout, 9002) jn, 'Set data to IC and use default condition', (trcdta_bdy(jn,ib)%cn_obc,ib=1,nb_bdy)
204            ENDDO
205            WRITE(numout,*) ' '
206            DO ib = 1, nb_bdy
207                IF (nn_trcdmp_bdy(ib) .EQ. 0) WRITE(numout,9003) '   Boundary ',ib,' -> NO damping of tracers'
208                IF (nn_trcdmp_bdy(ib) .EQ. 1) WRITE(numout,9003) '   Boundary ',ib,' -> damping ONLY for tracers with external data provided'
209                IF (nn_trcdmp_bdy(ib) .EQ. 2) WRITE(numout,9003) '   Boundary ',ib,' -> damping of ALL tracers'
210                IF (nn_trcdmp_bdy(ib) .GT. 0) THEN
211                   WRITE(numout,9003) '     USE damping parameters from nambdy for boundary ', ib,' : '
212                   WRITE(numout,'(a,f10.2,a)') '     - Inflow damping time scale  : ',rn_time_dmp(ib),' days'
213                   WRITE(numout,'(a,f10.2,a)') '     - Outflow damping time scale : ',rn_time_dmp_out(ib),' days'
214                ENDIF
215            ENDDO
216         ENDIF
217
218         WRITE(numout,'(2a)') '   OPEN BC data repository : ', TRIM(cn_dir_obc)
219      ENDIF
2209001  FORMAT(2x,i5, 3x, a15, 3x, a5, 6x, e11.3, 4x, 10a13)
2219002  FORMAT(2x,i5, 3x, a41, 3x, 10a13)
2229003  FORMAT(a, i5, a)
223
224      !
225      ! OPEN Lateral boundary conditions
226      IF( ln_bdy .AND. nb_trcobc > 0 ) THEN
227         ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), nbmap_ptr(nb_trcobc), STAT=ierr1 )
228         IF( ierr1 > 0 ) THEN
229            CALL ctl_stop( 'trc_bc_init: unable to allocate sf_trcobc structure' )   ;   RETURN
230         ENDIF
231
232         igrd = 1                       ! Everything is at T-points here
233
234         DO jn = 1, ntrc
235            DO ib = 1, nb_bdy
236
237               nblen = idx_bdy(ib)%nblen(igrd)
238
239               IF ( ln_trc_obc(jn) ) THEN
240               ! Initialise from external data
241                  jl = n_trc_indobc(jn)
242                  slf_i(jl)    = sn_trcobc(jn)
243                  rf_trofac(jl) = rn_trofac(jn)
244                                               ALLOCATE( sf_trcobc(jl)%fnow(nblen,1,jpk)   , STAT=ierr2 )
245                  IF( sn_trcobc(jn)%ln_tint )  ALLOCATE( sf_trcobc(jl)%fdta(nblen,1,jpk,2) , STAT=ierr3 )
246                  IF( ierr2 + ierr3 > 0 ) THEN
247                    CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer OBC data arrays' )   ;   RETURN
248                  ENDIF
249                  trcdta_bdy(jn,ib)%trc => sf_trcobc(jl)%fnow(:,1,:)
250                  trcdta_bdy(jn,ib)%rn_fac = rf_trofac(jl)
251                  ! create OBC mapping array
252                  nbmap_ptr(jl)%ptr => idx_bdy(ib)%nbmap(:,igrd)
253                  nbmap_ptr(jl)%ll_unstruc = ln_coords_file(igrd)
254               ELSE
255               ! Initialise obc arrays from initial conditions
256                  ALLOCATE ( trcdta_bdy(jn,ib)%trc(nblen,jpk) )
257                  DO ibd = 1, nblen
258                     DO ik = 1, jpkm1
259                        ii = idx_bdy(ib)%nbi(ibd,igrd)
260                        ij = idx_bdy(ib)%nbj(ibd,igrd)
261                        trcdta_bdy(jn,ib)%trc(ibd,ik) = trn(ii,ij,ik,jn) * tmask(ii,ij,ik)
262                     END DO
263                  END DO
264                  trcdta_bdy(jn,ib)%rn_fac = 1._wp
265               ENDIF
266            ENDDO
267         ENDDO
268
269         CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' )
270      ENDIF
271
272      ! SURFACE Boundary conditions
273      IF( nb_trcsbc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero
274         ALLOCATE( sf_trcsbc(nb_trcsbc), rf_trsfac(nb_trcsbc), STAT=ierr1 )
275         IF( ierr1 > 0 ) THEN
276            CALL ctl_stop( 'trc_bc_init: unable to allocate  sf_trcsbc structure' )   ;   RETURN
277         ENDIF
278         !
279         DO jn = 1, ntrc
280            IF( ln_trc_sbc(jn) ) THEN      ! update passive tracers arrays with input data read from file
281               jl = n_trc_indsbc(jn)
282               slf_i(jl)    = sn_trcsbc(jn)
283               rf_trsfac(jl) = rn_trsfac(jn)
284                                            ALLOCATE( sf_trcsbc(jl)%fnow(jpi,jpj,1)   , STAT=ierr2 )
285               IF( sn_trcsbc(jn)%ln_tint )  ALLOCATE( sf_trcsbc(jl)%fdta(jpi,jpj,1,2) , STAT=ierr3 )
286               IF( ierr2 + ierr3 > 0 ) THEN
287                 CALL ctl_stop( 'trc_bc_init : unable to allocate passive tracer SBC data arrays' )   ;   RETURN
288               ENDIF
289            ENDIF
290            !   
291         ENDDO
292         !                         ! fill sf_trcsbc with slf_i and control print
293         CALL fld_fill( sf_trcsbc, slf_i, cn_dir_sbc, 'trc_bc_init', 'Passive tracer SBC data', 'namtrc_bc' )
294         !
295      ENDIF
296      !
297      ! COSTAL Boundary conditions
298      IF( nb_trccbc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero
299         ALLOCATE( sf_trccbc(nb_trccbc), rf_trcfac(nb_trccbc), STAT=ierr1 )
300         IF( ierr1 > 0 ) THEN
301            CALL ctl_stop( 'trc_bc_ini: unable to allocate  sf_trccbc structure' )   ;   RETURN
302         ENDIF
303         !
304         DO jn = 1, ntrc
305            IF( ln_trc_cbc(jn) ) THEN      ! update passive tracers arrays with input data read from file
306               jl = n_trc_indcbc(jn)
307               slf_i(jl)    = sn_trccbc(jn)
308               rf_trcfac(jl) = rn_trcfac(jn)
309                                            ALLOCATE( sf_trccbc(jl)%fnow(jpi,jpj,1)   , STAT=ierr2 )
310               IF( sn_trccbc(jn)%ln_tint )  ALLOCATE( sf_trccbc(jl)%fdta(jpi,jpj,1,2) , STAT=ierr3 )
311               IF( ierr2 + ierr3 > 0 ) THEN
312                 CALL ctl_stop( 'trc_bc_ini : unable to allocate passive tracer CBC data arrays' )   ;   RETURN
313               ENDIF
314            ENDIF
315            !   
316         ENDDO
317         !                         ! fill sf_trccbc with slf_i and control print
318         CALL fld_fill( sf_trccbc, slf_i, cn_dir_cbc, 'trc_bc_init', 'Passive tracer CBC data', 'namtrc_bc' )
319         !
320      ENDIF
321      !
322      DEALLOCATE( slf_i )          ! deallocate local field structure
323      IF( nn_timing == 1 )  CALL timing_stop('trc_bc_init')
324      !
325   END SUBROUTINE trc_bc_init
326
327
328   SUBROUTINE trc_bc_read(kt, jit)
329      !!----------------------------------------------------------------------
330      !!                   ***  ROUTINE trc_bc_init  ***
331      !!
332      !! ** Purpose :  Read passive tracer Boundary Conditions data
333      !!
334      !! ** Method  :  Read BC inputs and update data structures using fldread
335      !!             
336      !!----------------------------------------------------------------------
337      USE fldread
338     
339      !! * Arguments
340      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
341      INTEGER, INTENT( in ), OPTIONAL ::   jit   ! subcycle time-step index (for timesplitting option)
342      !!---------------------------------------------------------------------
343      !
344      IF( nn_timing == 1 )  CALL timing_start('trc_bc_read')
345
346      IF( kt == nit000 .AND. lwp) THEN
347         WRITE(numout,*)
348         WRITE(numout,*) 'trc_bc_read : Surface boundary conditions for passive tracers.'
349         WRITE(numout,*) '~~~~~~~~~~~ '
350      ENDIF
351
352      IF ( PRESENT(jit) ) THEN 
353
354         ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step)
355         IF( nb_trcobc > 0 ) THEN
356           if (lwp) write(numout,'(a,i5,a,i10)') '   reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt
357           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcobc, map=nbmap_ptr, kit=jit, kt_offset=+1)
358         ENDIF
359
360         ! SURFACE boundary conditions
361         IF( nb_trcsbc > 0 ) THEN
362           if (lwp) write(numout,'(a,i5,a,i10)') '   reading SBC data for ', nb_trcsbc ,' variable(s) at step ', kt
363           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcsbc, kit=jit)
364         ENDIF
365
366         ! COASTAL boundary conditions
367         IF( nb_trccbc > 0 ) THEN
368           if (lwp) write(numout,'(a,i5,a,i10)') '   reading CBC data for ', nb_trccbc ,' variable(s) at step ', kt
369           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trccbc, kit=jit)
370         ENDIF
371
372      ELSE
373
374         ! OPEN boundary conditions (use time_offset=+1 as they are applied at the end of the step)
375         IF( nb_trcobc > 0 ) THEN
376           if (lwp) write(numout,'(a,i5,a,i10)') '   reading OBC data for ', nb_trcobc ,' variable(s) at step ', kt
377           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcobc, map=nbmap_ptr, kt_offset=+1)
378         ENDIF
379
380         ! SURFACE boundary conditions
381         IF( nb_trcsbc > 0 ) THEN
382           if (lwp) write(numout,'(a,i5,a,i10)') '   reading SBC data for ', nb_trcsbc ,' variable(s) at step ', kt
383           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trcsbc)
384         ENDIF
385
386         ! COASTAL boundary conditions
387         IF( nb_trccbc > 0 ) THEN
388           if (lwp) write(numout,'(a,i5,a,i10)') '   reading CBC data for ', nb_trccbc ,' variable(s) at step ', kt
389           CALL fld_read(kt=kt, kn_fsbc=1, sd=sf_trccbc)
390         ENDIF
391
392      ENDIF
393
394      !
395      IF( nn_timing == 1 )  CALL timing_stop('trc_bc_read')
396      !
397   END SUBROUTINE trc_bc_read
398
399#else
400   !!----------------------------------------------------------------------
401   !!   Dummy module                              NO 3D passive tracer data
402   !!----------------------------------------------------------------------
403CONTAINS
404
405   SUBROUTINE trc_bc_init( ntrc )        ! Empty routine
406      INTEGER,INTENT(IN) :: ntrc                           ! number of tracers
407      WRITE(*,*) 'trc_bc_init: You should not have seen this print! error?', kt
408   END SUBROUTINE trc_bc_init
409
410   SUBROUTINE trc_bc_read( kt )        ! Empty routine
411      WRITE(*,*) 'trc_bc_read: You should not have seen this print! error?', kt
412   END SUBROUTINE trc_bc_read
413#endif
414
415   !!======================================================================
416END MODULE trcbc
Note: See TracBrowser for help on using the repository browser.