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/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/PISCES/trcwri_pisces.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 8 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

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