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

source: NEMO/trunk/src/TOP/PISCES/trcwri_pisces.F90 @ 10068

Last change on this file since 10068 was 10068, checked in by nicolasmartin, 6 years ago

First part of modifications to have a common default header : fix typos and SVN keywords properties

  • Property svn:keywords set to yes
File size: 4.4 KB
RevLine 
[3295]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   !!----------------------------------------------------------------------
[7646]8#if defined key_top && defined key_iomput 
[3295]9   !!----------------------------------------------------------------------
10   !! trc_wri_pisces   :  outputs of concentration fields
11   !!----------------------------------------------------------------------
12   USE trc         ! passive tracers common variables
[3680]13   USE sms_pisces  ! PISCES variables
[3295]14   USE iom         ! I/O manager
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC trc_wri_pisces 
20
[6140]21   !!----------------------------------------------------------------------
[10067]22   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[6140]23   !! $Id: trcnam.F90 5836 2015-10-26 14:49:40Z cetlod $
[10068]24   !! Software governed by the CeCILL license (see ./LICENSE)
[6140]25   !!----------------------------------------------------------------------
[3295]26CONTAINS
27
28   SUBROUTINE trc_wri_pisces
29      !!---------------------------------------------------------------------
30      !!                     ***  ROUTINE trc_wri_trc  ***
31      !!
32      !! ** Purpose :   output passive tracers fields
33      !!---------------------------------------------------------------------
[4996]34      CHARACTER (len=20)           :: cltra
35      REAL(wp)                     :: zfact
36      INTEGER                      :: ji, jj, jk, jn
37      REAL(wp), DIMENSION(jpi,jpj) :: zdic, zo2min, zdepo2min
[3295]38      !!---------------------------------------------------------------------
39 
40      ! write the tracer concentrations in the file
41      ! ---------------------------------------
[7646]42      IF( ln_p2z ) THEN
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
[4996]55
[7646]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) * e3t_n(:,:,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(:,:) = gdepw_n(:,:,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) = gdepw_n(ji,jj,jk)
74                        ENDIF
[4996]75                     ENDIF
[7646]76                  END DO
[4996]77               END DO
78            END DO
[7646]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
[3295]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   !!----------------------------------------------------------------------
[10067]99   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[3295]100   !! $Id: trcwri_pisces.F90 3160 2011-11-20 14:27:18Z cetlod $
[10068]101   !! Software governed by the CeCILL license (see ./LICENSE)
[3295]102   !!======================================================================
103END MODULE trcwri_pisces
Note: See TracBrowser for help on using the repository browser.