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_r5107_NOC_MEDUSA/NEMOGCM/NEMO/TOP_SRC/IDTRA – NEMO

source: branches/NERC/dev_r5107_NOC_MEDUSA/NEMOGCM/NEMO/TOP_SRC/IDTRA/trcsms_idtra.F90 @ 5707

Last change on this file since 5707 was 5707, checked in by acc, 9 years ago

JPALM --25-08-2015 -- add MEDUSA in the branch. MEDUSA version already up-to-date with this trunk revision

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