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_pisces.F90 in NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/TOP/PISCES – NEMO

source: NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/TOP/PISCES/trcwri_pisces.F90 @ 13463

Last change on this file since 13463 was 13463, checked in by andmirek, 4 years ago

Ticket #2195:update to trunk 13461

  • Property svn:keywords set to Id
File size: 4.4 KB
Line 
1MODULE trcwri_pisces
2   !!======================================================================
3   !!                       *** MODULE trcwri ***
4   !!    PISCES :   Output of PISCES tracers
5   !!======================================================================
6   !! History :   1.0  !  2009-05 (C. Ethe)  Original code
7   !!----------------------------------------------------------------------
8#if defined key_top && defined key_iomput 
9   !!----------------------------------------------------------------------
10   !! trc_wri_pisces   :  outputs of concentration fields
11   !!----------------------------------------------------------------------
12   USE trc         ! passive tracers common variables
13   USE sms_pisces  ! PISCES variables
14   USE iom         ! I/O manager
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC trc_wri_pisces 
20
21   !! * Substitutions
22#  include "do_loop_substitute.h90"
23#  include "domzgr_substitute.h90"
24   !!----------------------------------------------------------------------
25   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
26   !! $Id$
27   !! Software governed by the CeCILL license (see ./LICENSE)
28   !!----------------------------------------------------------------------
29CONTAINS
30
31   SUBROUTINE trc_wri_pisces( Kmm )
32      !!---------------------------------------------------------------------
33      !!                     ***  ROUTINE trc_wri_trc  ***
34      !!
35      !! ** Purpose :   output passive tracers fields
36      !!---------------------------------------------------------------------
37      INTEGER, INTENT(in)          :: Kmm      ! time level indices
38      CHARACTER (len=20)           :: cltra
39      REAL(wp)                     :: zfact
40      INTEGER                      :: ji, jj, jk, jn
41      REAL(wp), DIMENSION(jpi,jpj) :: zdic, zo2min, zdepo2min
42      !!---------------------------------------------------------------------
43 
44      ! write the tracer concentrations in the file
45      ! ---------------------------------------
46      IF( ln_p2z ) THEN
47         DO jn = jp_pcs0, jp_pcs1
48            cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
49            CALL iom_put( cltra, tr(:,:,:,jn,Kmm) )
50         END DO
51      ELSE
52         DO jn = jp_pcs0, jp_pcs1
53            zfact = 1.0e+6 
54            IF( jn == jpno3 .OR. jn == jpnh4 ) zfact = rno3 * 1.0e+6 
55            IF( jn == jppo4  )                 zfact = po4r * 1.0e+6
56            cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
57            IF( iom_use( cltra ) )  CALL iom_put( cltra, tr(:,:,:,jn,Kmm) * zfact )
58         END DO
59
60         IF( iom_use( "INTDIC" ) ) THEN                     !   DIC content in kg/m2
61            zdic(:,:) = 0.
62            DO jk = 1, jpkm1
63               zdic(:,:) = zdic(:,:) + tr(:,:,jk,jpdic,Kmm) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) * 12.
64            ENDDO
65            CALL iom_put( 'INTDIC', zdic )     
66         ENDIF
67         !
68         IF( iom_use( "O2MIN" ) .OR. iom_use ( "ZO2MIN" ) ) THEN  ! Oxygen minimum concentration and depth
69            zo2min   (:,:) = tr(:,:,1,jpoxy,Kmm) * tmask(:,:,1)
70            zdepo2min(:,:) = gdepw(:,:,1,Kmm)   * tmask(:,:,1)
71            DO_3D( 1, 1, 1, 1, 2, jpkm1 )
72               IF( tmask(ji,jj,jk) == 1 ) then
73                  IF( tr(ji,jj,jk,jpoxy,Kmm) < zo2min(ji,jj) ) then
74                     zo2min   (ji,jj) = tr(ji,jj,jk,jpoxy,Kmm)
75                     zdepo2min(ji,jj) = gdepw(ji,jj,jk,Kmm)
76                  ENDIF
77               ENDIF
78            END_3D
79            !
80            CALL iom_put('O2MIN' , zo2min     )                              ! oxygen minimum concentration
81            CALL iom_put('ZO2MIN', zdepo2min  )                              ! depth of oxygen minimum concentration
82             !
83         ENDIF
84     ENDIF
85      !
86   END SUBROUTINE trc_wri_pisces
87
88#else
89   !!----------------------------------------------------------------------
90   !!  Dummy module :                                     No passive tracer
91   !!----------------------------------------------------------------------
92   PUBLIC trc_wri_pisces
93CONTAINS
94   SUBROUTINE trc_wri_pisces                     ! Empty routine 
95   END SUBROUTINE trc_wri_pisces
96#endif
97
98   !!----------------------------------------------------------------------
99   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
100   !! $Id$
101   !! Software governed by the CeCILL license (see ./LICENSE)
102   !!======================================================================
103END MODULE trcwri_pisces
Note: See TracBrowser for help on using the repository browser.