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_c14.F90 in NEMO/branches/2020/r12377_ticket2386/src/TOP/C14 – NEMO

source: NEMO/branches/2020/r12377_ticket2386/src/TOP/C14/trcwri_c14.F90 @ 13540

Last change on this file since 13540 was 13540, checked in by andmirek, 3 years ago

Ticket #2386: update to latest trunk

  • Property svn:keywords set to Id
File size: 5.8 KB
Line 
1MODULE trcwri_c14
2   !!======================================================================
3   !!                       *** MODULE trcwri ***
4   !!    MY_SRC :   Additional outputs for C14 tracers
5   !!======================================================================
6   !! History :   1.0  !  2009-05 (C. Ethe)  Original code
7   !! History :   2.0  !  2015 (A. Mouchet)  adapted code for C14
8   !!----------------------------------------------------------------------
9#if defined key_top && defined key_iomput
10   !!----------------------------------------------------------------------
11   !! trc_wri_c14   :  outputs of ventilation fields
12   !!----------------------------------------------------------------------
13   USE oce_trc       ! Ocean variables
14   USE trc         ! passive tracers common variables
15   USE iom         ! I/O manager
16   USE sms_c14
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC trc_wri_c14
22   !
23   !   Standard ratio: 1.176E-12 ; Avogadro's nbr = 6.022E+23 at/mol ; bomb C14 traditionally reported as 1.E+26 atoms
24   REAL(wp), PARAMETER  :: atomc14 = 1.176 * 6.022E-15   ! conversion factor
25   !! * Substitutions
26#  include "do_loop_substitute.h90"
27
28
29CONTAINS
30
31   SUBROUTINE trc_wri_c14( Kmm )
32      !!---------------------------------------------------------------------
33      !!                     ***  ROUTINE trc_wri_c14  ***
34      !!
35      !! ** Purpose :   output additional C14 tracers fields
36      !!---------------------------------------------------------------------
37      INTEGER, INTENT(in)  :: Kmm           ! time level indices
38      CHARACTER (len=20)   :: cltra         ! short title for tracer
39      INTEGER              :: ji,jj,jk,jn   ! dummy loop indexes
40      REAL(wp)             :: zage,zarea,ztemp   ! temporary
41      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   :: zres, z2d ! temporary storage 2D
42      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: z3d , zz3d ! temporary storage 3D
43      !!---------------------------------------------------------------------
44 
45      ! write the tracer concentrations in the file
46      ! ---------------------------------------
47      cltra = TRIM( ctrcnm(jp_c14) )                  ! short title for tracer
48      CALL iom_put( cltra, tr(:,:,:,jp_c14,Kmm) )
49
50      ! compute and write the tracer diagnostic in the file
51      ! ---------------------------------------
52     
53      IF( iom_use("DeltaC14") .OR. iom_use("C14Age") .OR. iom_use("RAge")   ) THEN
54         !
55         ALLOCATE( z2d(jpi,jpj), zres(jpi,jpj) )
56         ALLOCATE( z3d(jpi,jpj,jpk), zz3d(jpi,jpj,jpk) )
57         !
58         zage = -1._wp / rlam14 / rsiyea  ! factor for radioages in year
59         z3d(:,:,:)  = 1._wp
60         zz3d(:,:,:) = 0._wp
61         !
62         DO_3D( 1, 1, 1, 1, 1, jpkm1 )
63            IF( tmask(ji,jj,jk) > 0._wp) THEN
64               z3d (ji,jj,jk) = tr(ji,jj,jk,jp_c14,Kmm)
65               zz3d(ji,jj,jk) = LOG( z3d(ji,jj,jk) )
66            ENDIF
67         END_3D
68         zres(:,:) = z3d(:,:,1)
69
70         ! Reservoir age [yr]
71         z2d(:,:) =0._wp
72         jk = 1
73         DO_2D( 1, 1, 1, 1 )
74            ztemp = zres(ji,jj) / c14sbc(ji,jj)
75            IF( ztemp > 0._wp .AND. tmask(ji,jj,jk) > 0._wp ) z2d(ji,jj) = LOG( ztemp )
76         END_2D
77         !
78         z3d(:,:,:) = 1.d03 * ( z3d(:,:,:) - 1._wp )
79         CALL iom_put( "DeltaC14" , z3d(:,:,:)  )  ! Delta C14 [permil]
80         CALL iom_put( "C14Age"   , zage * zz3d(:,:,:) )            !  Radiocarbon age [yr]
81
82         CALL iom_put( "qtr_c14", rsiyea * qtr_c14(:,:)  )            !  Radiocarbon surf flux [./m2/yr]
83         CALL iom_put( "qint_c14" , qint_c14  )                       ! cumulative flux [./m2]
84         CALL iom_put( "RAge" , zage * z2d(:,:) )                     ! Reservoir age [yr]
85         !
86         DEALLOCATE( z2d, zres, z3d, zz3d )
87         !
88      ENDIF
89      !
90      !  0-D fields
91      !
92      CALL iom_put( "AtmCO2", co2sbc )  !     global atmospheric CO2 [ppm]
93   
94      IF( iom_use("AtmC14") ) THEN
95         zarea = glob_sum( 'trcwri_c14', e1e2t(:,:) )           ! global ocean surface
96         ztemp = glob_sum( 'trcwri_c14', c14sbc(:,:) * e1e2t(:,:) )
97         ztemp = ( ztemp / zarea - 1._wp ) * 1000._wp
98         CALL iom_put( "AtmC14" , ztemp )   ! Global atmospheric DeltaC14 [permil]
99      ENDIF
100      IF( iom_use("K_C14") ) THEN
101         ztemp = glob_sum ( 'trcwri_c14', exch_c14(:,:) * e1e2t(:,:) )
102         ztemp = rsiyea * ztemp / zarea
103         CALL iom_put( "K_C14" , ztemp )   ! global mean exchange velocity for C14/C ratio [m/yr]
104      ENDIF
105      IF( iom_use("K_CO2") ) THEN
106         zarea = glob_sum( 'trcwri_c14', e1e2t(:,:) )           ! global ocean surface
107         ztemp = glob_sum ( 'trcwri_c14', exch_co2(:,:) * e1e2t(:,:) )
108         ztemp = 360000._wp * ztemp / zarea       ! cm/h units: directly comparable with literature
109         CALL iom_put( "K_CO2", ztemp )  !  global mean CO2 piston velocity [cm/hr]
110      ENDIF
111      IF( iom_use("C14Inv") ) THEN
112         ztemp = glob_sum( 'trcwri_c14', tr(:,:,:,jp_c14,Kmm) * cvol(:,:,:) )
113         ztemp = atomc14 * xdicsur * ztemp
114         CALL iom_put( "C14Inv", ztemp )  !  Radiocarbon ocean inventory [10^26 atoms]
115      END IF
116      !
117   END SUBROUTINE trc_wri_c14
118
119#else
120   !!----------------------------------------------------------------------
121   !!  Dummy module :                                     No C14 tracer
122   !!----------------------------------------------------------------------
123   PUBLIC trc_wri_c14
124CONTAINS
125   SUBROUTINE trc_wri_c14                     ! Empty routine 
126   END SUBROUTINE trc_wri_c14
127#endif
128
129   !! * Substitutions
130#  include "do_loop_substitute.h90"
131   !!----------------------------------------------------------------------
132   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
133   !! $Id$
134   !! Software governed by the CeCILL license (see ./LICENSE)
135   !!======================================================================
136END MODULE trcwri_c14
Note: See TracBrowser for help on using the repository browser.