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.
Changeset 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/C14/trcwri_c14.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/C14/trcwri_c14.F90

    r10425 r12928  
    2323   !   Standard ratio: 1.176E-12 ; Avogadro's nbr = 6.022E+23 at/mol ; bomb C14 traditionally reported as 1.E+26 atoms 
    2424   REAL(wp), PARAMETER  :: atomc14 = 1.176 * 6.022E-15   ! conversion factor  
     25   !! * Substitutions 
     26#  include "do_loop_substitute.h90" 
    2527 
    2628 
    2729CONTAINS 
    2830 
    29    SUBROUTINE trc_wri_c14 
     31   SUBROUTINE trc_wri_c14( Kmm ) 
    3032      !!--------------------------------------------------------------------- 
    3133      !!                     ***  ROUTINE trc_wri_c14  *** 
     
    3335      !! ** Purpose :   output additional C14 tracers fields  
    3436      !!--------------------------------------------------------------------- 
     37      INTEGER, INTENT(in)  :: Kmm           ! time level indices 
    3538      CHARACTER (len=20)   :: cltra         ! short title for tracer 
    3639      INTEGER              :: ji,jj,jk,jn   ! dummy loop indexes 
     
    4346      ! --------------------------------------- 
    4447      cltra = TRIM( ctrcnm(jp_c14) )                  ! short title for tracer 
    45       CALL iom_put( cltra, trn(:,:,:,jp_c14) ) 
     48      CALL iom_put( cltra, tr(:,:,:,jp_c14,Kmm) ) 
    4649 
    4750      ! compute and write the tracer diagnostic in the file 
     
    5760         zz3d(:,:,:) = 0._wp 
    5861         ! 
    59          DO jk = 1, jpkm1 
    60             DO jj = 1, jpj 
    61                DO ji = 1, jpi 
    62                   IF( tmask(ji,jj,jk) > 0._wp) THEN 
    63                      z3d (ji,jj,jk) = trn(ji,jj,jk,jp_c14) 
    64                      zz3d(ji,jj,jk) = LOG( z3d(ji,jj,jk) ) 
    65                   ENDIF 
    66                ENDDO 
    67             ENDDO 
    68          ENDDO 
     62         DO_3D_11_11( 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 
    6968         zres(:,:) = z3d(:,:,1) 
    7069 
     
    7271         z2d(:,:) =0._wp 
    7372         jk = 1 
    74          DO jj = 1, jpj 
    75             DO ji = 1, jpi 
    76                ztemp = zres(ji,jj) / c14sbc(ji,jj) 
    77                IF( ztemp > 0._wp .AND. tmask(ji,jj,jk) > 0._wp ) z2d(ji,jj) = LOG( ztemp ) 
    78             ENDDO 
    79          ENDDO 
     73         DO_2D_11_11 
     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 
    8077         ! 
    8178         z3d(:,:,:) = 1.d03 * ( z3d(:,:,:) - 1._wp ) 
     
    113110      ENDIF 
    114111      IF( iom_use("C14Inv") ) THEN 
    115          ztemp = glob_sum( 'trcwri_c14', trn(:,:,:,jp_c14) * cvol(:,:,:) ) 
     112         ztemp = glob_sum( 'trcwri_c14', tr(:,:,:,jp_c14,Kmm) * cvol(:,:,:) ) 
    116113         ztemp = atomc14 * xdicsur * ztemp 
    117114         CALL iom_put( "C14Inv", ztemp )  !  Radiocarbon ocean inventory [10^26 atoms] 
     
    130127#endif 
    131128 
     129   !! * Substitutions 
     130#  include "do_loop_substitute.h90" 
    132131   !!---------------------------------------------------------------------- 
    133132   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
Note: See TracChangeset for help on using the changeset viewer.