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/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/TOP_SRC/PISCES/trcwri_pisces.F90 @ 6808

Last change on this file since 6808 was 6808, checked in by jamesharle, 8 years ago

merge with trunk@6232 for consistency with SSB code

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