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.
trcsms_my_trc.F90 in branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/MY_TRC – NEMO

source: branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcsms_my_trc.F90 @ 7073

Last change on this file since 7073 was 7073, checked in by cetlod, 8 years ago

New top interface : Update my_trc module

  • Property svn:keywords set to Id
File size: 3.4 KB
Line 
1MODULE trcsms_my_trc
2   !!======================================================================
3   !!                         ***  MODULE trcsms_my_trc  ***
4   !! TOP :   Main module of the MY_TRC tracers
5   !!======================================================================
6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec) Original code
7   !!----------------------------------------------------------------------
8   !! trc_sms_my_trc       : MY_TRC model main routine
9   !! trc_sms_my_trc_alloc : allocate arrays specific to MY_TRC sms
10   !!----------------------------------------------------------------------
11   USE par_trc         ! TOP parameters
12   USE oce_trc         ! Ocean variables
13   USE trc             ! TOP variables
14   USE trd_oce
15   USE trdtrc
16   USE trcbc, only : trc_bc_read
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC   trc_sms_my_trc       ! called by trcsms.F90 module
22   PUBLIC   trc_sms_my_trc_alloc ! called by trcini_my_trc.F90 module
23
24   ! Defined HERE the arrays specific to MY_TRC sms and ALLOCATE them in trc_sms_my_trc_alloc
25
26   !!----------------------------------------------------------------------
27   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
28   !! $Id$
29   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE trc_sms_my_trc( kt )
34      !!----------------------------------------------------------------------
35      !!                     ***  trc_sms_my_trc  ***
36      !!
37      !! ** Purpose :   main routine of MY_TRC model
38      !!
39      !! ** Method  : -
40      !!----------------------------------------------------------------------
41      !
42      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
43      INTEGER ::   jn   ! dummy loop index
44      REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrmyt
45      !!----------------------------------------------------------------------
46      !
47      IF( nn_timing == 1 )  CALL timing_start('trc_sms_my_trc')
48      !
49      IF(lwp) WRITE(numout,*)
50      IF(lwp) WRITE(numout,*) ' trc_sms_my_trc:  MY_TRC model'
51      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
52
53      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrmyt )
54
55      CALL trc_bc_read  ( kt )       ! tracers: surface and lateral Boundary Conditions
56
57      ! add here the call to BGC model
58
59      ! Save the trends in the mixed layer
60      IF( l_trdtrc ) THEN
61          DO jn = jp_myt0, jp_myt1
62            ztrmyt(:,:,:) = tra(:,:,:,jn)
63            CALL trd_trc( ztrmyt, jn, jptra_sms, kt )   ! save trends
64          END DO
65          CALL wrk_dealloc( jpi, jpj, jpk, ztrmyt )
66      END IF
67      !
68      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_my_trc')
69      !
70   END SUBROUTINE trc_sms_my_trc
71
72
73   INTEGER FUNCTION trc_sms_my_trc_alloc()
74      !!----------------------------------------------------------------------
75      !!              ***  ROUTINE trc_sms_my_trc_alloc  ***
76      !!----------------------------------------------------------------------
77      !
78      ! ALLOCATE here the arrays specific to MY_TRC
79      ! ALLOCATE( tab(...) , STAT=trc_sms_my_trc_alloc )
80      trc_sms_my_trc_alloc = 0      ! set to zero if no array to be allocated
81      !
82      IF( trc_sms_my_trc_alloc /= 0 ) CALL ctl_warn('trc_sms_my_trc_alloc : failed to allocate arrays')
83      !
84   END FUNCTION trc_sms_my_trc_alloc
85
86
87   !!======================================================================
88END MODULE trcsms_my_trc
Note: See TracBrowser for help on using the repository browser.