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/2013/dev_CMCC_INGV_2013/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2013/dev_CMCC_INGV_2013/NEMOGCM/NEMO/TOP_SRC/trcbc.F90 @ 4201

Last change on this file since 4201 was 4201, checked in by poddo, 11 years ago

ticket #1178 Merge of CMCC-INGV 2013 branches

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