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.F90 in branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC/trcwri.F90 @ 2007

Last change on this file since 2007 was 2007, checked in by smasson, 14 years ago

update branches/DEV_r1879_FCM/NEMOGCM/NEMO with tags/nemo_v3_2_1/NEMO

File size: 6.2 KB
Line 
1MODULE trcwri
2   !!===================================================================================
3   !!                       *** MODULE trcwri ***
4   !!    TOP :   Output of passive tracers
5   !!====================================================================================
6   !! History :   1.0  !  2009-05 (C. Ethe)  Original code
7   !!                  !  2010-03 (C. Ethe, R. Seferian ) Add the tracer transport trends
8   !!----------------------------------------------------------------------
9#if defined key_top &&  defined key_iomput
10   !!----------------------------------------------------------------------
11   !!   'key_top' && 'key_iomput'                              TOP models
12   !!----------------------------------------------------------------------
13   !! trc_wri_trc   :  outputs of concentration fields
14   !! trc_wri_trd   :  outputs of transport trends
15   !!----------------------------------------------------------------------
16   USE dom_oce         ! ocean space and time domain variables
17   USE oce_trc
18   USE trp_trc
19   USE trc
20   USE trdmld_trc_oce, ONLY : luttrd
21   USE iom
22#if defined key_off_tra
23   USE oce_trc
24   USE dianam
25#endif
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC trc_wri     
31
32   !! * Substitutions
33#  include "top_substitute.h90"
34   !!----------------------------------------------------------------------
35   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
36   !! $Id: trcdia.F90 1450 2009-05-15 14:12:12Z cetlod $
37   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39
40CONTAINS
41
42   SUBROUTINE trc_wri( kt )
43      !!---------------------------------------------------------------------
44      !!                     ***  ROUTINE trc_wri  ***
45      !!
46      !! ** Purpose :   output passive tracers fields and dynamical trends
47      !!---------------------------------------------------------------------
48      INTEGER, INTENT( in ) :: kt
49      !!---------------------------------------------------------------------
50
51      !
52      CALL iom_setkt  ( kt + ndttrc - 1 )       ! set the passive tracer time step
53      CALL trc_wri_trc( kt              )       ! outputs for tracer concentration
54      CALL trc_wri_trd( kt              )       ! outputs for dynamical trends
55      CALL iom_setkt  ( kt              )       ! set the model time step
56      !
57   END SUBROUTINE trc_wri
58
59   SUBROUTINE trc_wri_trc( kt ) 
60      !!---------------------------------------------------------------------
61      !!                     ***  ROUTINE trc_wri_trc  ***
62      !!
63      !! ** Purpose :   output passive tracers fields
64      !!---------------------------------------------------------------------
65      INTEGER, INTENT( in ) :: kt       ! ocean time-step
66      INTEGER               :: jn
67      CHARACTER (len=20)    :: cltra, cltras
68#if defined key_off_tra
69      CHARACTER (len=40) :: clhstnam
70      INTEGER ::   inum = 11            ! temporary logical unit
71#endif
72      !!---------------------------------------------------------------------
73 
74#if defined key_off_tra
75      IF( kt == nittrc000 ) THEN
76        ! WRITE root name in date.file for use by postpro
77         IF(lwp) THEN
78            CALL dia_nam( clhstnam, nwritetrc,' ' )
79            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
80            WRITE(inum,*) clhstnam
81            CLOSE(inum)
82         ENDIF
83      ENDIF
84#endif
85      ! write the tracer concentrations in the file
86      ! ---------------------------------------
87      DO jn = 1, jptra
88         cltra = ctrcnm(jn)                   ! short title for tracer
89         CALL iom_put( cltra, trn(:,:,:,jn) )
90      END DO
91      !
92   END SUBROUTINE trc_wri_trc
93
94# if defined key_trc_diatrd
95
96   SUBROUTINE trc_wri_trd( kt )
97      !!----------------------------------------------------------------------
98      !!                     ***  ROUTINE trc_wri_trd  ***
99      !!
100      !! ** Purpose :   output of passive tracer : advection-diffusion trends
101      !!
102      !!----------------------------------------------------------------------
103      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
104      !!
105      CHARACTER (len=3) ::   cltra
106      INTEGER  ::   jn, jl, ikn
107      !!----------------------------------------------------------------------
108
109      DO jn = 1, jptra
110         IF( luttrd(jn) ) THEN
111            ikn = ikeep(jn)
112            DO jl = 1, jpdiatrc
113               IF( jl == jptrc_xad ) WRITE (cltra,"(3a)") 'XAD' ! x advection for tracer
114               IF( jl == jptrc_yad ) WRITE (cltra,"(3a)") 'YAD'  ! y advection for tracer
115               IF( jl == jptrc_zad ) WRITE (cltra,"(3a)") 'ZAD'  ! z advection for tracer
116               IF( jl == jptrc_xdf ) WRITE (cltra,"(3a)") 'XDF'  ! x diffusion for tracer
117               IF( jl == jptrc_ydf ) WRITE (cltra,"(3a)") 'YDF'  ! y diffusion for tracer
118               IF( jl == jptrc_zdf ) WRITE (cltra,"(3a)") 'ZDF'  ! z diffusion for tracer
119# if defined key_trcldf_eiv
120               IF( jl == jptrc_xei ) WRITE (cltra,"(3a)") 'XGV'  ! x gent velocity for tracer
121               IF( jl == jptrc_yei ) WRITE (cltra,"(3a)") 'YGV'  ! y gent velocity for tracer
122               IF( jl == jptrc_zei ) WRITE (cltra,"(3a)") 'ZGV'  ! z gent velocity for tracer
123# endif
124# if defined key_trcdmp
125               IF( jl == jptrc_dmp ) WRITE (cltra,"(3a)") 'DMP'  ! damping
126# endif
127               IF( jl == jptrc_sbc ) WRITE (cltra,"(3a)") 'SBC'  ! surface boundary conditions
128               ! write the trends
129               CALL iom_put( cltra, trtrd(:,:,:,ikn,jl) )
130            END DO
131         END IF
132      END DO
133      !
134   END SUBROUTINE trc_wri_trd
135
136# else
137   SUBROUTINE trc_wri_trd( kt )                      ! Dummy routine
138      INTEGER, INTENT ( in ) ::   kt
139   END SUBROUTINE trc_wri_trd
140#endif
141#else
142   !!----------------------------------------------------------------------
143   !!  Dummy module :                                     No passive tracer
144   !!----------------------------------------------------------------------
145   PUBLIC trc_wri
146CONTAINS
147   SUBROUTINE trc_wri( kt )                     ! Empty routine   
148   INTEGER, INTENT(in) :: kt
149   END SUBROUTINE trc_wri
150#endif
151
152   !!======================================================================
153END MODULE trcwri
Note: See TracBrowser for help on using the repository browser.