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.
trcwri_my_trc.F90 in branches/UKMO/r6232_collate_bgc_diagnostics/NEMOGCM/NEMO/TOP_SRC/MY_TRC – NEMO

source: branches/UKMO/r6232_collate_bgc_diagnostics/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcwri_my_trc.F90 @ 11134

Last change on this file since 11134 was 11134, checked in by jcastill, 5 years ago

Full set of changes as in the original branch

File size: 4.1 KB
RevLine 
[3444]1MODULE trcwri_my_trc
2   !!======================================================================
3   !!                       *** MODULE trcwri ***
4   !!    my_trc :   Output of my_trc tracers
5   !!======================================================================
6   !! History :   1.0  !  2009-05 (C. Ethe)  Original code
7   !!----------------------------------------------------------------------
[5407]8#if defined key_top && defined key_my_trc && defined key_iomput
[3444]9   !!----------------------------------------------------------------------
10   !!   'key_my_trc'                                           my_trc model
11   !!----------------------------------------------------------------------
12   !! trc_wri_my_trc   :  outputs of concentration fields
13   !!----------------------------------------------------------------------
14   USE trc         ! passive tracers common variables
15   USE iom         ! I/O manager
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC trc_wri_my_trc 
[11134]21#if defined key_tracer_budget
22   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:), SAVE :: trb_temp ! slwa
23#endif
[3444]24
[11134]25
[4305]26#  include "top_substitute.h90"
[3444]27CONTAINS
28
[11134]29#if defined key_tracer_budget
30   SUBROUTINE trc_wri_my_trc (kt, fl) ! slwa
31#else
[3444]32   SUBROUTINE trc_wri_my_trc
[11134]33#endif
[3444]34      !!---------------------------------------------------------------------
35      !!                     ***  ROUTINE trc_wri_trc  ***
36      !!
37      !! ** Purpose :   output passive tracers fields
38      !!---------------------------------------------------------------------
[11134]39#if defined key_tracer_budget
40      INTEGER, INTENT( in ), OPTIONAL     :: fl 
41      INTEGER, INTENT( in )               :: kt
42      REAL(wp), DIMENSION(jpi,jpj,jpk)    :: trpool !tracer pool temporary output
43#else
44      INTEGER, INTENT( in )               :: kt
45#endif
[3444]46      CHARACTER (len=20)   :: cltra
[11134]47      INTEGER              :: jn,jk ! JC TODO jk defined here but may not be used
[3444]48      !!---------------------------------------------------------------------
49 
50      ! write the tracer concentrations in the file
51      ! ---------------------------------------
[11134]52
53
54#if defined key_tracer_budget
55      IF( PRESENT(fl)) THEN
56! depth integrated
57! for strict budgetting write this out at end of timestep as an average between 'now' and 'after' at kt
58         DO jn = jp_myt0, jp_myt1 
59          IF(ln_trdtrc (jn))THEN
60            trpool(:,:,:) = 0.5 * ( trn(:,:,:,jn) * fse3t_a(:,:,:) +  &
61                                        trb_temp(:,:,:,jn) * fse3t(:,:,:) )
62            cltra = TRIM( ctrcnm(jn) )//"e3t"     ! depth integrated output
63            IF( kt == nittrc000 ) write(6,*)'output pool ',cltra
64            DO jk = 1, jpk
65               trpool(:,:,jk) = trpool(:,:,jk)
66            END DO
67            CALL iom_put( cltra, trpool)
68
69          END IF
70         END DO
71
72      ELSE
73
74         IF( kt == nittrc000 ) THEN
75           ALLOCATE(trb_temp(jpi,jpj,jpk,jp_my_trc))  ! slwa
76         ENDIF
77         trb_temp(:,:,:,:)=trn(:,:,:,:) ! slwa save for tracer budget (unfiltered trn)
78
79
80      END IF
81#else
[3444]82      DO jn = jp_myt0, jp_myt1
83         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
[4996]84         CALL iom_put( cltra, trn(:,:,:,jn) )
[3444]85      END DO
[11134]86#endif
[3444]87      !
88   END SUBROUTINE trc_wri_my_trc
89
90#else
91   !!----------------------------------------------------------------------
92   !!  Dummy module :                                     No passive tracer
93   !!----------------------------------------------------------------------
94   PUBLIC trc_wri_my_trc
95CONTAINS
[11134]96#if defined key_tracer_budget
97   SUBROUTINE trc_wri_my_trc (kt, fl) ! slwa
98      INTEGER, INTENT( in ), OPTIONAL     :: fl 
99      INTEGER, INTENT( in )               :: kt
100#else
101   ! JC TODO Subroutine arguments (kt) inconsistent with earlier definition
102   SUBROUTINE trc_wri_my_trc (kt)
103      INTEGER, INTENT( in )               :: kt
104#endif
[3444]105   END SUBROUTINE trc_wri_my_trc
106#endif
107
108   !!----------------------------------------------------------------------
109   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[11132]110   !! $Id$
[3444]111   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
112   !!======================================================================
113END MODULE trcwri_my_trc
Note: See TracBrowser for help on using the repository browser.