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/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/C14 – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/C14/trcwri_c14.F90 @ 10975

Last change on this file since 10975 was 10975, checked in by acc, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Finish converting all TOP routines and knock-on effects of these conversions. Fully SETTE tested (SETTE tests 1-6 and 9). This completes the first stage conversion of TRA and TOP but need to revisit and pass ts and tr arrays through the argument lists where appropriate.

  • 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
26
27CONTAINS
28
29   SUBROUTINE trc_wri_c14( Kmm )
30      !!---------------------------------------------------------------------
31      !!                     ***  ROUTINE trc_wri_c14  ***
32      !!
33      !! ** Purpose :   output additional C14 tracers fields
34      !!---------------------------------------------------------------------
35      INTEGER, INTENT(in)  :: Kmm           ! time level indices
36      CHARACTER (len=20)   :: cltra         ! short title for tracer
37      INTEGER              :: ji,jj,jk,jn   ! dummy loop indexes
38      REAL(wp)             :: zage,zarea,ztemp   ! temporary
39      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   :: zres, z2d ! temporary storage 2D
40      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: z3d , zz3d ! temporary storage 3D
41      !!---------------------------------------------------------------------
42 
43      ! write the tracer concentrations in the file
44      ! ---------------------------------------
45      cltra = TRIM( ctrcnm(jp_c14) )                  ! short title for tracer
46      CALL iom_put( cltra, tr(:,:,:,jp_c14,Kmm) )
47
48      ! compute and write the tracer diagnostic in the file
49      ! ---------------------------------------
50     
51      IF( iom_use("DeltaC14") .OR. iom_use("C14Age") .OR. iom_use("RAge")   ) THEN
52         !
53         ALLOCATE( z2d(jpi,jpj), zres(jpi,jpj) )
54         ALLOCATE( z3d(jpi,jpj,jpk), zz3d(jpi,jpj,jpk) )
55         !
56         zage = -1._wp / rlam14 / rsiyea  ! factor for radioages in year
57         z3d(:,:,:)  = 1._wp
58         zz3d(:,:,:) = 0._wp
59         !
60         DO jk = 1, jpkm1
61            DO jj = 1, jpj
62               DO ji = 1, jpi
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               ENDDO
68            ENDDO
69         ENDDO
70         zres(:,:) = z3d(:,:,1)
71
72         ! Reservoir age [yr]
73         z2d(:,:) =0._wp
74         jk = 1
75         DO jj = 1, jpj
76            DO ji = 1, jpi
77               ztemp = zres(ji,jj) / c14sbc(ji,jj)
78               IF( ztemp > 0._wp .AND. tmask(ji,jj,jk) > 0._wp ) z2d(ji,jj) = LOG( ztemp )
79            ENDDO
80         ENDDO
81         !
82         z3d(:,:,:) = 1.d03 * ( z3d(:,:,:) - 1._wp )
83         CALL iom_put( "DeltaC14" , z3d(:,:,:)  )  ! Delta C14 [permil]
84         CALL iom_put( "C14Age"   , zage * zz3d(:,:,:) )            !  Radiocarbon age [yr]
85
86         CALL iom_put( "qtr_c14", rsiyea * qtr_c14(:,:)  )            !  Radiocarbon surf flux [./m2/yr]
87         CALL iom_put( "qint_c14" , qint_c14  )                       ! cumulative flux [./m2]
88         CALL iom_put( "RAge" , zage * z2d(:,:) )                     ! Reservoir age [yr]
89         !
90         DEALLOCATE( z2d, zres, z3d, zz3d )
91         !
92      ENDIF
93      !
94      !  0-D fields
95      !
96      CALL iom_put( "AtmCO2", co2sbc )  !     global atmospheric CO2 [ppm]
97   
98      IF( iom_use("AtmC14") ) THEN
99         zarea = glob_sum( 'trcwri_c14', e1e2t(:,:) )           ! global ocean surface
100         ztemp = glob_sum( 'trcwri_c14', c14sbc(:,:) * e1e2t(:,:) )
101         ztemp = ( ztemp / zarea - 1._wp ) * 1000._wp
102         CALL iom_put( "AtmC14" , ztemp )   ! Global atmospheric DeltaC14 [permil]
103      ENDIF
104      IF( iom_use("K_C14") ) THEN
105         ztemp = glob_sum ( 'trcwri_c14', exch_c14(:,:) * e1e2t(:,:) )
106         ztemp = rsiyea * ztemp / zarea
107         CALL iom_put( "K_C14" , ztemp )   ! global mean exchange velocity for C14/C ratio [m/yr]
108      ENDIF
109      IF( iom_use("K_CO2") ) THEN
110         zarea = glob_sum( 'trcwri_c14', e1e2t(:,:) )           ! global ocean surface
111         ztemp = glob_sum ( 'trcwri_c14', exch_co2(:,:) * e1e2t(:,:) )
112         ztemp = 360000._wp * ztemp / zarea       ! cm/h units: directly comparable with literature
113         CALL iom_put( "K_CO2", ztemp )  !  global mean CO2 piston velocity [cm/hr]
114      ENDIF
115      IF( iom_use("C14Inv") ) THEN
116         ztemp = glob_sum( 'trcwri_c14', tr(:,:,:,jp_c14,Kmm) * cvol(:,:,:) )
117         ztemp = atomc14 * xdicsur * ztemp
118         CALL iom_put( "C14Inv", ztemp )  !  Radiocarbon ocean inventory [10^26 atoms]
119      END IF
120      !
121   END SUBROUTINE trc_wri_c14
122
123#else
124   !!----------------------------------------------------------------------
125   !!  Dummy module :                                     No C14 tracer
126   !!----------------------------------------------------------------------
127   PUBLIC trc_wri_c14
128CONTAINS
129   SUBROUTINE trc_wri_c14                     ! Empty routine 
130   END SUBROUTINE trc_wri_c14
131#endif
132
133   !!----------------------------------------------------------------------
134   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
135   !! $Id$
136   !! Software governed by the CeCILL license (see ./LICENSE)
137   !!======================================================================
138END MODULE trcwri_c14
Note: See TracBrowser for help on using the repository browser.