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

source: branches/UKMO/dev_r5518_nemo_fabm_ukmo/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcwri_my_trc.F90 @ 7829

Last change on this file since 7829 was 7829, checked in by dford, 7 years ago

Add a version of the NEMO-FABM coupling code. In theory, this should give equivalent results to PML gitlab commit 2e51db55.

File size: 4.9 KB
Line 
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   !!----------------------------------------------------------------------
8#if defined key_top && defined key_my_trc && defined key_iomput
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 
21#if defined key_tracer_budget
22   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:), SAVE :: trb_temp ! slwa
23#endif
24
25
26#  include "top_substitute.h90"
27CONTAINS
28
29#if defined key_tracer_budget
30   SUBROUTINE trc_wri_my_trc (kt, fl) ! slwa
31#else
32   SUBROUTINE trc_wri_my_trc
33#endif
34      !!---------------------------------------------------------------------
35      !!                     ***  ROUTINE trc_wri_trc  ***
36      !!
37      !! ** Purpose :   output passive tracers fields
38      !!---------------------------------------------------------------------
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#endif
44      CHARACTER (len=20)   :: cltra
45      INTEGER              :: jn,jk
46      !!---------------------------------------------------------------------
47 
48      ! write the tracer concentrations in the file
49      ! ---------------------------------------
50
51
52#if defined key_tracer_budget
53      IF( PRESENT(fl)) THEN
54! depth integrated
55! for strict budgetting write this out at end of timestep as an average between 'now' and 'after' at kt
56         DO jn = jp_myt0, jp_myt1 
57            trpool(:,:,:) = 0.5 * ( trn(:,:,:,jn) * fse3t_a(:,:,:) +  &
58                                        trb_temp(:,:,:,jn) * fse3t(:,:,:) )
59!
60            cltra = TRIM( ctrcnm(jn) )                  ! output of tracer density
61            CALL iom_put( cltra, trpool(:,:,:) / (0.5* (fse3t(:,:,:) + fse3t_a(:,:,:) ) ) )
62!
63            cltra = TRIM( ctrcnm(jn) )//"_pool"     ! volume integrated output
64            DO jk = 1, jpk
65               trpool(:,:,jk) = trpool(:,:,jk) * e1t(:,:) * e2t(:,:)
66            END DO
67            CALL iom_put( cltra, trpool)
68
69!           cltra = TRIM( ctrcnm(jn) )//"_pool"     ! volume integrated output
70!           DO jk = 1, jpk
71!              trpool(:,:,jk) = 0.5 * ( trn(:,:,jk,jn) * fse3t_a(:,:,jk) +  &
72!                                       trb_temp(:,:,jk,jn) * fse3t(:,:,jk) ) * &
73!                                       e1t(:,:) * e2t(:,:)
74!           END DO
75!           CALL iom_put( cltra, trpool)
76!           cltra = TRIM( ctrcnm(jn) )                  ! output of tracer density
77!           CALL iom_put( cltra, trpool(:,:,:) / (0.5* (fse3t(:,:,:) + fse3t_a(:,:,:) ) ) )
78         END DO
79         CALL iom_put( "DEPTH" , 0.5* (fse3t(:,:,:) + fse3t_a(:,:,:) ) )  !  equivalent 'depth' at same time as tracer pool output
80      ELSE
81
82         IF( kt == nittrc000 ) THEN
83           ALLOCATE(trb_temp(jpi,jpj,jpk,jptra))  ! slwa
84         ENDIF
85         trb_temp(:,:,:,:)=trn(:,:,:,:) ! slwa save for tracer budget (unfiltered trn)
86
87!        DO jn = jp_myt0, jp_myt1
88!           cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
89!           CALL iom_put( cltra, trn(:,:,:,jn) )
90!        END DO
91! write out depths and areas in double precision for tracer budget calculations
92         CALL iom_put( "AREA" , e1t(:,:) * e2t(:,:))
93!        CALL iom_put( "DEPTH" , fse3t(:,:,:) )  ! need depth at same time as tracer output
94
95      END IF
96#else
97      DO jn = jp_myt0, jp_myt1
98         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
99         CALL iom_put( cltra, trn(:,:,:,jn) )
100      END DO
101#endif
102      !
103   END SUBROUTINE trc_wri_my_trc
104
105#else
106   !!----------------------------------------------------------------------
107   !!  Dummy module :                                     No passive tracer
108   !!----------------------------------------------------------------------
109   PUBLIC trc_wri_my_trc
110CONTAINS
111   SUBROUTINE trc_wri_my_trc                     ! Empty routine 
112   END SUBROUTINE trc_wri_my_trc
113#endif
114
115   !!----------------------------------------------------------------------
116   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
117   !! $Id$
118   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
119   !!======================================================================
120END MODULE trcwri_my_trc
Note: See TracBrowser for help on using the repository browser.