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 branches/r6232_hadgem3_cplfld/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/r6232_hadgem3_cplfld/NEMOGCM/NEMO/TOP_SRC/PISCES/trcwri_pisces.F90 @ 7462

Last change on this file since 7462 was 7462, checked in by jcastill, 7 years ago

Remove svn keys

File size: 4.2 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 && ( defined key_pisces || defined key_pisces_reduced )
9   !!----------------------------------------------------------------------
10   !!   'key_pisces or key_pisces_reduced'                     PISCES model
11   !!----------------------------------------------------------------------
12   !! trc_wri_pisces   :  outputs of concentration fields
13   !!----------------------------------------------------------------------
14   USE trc         ! passive tracers common variables
15   USE sms_pisces  ! PISCES variables
16   USE iom         ! I/O manager
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC trc_wri_pisces 
22
23#  include "top_substitute.h90"
24CONTAINS
25
26   SUBROUTINE trc_wri_pisces
27      !!---------------------------------------------------------------------
28      !!                     ***  ROUTINE trc_wri_trc  ***
29      !!
30      !! ** Purpose :   output passive tracers fields
31      !!---------------------------------------------------------------------
32      CHARACTER (len=20)           :: cltra
33      REAL(wp)                     :: zfact
34      INTEGER                      :: ji, jj, jk, jn
35      REAL(wp), DIMENSION(jpi,jpj) :: zdic, zo2min, zdepo2min
36      !!---------------------------------------------------------------------
37 
38      ! write the tracer concentrations in the file
39      ! ---------------------------------------
40#if defined key_pisces_reduced
41      DO jn = jp_pcs0, jp_pcs1
42         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
43         CALL iom_put( cltra, trn(:,:,:,jn) )
44      END DO
45#else
46      DO jn = jp_pcs0, jp_pcs1
47         zfact = 1.0e+6 
48         IF( jn == jpno3 .OR. jn == jpnh4 ) zfact = rno3 * 1.0e+6 
49         IF( jn == jppo4  )                 zfact = po4r * 1.0e+6
50         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer
51         IF( iom_use( cltra ) )  CALL iom_put( cltra, trn(:,:,:,jn) * zfact )
52      END DO
53
54      IF( iom_use( "INTDIC" ) ) THEN                     !   DIC content in kg/m2
55         zdic(:,:) = 0.
56         DO jk = 1, jpkm1
57            zdic(:,:) = zdic(:,:) + trn(:,:,jk,jpdic) * fse3t(:,:,jk) * tmask(:,:,jk) * 12.
58         ENDDO
59         CALL iom_put( 'INTDIC', zdic )     
60      ENDIF
61      !
62      IF( iom_use( "O2MIN" ) .OR. iom_use ( "ZO2MIN" ) ) THEN  ! Oxygen minimum concentration and depth
63         zo2min   (:,:) = trn(:,:,1,jpoxy) * tmask(:,:,1)
64         zdepo2min(:,:) = fsdepw(:,:,1)    * tmask(:,:,1)
65         DO jk = 2, jpkm1
66            DO jj = 1, jpj
67               DO ji = 1, jpi
68                  IF( tmask(ji,jj,jk) == 1 ) then
69                     IF( trn(ji,jj,jk,jpoxy) < zo2min(ji,jj) ) then
70                        zo2min   (ji,jj) = trn(ji,jj,jk,jpoxy)
71                        zdepo2min(ji,jj) = fsdepw(ji,jj,jk)
72                     ENDIF
73                  ENDIF
74               END DO
75            END DO
76         END DO
77         !
78         CALL iom_put('O2MIN' , zo2min     )                              ! oxygen minimum concentration
79         CALL iom_put('ZO2MIN', zdepo2min  )                              ! depth of oxygen minimum concentration
80          !
81      ENDIF
82#endif
83      !
84   END SUBROUTINE trc_wri_pisces
85
86#else
87   !!----------------------------------------------------------------------
88   !!  Dummy module :                                     No passive tracer
89   !!----------------------------------------------------------------------
90   PUBLIC trc_wri_pisces
91CONTAINS
92   SUBROUTINE trc_wri_pisces                     ! Empty routine 
93   END SUBROUTINE trc_wri_pisces
94#endif
95
96   !!----------------------------------------------------------------------
97   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
98   !! $Id$
99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
100   !!======================================================================
101END MODULE trcwri_pisces
Note: See TracBrowser for help on using the repository browser.