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_cfc.F90 in branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/CFC – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/CFC/trcsms_cfc.F90

Last change on this file was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 20.3 KB
Line 
1MODULE trcsms_cfc
2   !!======================================================================
3   !!                      ***  MODULE trcsms_cfc  ***
4   !! TOP : CFC main model
5   !!======================================================================
6   !! History :  OPA  !  1999-10  (JC. Dutay)  original code
7   !!  NEMO      1.0  !  2004-03  (C. Ethe) free form + modularity
8   !!            2.0  !  2007-12  (C. Ethe, G. Madec)  reorganisation
9   !!                 !  2016-06  (J. Palmieri)  update for UKESM1
10   !!                 !  2017-04  (A. Yool)  update to add SF6, fix coefficients
11   !!----------------------------------------------------------------------
12#if defined key_cfc
13   !!----------------------------------------------------------------------
14   !!   'key_cfc'                                               CFC tracers
15   !!----------------------------------------------------------------------
16   !!   trc_sms_cfc  :  compute and add CFC suface forcing to CFC trends
17   !!   cfc_init     :  sets constants for CFC surface forcing computation
18   !!----------------------------------------------------------------------
19   USE dom_oce       ! ocean space and time domain
20   USE oce_trc       ! Ocean variables
21   USE par_trc       ! TOP parameters
22   USE trc           ! TOP variables
23   USE trd_oce
24   USE trdtrc
25   USE iom           ! I/O library
26   USE wrk_nemo
27
28   USE yomhook, ONLY: lhook, dr_hook
29   USE parkind1, ONLY: jprb, jpim
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   trc_sms_cfc         ! called in ???   
35   PUBLIC   trc_sms_cfc_alloc   ! called in trcini_cfc.F90
36
37   INTEGER , PUBLIC, PARAMETER ::   jphem  =   2   ! parameter for the 2 hemispheres
38   INTEGER , PUBLIC            ::   jpyear         ! Number of years read in CFC1112 file
39   INTEGER , PUBLIC            ::   ndate_beg      ! initial calendar date (aammjj) for CFC
40   INTEGER , PUBLIC            ::   simu_type      ! Kind of simulation: 1- Spin-up
41                                                   !                     2- Hindcast/projection
42   INTEGER , PUBLIC            ::   nyear_res      ! restoring time constant (year)
43   INTEGER , PUBLIC            ::   nyear_beg      ! initial year (aa)
44   
45   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   p_cfc    ! partial hemispheric pressure for CFC
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   xphem    ! spatial interpolation factor for patm
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qtr_cfc  ! flux at surface
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qint_cfc ! cumulative flux
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   patm     ! atmospheric function
50
51   REAL(wp), DIMENSION(4,3) ::   soa   ! coefficient for solubility of CFC [mol/l/atm]
52   REAL(wp), DIMENSION(3,3) ::   sob   !    "               "
53   REAL(wp), DIMENSION(5,3) ::   sca   ! coefficients for schmidt number in degre Celcius
54     
55   !                          ! coefficients for conversion
56   REAL(wp) ::   xconv1 = 1.0          ! conversion from to
57   REAL(wp) ::   xconv2 = 0.01/3600.   ! conversion from cm/h to m/s:
58   REAL(wp) ::   xconv3 = 1.0e+3       ! conversion from mol/l/atm to mol/m3/atm
59   REAL(wp) ::   xconv4 = 1.0e-12      ! conversion from mol/m3/atm to mol/m3/pptv
60
61   !! trend temporary array:
62   REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrcfc
63
64   !! * Substitutions
65#  include "top_substitute.h90"
66   !!----------------------------------------------------------------------
67   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
68   !! $Id$
69   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
70   !!----------------------------------------------------------------------
71CONTAINS
72
73   SUBROUTINE trc_sms_cfc( kt )
74      !!----------------------------------------------------------------------
75      !!                     ***  ROUTINE trc_sms_cfc  ***
76      !!
77      !! ** Purpose :   Compute the surface boundary contition on CFC 11
78      !!             passive tracer associated with air-mer fluxes and add it
79      !!             to the general trend of tracers equations.
80      !!
81      !! ** Method  : - get the atmospheric partial pressure - given in pico -
82      !!              - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3)
83      !!              - computation of transfert speed ( given in cm/hour ----> cm/s )
84      !!              - the input function is given by :
85      !!                speed * ( concentration at equilibrium - concentration at surface )
86      !!              - the input function is in pico-mol/m3/s and the
87      !!                CFC concentration in pico-mol/m3
88      !!----------------------------------------------------------------------
89      !
90      INTEGER, INTENT(in) ::   kt    ! ocean time-step index
91      !
92      INTEGER  ::   ji, jj, jn, jl, jm, js
93      INTEGER  ::   iyear_beg, iyear_end, iyear_tmp
94      INTEGER  ::   im1, im2, ierr
95      REAL(wp) ::   ztap, zdtap       
96      REAL(wp) ::   zt1, zt2, zt3, zt4, zv2
97      REAL(wp) ::   zsol      ! solubility
98      REAL(wp) ::   zsch      ! schmidt number
99      REAL(wp) ::   zpp_cfc   ! atmospheric partial pressure of CFC
100      REAL(wp) ::   zca_cfc   ! concentration at equilibrium
101      REAL(wp) ::   zak_cfc   ! transfert coefficients
102      REAL(wp), ALLOCATABLE, DIMENSION(:,:)  ::   zpatm     ! atmospheric function
103      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
104      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
105      REAL(KIND=jprb)               :: zhook_handle
106
107      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_SMS_CFC'
108
109      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
110
111      !!----------------------------------------------------------------------
112      !
113      !
114      IF( nn_timing == 1 )  CALL timing_start('trc_sms_cfc')
115      !
116      ALLOCATE( zpatm(jphem,jp_cfc), STAT=ierr )
117      IF( ierr > 0 ) THEN
118         CALL ctl_stop( 'trc_sms_cfc: unable to allocate zpatm array' )   ;   RETURN
119      ENDIF
120
121      IF( kt == nittrc000 )   CALL cfc_init
122
123      ! Temporal interpolation
124      ! ----------------------
125      !! JPALM -- 15-06-2016 -- define 2 kinds of CFC run:
126      !!                     1- the SPIN-UP and 2- Hindcast/Projections
127      !!                     -- main difference is the way to define the year of
128      !!                     simulation, that determine the atm pCFC.
129      !!                     1-- Spin-up: our atm forcing is of 30y we cycle on.
130      !!                     So we do 90y CFC cycles to be in good
131      !!                     correspondence with the atmosphere
132      !!                     2-- Hindcast/proj, instead of nyear-1900 we keep
133      !!                     the 2 last digit, and enable 3 cycle from 1800 to 2100. 
134      !!----------------------------------------------------------------------
135      IF (simu_type==1) THEN
136         !! 1 -- SPIN-UP
137         iyear_tmp = nyear - nyear_res  !! JPALM -- in our spin-up, nyear_res is 1000
138         iyear_beg = MOD( iyear_tmp , 90 )
139         !! JPALM -- the pCFC file only got 78 years.
140         !!       So if iyear_beg > 78 then we set pCFC to 0
141         !!             iyear_beg = 0 as well -- must try to avoid obvious problems
142         !!             as Pcfc is set to 0.00 up to year 32, let set iyear_beg to year 10
143         !!          else, must add 30 to iyear_beg to match with P_cfc indices
144         !!---------------------------------------
145         IF ((iyear_beg > 77) .OR. (iyear_beg==0)) THEN
146            iyear_beg = 10
147         ELSE
148            iyear_beg = iyear_beg + 30
149         ENDIF
150      ELSEIF (simu_type==2) THEN
151         !! 2 -- Hindcast/proj
152         iyear_beg = MOD(nyear, 100)
153         IF (iyear_beg < 20)  iyear_beg = iyear_beg + 100
154         !! JPALM -- Same than previously, if iyear_beg is out of P_cfc range,
155         !!       we want to set p_CFC to 0.00 --> set iyear_beg = 10
156         IF ((iyear_beg < 30) .OR. (iyear_beg > 115)) iyear_beg = 10             
157      ENDIF
158      !!
159      IF ( nmonth <= 6 ) THEN
160         iyear_beg = iyear_beg - 1
161         im1       =  6 - nmonth + 1
162         im2       =  6 + nmonth - 1
163      ELSE
164         im1       = 12 - nmonth + 7
165         im2       =      nmonth - 7
166      ENDIF
167      iyear_end = iyear_beg + 1
168
169      !                                                  !------------!
170      DO jl = 1, jp_cfc                                  !  CFC loop  !
171         !                                               !------------!
172         jn = jp_cfc0 + jl - 1
173         ! time interpolation at time kt
174         DO jm = 1, jphem
175            zpatm(jm,jl) = (  p_cfc(iyear_beg, jm, jl) * FLOAT (im1)  &
176               &           +  p_cfc(iyear_end, jm, jl) * FLOAT (im2) ) / 12.
177         END DO
178         
179         !                                                         !------------!
180         DO jj = 1, jpj                                            !  i-j loop  !
181            DO ji = 1, jpi                                         !------------!
182 
183               ! space interpolation
184               zpp_cfc  =       xphem(ji,jj)   * zpatm(1,jl)   &
185                  &     + ( 1.- xphem(ji,jj) ) * zpatm(2,jl)
186
187               ! Computation of concentration at equilibrium : in picomol/l
188               ! coefficient for solubility for CFC-11/12 in  mol/l/atm
189               IF( tmask(ji,jj,1) .GE. 0.5 ) THEN
190                  ztap  = ( tsn(ji,jj,1,jp_tem) + 273.16 ) * 0.01
191                  zdtap = sob(1,jl) + ztap * ( sob(2,jl) + ztap * sob(3,jl) ) 
192                  zsol  =  EXP( soa(1,jl) + soa(2,jl) / ztap + soa(3,jl) * LOG( ztap )   &
193                     &                    + soa(4,jl) * ztap * ztap + tsn(ji,jj,1,jp_sal) * zdtap ) 
194               ELSE
195                  zsol  = 0.e0
196               ENDIF
197               ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv   
198               zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1) 
199               ! concentration at equilibrium
200               zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1)             
201 
202               ! Computation of speed transfert
203               !    Schmidt number
204               zt1  = tsn(ji,jj,1,jp_tem)
205               zt2  = zt1 * zt1 
206               zt3  = zt1 * zt2
207               zt4  = zt1 * zt3
208               zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 + sca(5,jl) * zt4
209
210               !    speed transfert : formulae of wanninkhof 1992
211               zv2     = wndm(ji,jj) * wndm(ji,jj)
212               zsch    = zsch / 660.
213               ! AXY (25/04/17): OMIP protocol specifies lower Wanninkhof (2014) value
214               ! zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1)
215               zak_cfc = ( 0.251 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1)
216
217               ! Input function  : speed *( conc. at equil - concen at surface )
218               ! trn in pico-mol/l idem qtr; ak in en m/a
219               qtr_cfc(ji,jj,jl) = -zak_cfc * ( trb(ji,jj,1,jn) - zca_cfc )   &
220#if defined key_degrad
221                  &                         * facvol(ji,jj,1)                           &
222#endif
223                  &                         * tmask(ji,jj,1) * ( 1. - fr_i(ji,jj) )
224               ! Add the surface flux to the trend
225               tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr_cfc(ji,jj,jl) / fse3t(ji,jj,1) 
226
227               ! cumulation of surface flux at each time step
228               qint_cfc(ji,jj,jl) = qint_cfc(ji,jj,jl) + qtr_cfc(ji,jj,jl) * rdt
229               !                                               !----------------!
230            END DO                                             !  end i-j loop  !
231         END DO                                                !----------------!
232         !                                                  !----------------!
233      END DO                                                !  end CFC loop  !
234         !
235      IF( kt == nittrc000 ) THEN
236         DO jl = 1, jp_cfc   
237             WRITE(NUMOUT,*) ' '
238             WRITE(NUMOUT,*) 'CFC interpolation verification '  !! Jpalm 
239             WRITE(NUMOUT,*) '################################## '
240             WRITE(NUMOUT,*) ' '
241               if (jl.EQ.1) then
242                   WRITE(NUMOUT,*) 'Traceur = CFC11: '
243               elseif (jl.EQ.2) then
244                   WRITE(NUMOUT,*) 'Traceur = CFC12: '
245               elseif (jl.EQ.3) then
246                   WRITE(NUMOUT,*) 'Traceur = SF6: '
247               endif
248             WRITE(NUMOUT,*) 'nyear    = ', nyear
249             WRITE(NUMOUT,*) 'nmonth   = ', nmonth
250             WRITE(NUMOUT,*) 'iyear_beg= ', iyear_beg
251             WRITE(NUMOUT,*) 'iyear_end= ', iyear_end
252             WRITE(NUMOUT,*) 'p_cfc(iyear_beg)= ',p_cfc(iyear_beg, 1, jl)
253             WRITE(NUMOUT,*) 'p_cfc(iyear_end)= ',p_cfc(iyear_end, 1, jl)
254             WRITE(NUMOUT,*) 'Im1= ',im1
255             WRITE(NUMOUT,*) 'Im2= ',im2
256             WRITE(NUMOUT,*) 'zpp_cfc = ',zpp_cfc
257             WRITE(NUMOUT,*) ' '
258         END DO 
259# if defined key_debug_medusa
260         CALL flush(numout)
261# endif
262      ENDIF
263        !
264      !IF( lrst_trc ) THEN
265      !   IF(lwp) WRITE(numout,*)
266      !   IF(lwp) WRITE(numout,*) 'trc_sms_cfc : cumulated input function fields written in ocean restart file ',   &
267      !      &                    'at it= ', kt,' date= ', ndastp
268      !   IF(lwp) WRITE(numout,*) '~~~~'
269      !   DO jn = jp_cfc0, jp_cfc1
270      !      CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) )
271      !   END DO
272      !ENDIF                                           
273      !
274      IF  (iom_use("qtrCFC11"))  CALL iom_put( "qtrCFC11"  , qtr_cfc (:,:,1) )
275      IF  (iom_use("qintCFC11")) CALL iom_put( "qintCFC11" , qint_cfc(:,:,1) )
276      IF  (iom_use("qtrCFC12"))  CALL iom_put( "qtrCFC12"  , qtr_cfc (:,:,2) )
277      IF  (iom_use("qintCFC12")) CALL iom_put( "qintCFC12" , qint_cfc(:,:,2) )
278      IF  (iom_use("qtrSF6"))    CALL iom_put( "qtrSF6"    , qtr_cfc (:,:,3) )
279      IF  (iom_use("qintSF6"))   CALL iom_put( "qintSF6"   , qint_cfc(:,:,3) )
280      !
281      IF( l_trdtrc ) THEN
282          CALL wrk_alloc( jpi, jpj, jpk, ztrcfc )
283          DO jn = jp_cfc0, jp_cfc1
284             ztrcfc(:,:,:) = tra(:,:,:,jn)
285            CALL trd_trc( ztrcfc, jn, jptra_sms, kt )   ! save trends
286          END DO
287          CALL wrk_dealloc( jpi, jpj, jpk, ztrcfc )
288      END IF
289      !
290# if defined key_debug_medusa
291      IF(lwp) WRITE(numout,*) '   CFC - Check: nn_timing = ', nn_timing
292      CALL flush(numout)
293# endif
294      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_cfc')
295      !
296      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
297   END SUBROUTINE trc_sms_cfc
298
299
300   SUBROUTINE cfc_init
301      !!---------------------------------------------------------------------
302      !!                     ***  cfc_init  *** 
303      !!
304      !! ** Purpose : sets constants for CFC model
305      !!---------------------------------------------------------------------
306      INTEGER :: jl, jn, iyear_beg, iyear_tmp
307      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
308      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
309      REAL(KIND=jprb)               :: zhook_handle
310
311      CHARACTER(LEN=*), PARAMETER :: RoutineName='CFC_INIT'
312
313      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
314
315
316      ! coefficient for CFC11
317      !----------------------
318
319      ! Solubility
320      soa(1,1) = -229.9261 
321      soa(2,1) =  319.6552
322      soa(3,1) =  119.4471
323      soa(4,1) =   -1.39165
324
325      sob(1,1) = -0.142382
326      sob(2,1) =  0.091459
327      sob(3,1) = -0.0157274
328
329      ! Schmidt number          AXY (25/04/17)
330      sca(1,1) = 3579.2       ! = 3501.8
331      sca(2,1) = -222.63      ! = -210.31
332      sca(3,1) =    7.5749    ! =    6.1851
333      sca(4,1) =   -0.14595   ! =   -0.07513
334      sca(5,1) =    0.0011874 ! = absent
335
336      ! coefficient for CFC12
337      !----------------------
338
339      ! Solubility
340      soa(1,2) = -218.0971
341      soa(2,2) =  298.9702
342      soa(3,2) =  113.8049
343      soa(4,2) =   -1.39165
344
345      sob(1,2) = -0.143566
346      sob(2,2) =  0.091015
347      sob(3,2) = -0.0153924
348
349      ! schmidt number         AXY (25/04/17)
350      sca(1,2) = 3828.1      ! = 3845.4
351      sca(2,2) = -249.86     ! = -228.95
352      sca(3,2) =    8.7603   ! =    6.1908
353      sca(4,2) =   -0.1716   ! =   -0.067430
354      sca(5,2) =    0.001408 ! = absent
355
356      ! coefficients for SF6   AXY (25/04/17)
357      !---------------------
358     
359      ! Solubility
360      soa(1,3) =  -80.0343
361      soa(2,3) =  117.232
362      soa(3,3) =   29.5817
363      soa(4,3) =    0.0
364
365      sob(1,3) =  0.0335183
366      sob(2,3) = -0.0373942
367      sob(3,3) =  0.00774862
368
369      ! Schmidt number
370      sca(1,3) = 3177.5
371      sca(2,3) = -200.57
372      sca(3,3) =    6.8865
373      sca(4,3) =   -0.13335
374      sca(5,3) =    0.0010877
375
376      !!---------------------------------------------
377      !! JPALM -- re-initialize CFC fields and diags if restart a CFC cycle,
378      !!       Or if out of P_cfc range
379      IF (simu_type==1) THEN
380         iyear_tmp = nyear - nyear_res  !! JPALM -- in our spin-up, nyear_res is 1000
381         iyear_beg = MOD( iyear_tmp , 90 )
382         !!---------------------------------------
383         IF ((iyear_beg > 77) .OR. (iyear_beg==0)) THEN
384            qtr_cfc(:,:,:) = 0._wp
385            IF(lwp) THEN
386               WRITE(numout,*) 
387               WRITE(numout,*) 'restart a CFC cycle or out of P_cfc year bounds zero --'
388               WRITE(numout,*) '                          --    set qtr_CFC = 0.00   --'
389               WRITE(numout,*) '                          --   set qint_CFC = 0.00   --'
390               WRITE(numout,*) '                          --   set trn(CFC) = 0.00   --'
391            ENDIF
392            qtr_cfc(:,:,:) = 0._wp
393            qint_cfc(:,:,:) = 0._wp
394            trn(:,:,:,jp_cfc0:jp_cfc1) = 0._wp
395            trb(:,:,:,jp_cfc0:jp_cfc1) = 0._wp
396         ENDIF
397      !!
398      !! 2 -- Hindcast/proj
399      ELSEIF (simu_type==2) THEN
400         iyear_beg = MOD(nyear, 100)
401         IF (iyear_beg < 20)  iyear_beg = iyear_beg + 100
402         IF ((iyear_beg < 30) .OR. (iyear_beg > 115)) THEN
403            qtr_cfc(:,:,:) = 0._wp
404            IF(lwp) THEN
405               WRITE(numout,*)
406               WRITE(numout,*) 'restart a CFC cycle or out of P_cfc year bounds zero --'
407               WRITE(numout,*) '                          --    set qtr_CFC = 0.00   --'
408               WRITE(numout,*) '                          --   set qint_CFC = 0.00   --'
409               WRITE(numout,*) '                          --   set trn(CFC) = 0.00   --'
410            ENDIF
411            qtr_cfc(:,:,:) = 0._wp
412            qint_cfc(:,:,:) = 0._wp
413            trn(:,:,:,jp_cfc0:jp_cfc1) = 0._wp
414            trb(:,:,:,jp_cfc0:jp_cfc1) = 0._wp
415         ENDIF
416      ENDIF
417
418      IF(lwp) WRITE(numout,*)
419      !
420      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
421   END SUBROUTINE cfc_init
422
423
424   INTEGER FUNCTION trc_sms_cfc_alloc()
425   INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
426   INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
427   REAL(KIND=jprb)               :: zhook_handle
428
429   CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_SMS_CFC_ALLOC'
430
431   IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
432
433      !!----------------------------------------------------------------------
434      !!                     ***  ROUTINE trc_sms_cfc_alloc  ***
435      !!----------------------------------------------------------------------
436      ALLOCATE( xphem   (jpi,jpj)        ,     &
437         &      qtr_cfc (jpi,jpj,jp_cfc) ,     &
438         &      qint_cfc(jpi,jpj,jp_cfc) , STAT=trc_sms_cfc_alloc )
439         !
440      IF( trc_sms_cfc_alloc /= 0 ) CALL ctl_warn('trc_sms_cfc_alloc : failed to allocate arrays.')
441      !
442   IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
443   END FUNCTION trc_sms_cfc_alloc
444
445#else
446   !!----------------------------------------------------------------------
447   !!   Dummy module                                         No CFC tracers
448   !!----------------------------------------------------------------------
449CONTAINS
450   SUBROUTINE trc_sms_cfc( kt )       ! Empty routine
451   INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
452   INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
453   REAL(KIND=jprb)               :: zhook_handle
454
455   CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_SMS_CFC'
456
457   IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
458
459      WRITE(*,*) 'trc_sms_cfc: You should not have seen this print! error?', kt
460   IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
461   END SUBROUTINE trc_sms_cfc
462#endif
463
464   !!======================================================================
465END MODULE trcsms_cfc
Note: See TracBrowser for help on using the repository browser.