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.
trdtrc.F90 in branches/UKMO/dev_r5518_CICE_coupling_GSI7_GSI8/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/dev_r5518_CICE_coupling_GSI7_GSI8/NEMOGCM/NEMO/TOP_SRC/TRP/trdtrc.F90 @ 5662

Last change on this file since 5662 was 5662, checked in by dancopsey, 9 years ago

Removed SVN keywords.

File size: 7.7 KB
Line 
1MODULE trdtrc
2   !!======================================================================
3   !!                       ***  MODULE  trdtrc  ***
4   !! Ocean diagnostics:  mixed layer passive tracer trends
5   !!======================================================================
6   !! History :  3.0  !  2010-07  (C. Ethe)  Original code (from trdtrc.F90)
7   !!----------------------------------------------------------------------
8#if   defined key_top && ( defined key_trdmxl_trc   ||   defined key_trdtrc )
9   !!----------------------------------------------------------------------
10   !!   'key_trdmxl_trc'                  mixed layer trend diagnostics
11   !!   'key_trdtrc'                      3D trend diagnostics
12   !!----------------------------------------------------------------------
13   !!   trdtrc      : passive tracer trends
14   !!----------------------------------------------------------------------
15   USE trc               ! tracer definitions (trn, trb, tra, etc.)
16   USE trcnam_trp
17   USE trd_oce
18   USE trdtrc_oce       ! definition of main arrays used for trends computations
19   USE trdmxl_trc        ! Mixed layer trends diag.
20   USE iom               ! I/O library
21
22   IMPLICIT NONE
23   PRIVATE
24
25   INTERFACE trd_trc
26      MODULE PROCEDURE trd_trc_trp, trd_trc_bio
27   END INTERFACE
28
29   PUBLIC trd_trc
30
31   !! * Substitutions
32#  include "top_substitute.h90"
33   !!----------------------------------------------------------------------
34   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
35   !! $Id$
36   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
37   !!----------------------------------------------------------------------
38
39CONTAINS
40
41   SUBROUTINE trd_trc_trp( ptrtrd, kjn, ktrd, kt )
42      !!----------------------------------------------------------------------
43      !!                  ***  ROUTINE trd_trc  ***
44      !!----------------------------------------------------------------------
45      INTEGER, INTENT( in )  ::   kt                                  ! time step
46      INTEGER, INTENT( in )  ::   kjn                                 ! tracer index
47      INTEGER, INTENT( in )  ::   ktrd                                ! tracer trend index
48      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout )  ::   ptrtrd  ! Temperature or U trend
49      CHARACTER (len=20) :: cltra
50      !!----------------------------------------------------------------------
51
52      IF( kt == nittrc000 ) THEN
53!         IF(lwp)WRITE(numout,*)
54!         IF(lwp)WRITE(numout,*) 'trd_trc:'
55!         IF(lwp)WRITE(numout,*) '~~~~~~~~~~~~'
56      ENDIF
57
58      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
59      ! Mixed layer trends for passive tracers
60      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
61#if defined key_trdmxl_trc 
62      IF( lk_trdmxl_trc .AND. ln_trdtrc( kjn ) ) THEN
63         !
64         SELECT CASE ( ktrd )
65         CASE ( jptra_xad     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_xad, '3D', kjn )
66         CASE ( jptra_yad     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_yad, '3D', kjn )
67         CASE ( jptra_zad     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_zad, '3D', kjn )
68         CASE ( jptra_ldf     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_ldf, '3D', kjn )
69         CASE ( jptra_bbl     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_bbl, '3D', kjn )
70         CASE ( jptra_zdf     )
71            IF( ln_trcldf_iso ) THEN
72               CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_ldf, '3D', kjn )
73            ELSE
74               CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_zdf, '3D', kjn )
75            ENDIF
76         CASE ( jptra_dmp     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_dmp , '3D', kjn )
77         CASE ( jptra_nsr     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_sbc , '2D', kjn )
78         CASE ( jptra_sms     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_sms , '3D', kjn )
79         CASE ( jptra_radb    )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_radb, '3D', kjn )
80         CASE ( jptra_radn    )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_radn, '3D', kjn )
81         CASE ( jptra_atf     )   ;   CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_atf , '3D', kjn )
82         END SELECT
83         !
84      END IF
85#endif
86
87      IF( lk_trdtrc .AND. ln_trdtrc( kjn ) ) THEN
88         !
89         SELECT CASE( ktrd )
90         CASE( jptra_xad  )       ;    WRITE (cltra,'("XAD_",4a)')
91         CASE( jptra_yad  )       ;    WRITE (cltra,'("YAD_",4a)')
92         CASE( jptra_zad  )       ;    WRITE (cltra,'("ZAD_",4a)')
93         CASE( jptra_ldf  )       ;    WRITE (cltra,'("LDF_",4a)')
94         CASE( jptra_bbl  )       ;    WRITE (cltra,'("BBL_",4a)')
95         CASE( jptra_nsr  )       ;    WRITE (cltra,'("FOR_",4a)')
96         CASE( jptra_zdf  )       ;    WRITE (cltra,'("ZDF_",4a)')
97         CASE( jptra_dmp  )       ;    WRITE (cltra,'("DMP_",4a)')
98         CASE( jptra_sms  )       ;    WRITE (cltra,'("SMS_",4a)')
99         CASE( jptra_atf  )       ;    WRITE (cltra,'("ATF_",4a)')
100         CASE( jptra_radb )       ;    WRITE (cltra,'("RDB_",4a)')
101         CASE( jptra_radn )       ;    WRITE (cltra,'("RDN_",4a)')
102         END SELECT
103                                          cltra = TRIM(cltra)//TRIM(ctrcnm(kjn))
104                                          CALL iom_put( cltra,  ptrtrd(:,:,:) )
105         !
106      END IF
107
108   END SUBROUTINE trd_trc_trp
109
110   SUBROUTINE trd_trc_bio( ptrbio, ktrd, kt )
111      !!----------------------------------------------------------------------
112      !!                  ***  ROUTINE trd_bio  ***
113      !!----------------------------------------------------------------------
114
115      INTEGER, INTENT( in )  ::   kt                                  ! time step
116      INTEGER, INTENT( in )  ::   ktrd                                ! bio trend index
117      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout )  ::   ptrbio  ! Bio trend
118      !!----------------------------------------------------------------------
119
120#if defined key_trdmxl_trc 
121      CALL trd_mxl_bio_zint( ptrbio, ktrd ) ! Verticaly integrated biological trends
122#endif
123
124   END SUBROUTINE trd_trc_bio
125#else
126   !!----------------------------------------------------------------------
127   !!   Default option :                                       Empty module
128   !!----------------------------------------------------------------------
129
130   INTERFACE trd_trc
131      MODULE PROCEDURE trd_trc_trp, trd_trc_bio
132   END INTERFACE
133
134CONTAINS
135
136   SUBROUTINE trd_trc_trp( ptrtrd, kjn, ktrd, kt )
137      INTEGER               , INTENT( in )     ::   kt      ! time step
138      INTEGER               , INTENT( in )     ::   kjn     ! tracer index
139      INTEGER               , INTENT( in )     ::   ktrd    ! tracer trend index
140      REAL, DIMENSION(:,:,:), INTENT( inout )  ::   ptrtrd  ! Temperature or U trend
141      WRITE(*,*) 'trd_trc_trp : You should not have seen this print! error?', ptrtrd(1,1,1)
142      WRITE(*,*) '  "      "      : You should not have seen this print! error?', kjn
143      WRITE(*,*) '  "      "      : You should not have seen this print! error?', ktrd
144      WRITE(*,*) '  "      "      : You should not have seen this print! error?', kt
145   END SUBROUTINE trd_trc_trp
146
147   SUBROUTINE trd_trc_bio( ptrbio, ktrd, kt )
148      INTEGER               , INTENT( in )     ::   kt      ! time step
149      INTEGER               , INTENT( in )     ::   ktrd    ! tracer trend index
150      REAL, DIMENSION(:,:,:), INTENT( inout )  ::   ptrbio  ! Temperature or U trend
151      WRITE(*,*) 'trd_trc_trp : You should not have seen this print! error?', ptrbio(1,1,1)
152      WRITE(*,*) '  "      "      : You should not have seen this print! error?', ktrd
153      WRITE(*,*) '  "      "      : You should not have seen this print! error?', kt
154   END SUBROUTINE trd_trc_bio
155
156#endif
157   !!======================================================================
158END MODULE trdtrc
Note: See TracBrowser for help on using the repository browser.