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

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/trcwri_pisces.F90 @ 11949

Last change on this file since 11949 was 11949, checked in by acc, 4 years ago

Merge in changes from 2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps. This just creates a fresh copy of this branch to use as the merge base. See ticket #2341

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