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.
trcini_c14.F90 in branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/C14 – NEMO

source: branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/C14/trcini_c14.F90 @ 7068

Last change on this file since 7068 was 7068, checked in by cetlod, 8 years ago

ROBUST5_CNRS : implementation of part I of new TOP interface - 1st step -, see ticket #1782

File size: 3.4 KB
Line 
1MODULE trcini_c14
2   !!======================================================================
3   !!                         ***  MODULE trcini_c14  ***
4   !! TOP :   initialisation of the C14 tracers
5   !!======================================================================
6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec) Original code
7   !! History :   3.0  !  2015 (A. Mouchet) C14 Code
8   !!----------------------------------------------------------------------
9   !! trc_ini_c14   : C14 model initialisation
10   !!----------------------------------------------------------------------
11   USE par_trc         ! TOP parameters
12   USE oce_trc
13   USE trc
14   USE sms_c14
15   USE trcatm_c14
16   USE trcnam_c14
17   USE iom
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   trc_ini_c14   ! called by trcini.F90 module
23   
24   !
25
26   !!----------------------------------------------------------------------
27   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
28   !! $Id:               $
29   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE trc_ini_c14
34      !!----------------------------------------------------------------------
35      !!                     ***  trc_ini_c14  *** 
36      !!
37      !! ** Purpose :   initialization for C14 model
38      !!
39      !! ** Method  :
40      !!----------------------------------------------------------------------
41      !
42      REAL(wp) :: ztrai
43      INTEGER  :: jn
44      CHARACTER(len = 20)  ::  cltra
45      !!----------------------------------------------------------------------
46      !
47      !                       ! Allocate c14 arrays
48      IF( sms_c14_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_ini_c14: unable to allocate C14 arrays' )
49
50      IF(lwp) WRITE(numout,*)
51      IF(lwp) WRITE(numout,*) ' trc_ini_c14: initialisation of C14 model'
52      !
53      IF( .NOT. ln_rsttr )  THEN
54         !
55         IF(lwp) WRITE(numout,*) '                      ==>    PRESCRIBED initial VALUES'
56         IF(lwp) WRITE(numout,*) '                      ==>    Ocean C14/C :', rc14init 
57         !
58         trn(:,:,:,jp_c14) = rc14init * tmask(:,:,:)
59         !
60         qtr_c14(:,:) = 0._wp           ! Init of air-sea BC
61         !
62      ELSE
63
64        IF(lwp) WRITE(numout,*)
65        IF(lwp) WRITE(numout,*) ' trc_rst_read_c14 : Read specific variables for c14 model '
66        IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
67        !
68        CALL iom_get( numrtr, 'co2sbc', co2sbc ) 
69        CALL iom_get( numrtr, jpdom_autoglo, 'c14sbc', c14sbc ) 
70        CALL iom_get( numrtr, jpdom_autoglo, 'exch_co2', exch_co2 ) 
71        CALL iom_get( numrtr, jpdom_autoglo, 'exch_c14', exch_c14 ) 
72        CALL iom_get( numrtr, jpdom_autoglo, 'qtr_c14', qtr_c14 )
73        !
74      END IF
75      !
76      IF( ( nn_rsttr == 0 ) .OR. ( .NOT. ln_rsttr ) ) THEN
77      !
78      !                         !  qint set to zero <=== Initial of transient
79      !                         !                   <=== Restart=false
80         IF(lwp) WRITE(numout,*) '                    ==>    qint reset to ZERO '
81         qint_c14(:,:) = 0._wp
82      !
83      ELSE
84        !
85        CALL iom_get( numrtr, jpdom_autoglo, 'qint_c14', qint_c14 ) 
86        !
87      ENDIF
88      !
89      CALL trc_atm_c14_ini   ! Init atm values
90      !
91      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
92      !
93   END SUBROUTINE trc_ini_c14
94
95   !!======================================================================
96END MODULE trcini_c14
Note: See TracBrowser for help on using the repository browser.