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.
trcsms_idtra.F90 in branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/IDTRA – NEMO

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/IDTRA/trcsms_idtra.F90 @ 6046

Last change on this file since 6046 was 6046, checked in by jpalmier, 8 years ago

JPALM -- 14-12-2015 -- Add the ideal tracer modules

File size: 5.7 KB
Line 
1MODULE trcsms_idtra
2   !!======================================================================
3   !!                      ***  MODULE trcsms_idtra  ***
4   !! TOP : TRI main model
5   !!======================================================================
6   !! History :    -   !  1999-10  (JC. Dutay)  original code
7   !!             1.0  !  2004-03 (C. Ethe) free form + modularity
8   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  reorganisation
9   !!----------------------------------------------------------------------
10#if defined key_idtra
11   !!----------------------------------------------------------------------
12   !!   'key_idtra'                                               TRI tracers
13   !!----------------------------------------------------------------------
14   !!   trc_sms_idtra     :  compute and add TRI suface forcing to TRI trends
15   !!   trc_idtra_cst :  sets constants for TRI surface forcing computation
16   !!----------------------------------------------------------------------
17   USE oce_trc      ! Ocean variables
18   USE par_trc      ! TOP parameters
19   USE trc          ! TOP variables
20   USE trd_oce
21   USE trdtrc
22   USE iom
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   trc_sms_idtra       ! called in ???
28
29   INTEGER , PUBLIC    ::   nyear_res      ! restoring time constant (year)
30   INTEGER , PUBLIC    ::   numnatm
31   REAL(wp), PUBLIC    ::   FDEC
32   !                          ! coefficients for conversion
33   REAL(wp) ::  WTEMP
34
35
36   !! * Substitutions
37#  include "top_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
40   !! $Id$
41   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43
44CONTAINS
45
46   SUBROUTINE trc_sms_idtra( kt )
47      !!----------------------------------------------------------------------
48      !!                     ***  ROUTINE trc_sms_idtra  ***
49      !!
50      !! ** Purpose :   Compute the surface boundary contition on TRI 11
51      !!             passive tracer associated with air-mer fluxes and add it
52      !!             to the general trend of tracers equations.
53      !!
54      !! ** Method  : - get the atmospheric partial pressure - given in pico -
55      !!              - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3)
56      !!              - computation of transfert speed ( given in cm/hour ----> cm/s )
57      !!              - the input function is given by :
58      !!                speed * ( concentration at equilibrium - concentration at surface )
59      !!              - the input function is in pico-mol/m3/s and the
60      !!                TRI concentration in pico-mol/m3
61      !!               
62      !! *** For Idealized Tracers             
63      !!              - no need for any temporal references,
64      !!              nor any atmospheric concentration, nor air -sea fluxes
65      !!              - Here we fixe surface concentration to 1.0 Tracer-Unit/m3
66      !!              - Then we add a decay (radioactive-like) to this tracer concentration
67      !!              - the Half life deccay is chosen by the user, depending of the experiment.
68      !!             
69      !!----------------------------------------------------------------------
70      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
71      !!
72      INTEGER ::   ji, jj, jn, jl, jk
73
74
75
76      !!----------------------------------------------------------------------
77      IF(lwp) WRITE(numout,*) '   - JPALM - verif :'
78      IF(lwp) WRITE(numout,*) '   ~~~~~~~~~~~~~~~~~'
79      IF(lwp) WRITE(numout,*) '   - idtra decay factor : ', FDEC
80
81
82         !
83DO jn = jp_idtra0, jp_idtra1
84
85        ! DO jj = 1, jpj
86        !    DO ji = 1, jpi
87               ! Surface concentrarion fixed to 1 (ideal tracer concentration unit)
88               trn(:,:,1,jn) = 1.
89               trb(:,:,1,jn) = 1.
90               !
91        !    ENDDO
92        ! ENDDO
93
94!
95!DECAY of OUR IDEALIZED TRACER
96! ---------------------------------------
97
98         DO  jk =1,jpk
99            DO jj=1,jpj
100              DO  ji =1,jpi
101               !  IF (trn(ji,jj,jk,jn) > 0.0) THEN
102                    WTEMP = trn(ji,jj,jk,jn) * (1. - FDEC )
103                    tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) - WTEMP/rdt
104               !  ENDIF
105              ENDDO 
106            ENDDO
107         ENDDO
108
109ENDDO
110    !! jn loop
111!
112
113!!!!!! No added diagnostics to save here for idealize tracers...
114!!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
115!! #if defined key_trc_diaadd
116!!       ! Save diagnostics , just for TRI111
117!! # if ! defined key_iomput
118!!       trc2d(:,:,jp_idtra0_2d    ) = zpp_idtra(:,:)
119!! # else
120!! !           WRITE(NUMOUT,*) 'Iomput idtrasurf '
121!!       CALL iom_put( "TRISURF"  , zpp_idtra(:,:) )
122!! !      CALL iom_put( "TRISURF"  , xphem(:,:) )
123!! !           WRITE(NUMOUT,*) 'Iomputage '
124!!        CALL iom_put( "AGE"  , zage(:,:,:) )
125!! # endif
126!! #endif
127!!
128
129!!      IF( l_trdtrc ) THEN
130!!          DO jn = jp_idtra0, jp_idtra1
131!!            zidtradtra(:,:,:) = tra(:,:,:,jn)
132!!            CALL trd_mod_trc( zidtradtra, jn, jptrc_trd_sms, kt )   ! save trends
133!!          END DO
134!!      END IF
135
136   END SUBROUTINE trc_sms_idtra
137#else
138   !!----------------------------------------------------------------------
139   !!   Dummy module                                         No TRI tracers
140   !!----------------------------------------------------------------------
141CONTAINS
142   SUBROUTINE trc_sms_idtra( kt )       ! Empty routine
143      WRITE(*,*) 'trc_sms_idtra: You should not have seen this print! error?', kt
144   END SUBROUTINE trc_sms_idtra
145#endif
146
147   !!======================================================================
148END MODULE trcsms_idtra
149
150
151
152
Note: See TracBrowser for help on using the repository browser.