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_INGV_UKMO_2016/NEMOGCM/NEMO/TOP_SRC/MY_TRC – NEMO

source: branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcsms_my_trc.F90 @ 7351

Last change on this file since 7351 was 7351, checked in by emanuelaclementi, 7 years ago

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

  • Property svn:keywords set to Id
File size: 4.1 KB
RevLine 
[932]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#if defined key_my_trc
9   !!----------------------------------------------------------------------
10   !!   'key_my_trc'                                               CFC tracers
11   !!----------------------------------------------------------------------
[3294]12   !! trc_sms_my_trc       : MY_TRC model main routine
[2715]13   !! trc_sms_my_trc_alloc : allocate arrays specific to MY_TRC sms
[932]14   !!----------------------------------------------------------------------
15   USE par_trc         ! TOP parameters
[1255]16   USE oce_trc         ! Ocean variables
17   USE trc             ! TOP variables
[4990]18   USE trd_oce
19   USE trdtrc
[7351]20   USE trcbc, only : trc_bc_read
[932]21
22   IMPLICIT NONE
23   PRIVATE
24
[2715]25   PUBLIC   trc_sms_my_trc       ! called by trcsms.F90 module
26   PUBLIC   trc_sms_my_trc_alloc ! called by trcini_my_trc.F90 module
[932]27
[2715]28   ! Defined HERE the arrays specific to MY_TRC sms and ALLOCATE them in trc_sms_my_trc_alloc
[3294]29
[932]30   !!----------------------------------------------------------------------
[2528]31   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[3294]32   !! $Id$
[2715]33   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[932]34   !!----------------------------------------------------------------------
35CONTAINS
36
37   SUBROUTINE trc_sms_my_trc( kt )
38      !!----------------------------------------------------------------------
[3294]39      !!                     ***  trc_sms_my_trc  ***
[932]40      !!
41      !! ** Purpose :   main routine of MY_TRC model
42      !!
[3294]43      !! ** Method  : -
[932]44      !!----------------------------------------------------------------------
[2715]45      !
46      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
47      INTEGER ::   jn   ! dummy loop index
[3294]48      REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrmyt
[5385]49      !!----------------------------------------------------------------------
[3294]50      !
51      IF( nn_timing == 1 )  CALL timing_start('trc_sms_my_trc')
52      !
[932]53      IF(lwp) WRITE(numout,*)
54      IF(lwp) WRITE(numout,*) ' trc_sms_my_trc:  MY_TRC model'
55      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
[1162]56
[3294]57      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrmyt )
58
[7351]59      CALL trc_bc_read  ( kt )       ! tracers: surface and lateral Boundary Conditions
60
61      ! add here the call to BGC model
62
63      ! Save the trends in the mixed layer
64      IF( l_trdtrc ) THEN
[1255]65          DO jn = jp_myt0, jp_myt1
66            ztrmyt(:,:,:) = tra(:,:,:,jn)
[4990]67            CALL trd_trc( ztrmyt, jn, jptra_sms, kt )   ! save trends
[1255]68          END DO
[3294]69          CALL wrk_dealloc( jpi, jpj, jpk, ztrmyt )
[1255]70      END IF
[932]71      !
[3294]72      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_my_trc')
73      !
[932]74   END SUBROUTINE trc_sms_my_trc
[2715]75
76
77   INTEGER FUNCTION trc_sms_my_trc_alloc()
78      !!----------------------------------------------------------------------
79      !!              ***  ROUTINE trc_sms_my_trc_alloc  ***
80      !!----------------------------------------------------------------------
81      !
82      ! ALLOCATE here the arrays specific to MY_TRC
83      ! ALLOCATE( tab(...) , STAT=trc_sms_my_trc_alloc )
84      trc_sms_my_trc_alloc = 0      ! set to zero if no array to be allocated
85      !
86      IF( trc_sms_my_trc_alloc /= 0 ) CALL ctl_warn('trc_sms_my_trc_alloc : failed to allocate arrays')
87      !
88   END FUNCTION trc_sms_my_trc_alloc
89
90
[932]91#else
92   !!----------------------------------------------------------------------
93   !!   Dummy module                                        No MY_TRC model
94   !!----------------------------------------------------------------------
95CONTAINS
96   SUBROUTINE trc_sms_my_trc( kt )             ! Empty routine
97      INTEGER, INTENT( in ) ::   kt
98      WRITE(*,*) 'trc_sms_my_trc: You should not have seen this print! error?', kt
99   END SUBROUTINE trc_sms_my_trc
100#endif
101
102   !!======================================================================
103END MODULE trcsms_my_trc
Note: See TracBrowser for help on using the repository browser.