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/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/TOP_SRC/trcbc.F90 @ 6004

Last change on this file since 6004 was 6004, checked in by gm, 8 years ago

#1613: vvl by default, step III: Merge with the trunk (free surface simplification) (see wiki)

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