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_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/PISCES – NEMO

source: NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/PISCES/trcwri_pisces.F90 @ 12928

Last change on this file since 12928 was 12928, checked in by smueller, 4 years ago

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

  • Property svn:keywords set to Id
File size: 4.3 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   !!----------------------------------------------------------------------
24   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
25   !! $Id$
26   !! Software governed by the CeCILL license (see ./LICENSE)
27   !!----------------------------------------------------------------------
28CONTAINS
29
30   SUBROUTINE trc_wri_pisces( Kmm )
31      !!---------------------------------------------------------------------
32      !!                     ***  ROUTINE trc_wri_trc  ***
33      !!
34      !! ** Purpose :   output passive tracers fields
35      !!---------------------------------------------------------------------
36      INTEGER, INTENT(in)          :: Kmm      ! time level indices
37      CHARACTER (len=20)           :: cltra
38      REAL(wp)                     :: zfact
39      INTEGER                      :: ji, jj, jk, jn
40      REAL(wp), DIMENSION(jpi,jpj) :: zdic, zo2min, zdepo2min
41      !!---------------------------------------------------------------------
42 
43      ! write the tracer concentrations in the file
44      ! ---------------------------------------
45      IF( ln_p2z ) THEN
46         DO jn = jp_pcs0, jp_pcs1
47            cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
48            CALL iom_put( cltra, tr(:,:,:,jn,Kmm) )
49         END DO
50      ELSE
51         DO jn = jp_pcs0, jp_pcs1
52            zfact = 1.0e+6 
53            IF( jn == jpno3 .OR. jn == jpnh4 ) zfact = rno3 * 1.0e+6 
54            IF( jn == jppo4  )                 zfact = po4r * 1.0e+6
55            cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
56            IF( iom_use( cltra ) )  CALL iom_put( cltra, tr(:,:,:,jn,Kmm) * zfact )
57         END DO
58
59         IF( iom_use( "INTDIC" ) ) THEN                     !   DIC content in kg/m2
60            zdic(:,:) = 0.
61            DO jk = 1, jpkm1
62               zdic(:,:) = zdic(:,:) + tr(:,:,jk,jpdic,Kmm) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) * 12.
63            ENDDO
64            CALL iom_put( 'INTDIC', zdic )     
65         ENDIF
66         !
67         IF( iom_use( "O2MIN" ) .OR. iom_use ( "ZO2MIN" ) ) THEN  ! Oxygen minimum concentration and depth
68            zo2min   (:,:) = tr(:,:,1,jpoxy,Kmm) * tmask(:,:,1)
69            zdepo2min(:,:) = gdepw(:,:,1,Kmm)   * tmask(:,:,1)
70            DO_3D_11_11( 2, jpkm1 )
71               IF( tmask(ji,jj,jk) == 1 ) then
72                  IF( tr(ji,jj,jk,jpoxy,Kmm) < zo2min(ji,jj) ) then
73                     zo2min   (ji,jj) = tr(ji,jj,jk,jpoxy,Kmm)
74                     zdepo2min(ji,jj) = gdepw(ji,jj,jk,Kmm)
75                  ENDIF
76               ENDIF
77            END_3D
78            !
79            CALL iom_put('O2MIN' , zo2min     )                              ! oxygen minimum concentration
80            CALL iom_put('ZO2MIN', zdepo2min  )                              ! depth of oxygen minimum concentration
81             !
82         ENDIF
83     ENDIF
84      !
85   END SUBROUTINE trc_wri_pisces
86
87#else
88   !!----------------------------------------------------------------------
89   !!  Dummy module :                                     No passive tracer
90   !!----------------------------------------------------------------------
91   PUBLIC trc_wri_pisces
92CONTAINS
93   SUBROUTINE trc_wri_pisces                     ! Empty routine 
94   END SUBROUTINE trc_wri_pisces
95#endif
96
97   !!----------------------------------------------------------------------
98   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
99   !! $Id$
100   !! Software governed by the CeCILL license (see ./LICENSE)
101   !!======================================================================
102END MODULE trcwri_pisces
Note: See TracBrowser for help on using the repository browser.