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 8075 for branches/NERC – NEMO

Changeset 8075 for branches/NERC


Ignore:
Timestamp:
2017-05-25T18:58:42+02:00 (7 years ago)
Author:
jpalmier
Message:

JPALM -- update CFCs - add SF6 and update gas transfert param

Location:
branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/CFC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/CFC/par_cfc.F90

    r6164 r8075  
    55   !!====================================================================== 
    66   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec)  revised architecture 
     7   !!                  !  2017-04  (A. Yool)  add SF6 
    78   !!---------------------------------------------------------------------- 
    89   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    2021   USE par_medusa , ONLY : jp_medusa_trd   !: number of biological diag in MEDUSA 
    2122 
    22    USE par_idtra  , ONLY : jp_idtra        !: number of tracers in MEDUSA 
    23    USE par_idtra  , ONLY : jp_idtra_2d     !: number of tracers in MEDUSA 
    24    USE par_idtra  , ONLY : jp_idtra_3d     !: number of tracers in MEDUSA 
    25    USE par_idtra  , ONLY : jp_idtra_trd    !: number of tracers in MEDUSA 
     23   USE par_idtra  , ONLY : jp_idtra        !: number of tracers in ideal tracer 
     24   USE par_idtra  , ONLY : jp_idtra_2d     !: number of tracers in ideal tracer 
     25   USE par_idtra  , ONLY : jp_idtra_3d     !: number of tracers in ideal tracer 
     26   USE par_idtra  , ONLY : jp_idtra_trd    !: number of tracers in ideal tracer 
    2627 
    2728   IMPLICIT NONE 
     
    4142   !!--------------------------------------------------------------------- 
    4243   LOGICAL, PUBLIC, PARAMETER ::   lk_cfc     = .TRUE.      !: CFC flag  
    43    INTEGER, PUBLIC, PARAMETER ::   jp_cfc     =  1          !: number of passive tracers 
    44    INTEGER, PUBLIC, PARAMETER ::   jp_cfc_2d  =  2          !: additional 2d output arrays ('key_trc_diaadd') 
     44   INTEGER, PUBLIC, PARAMETER ::   jp_cfc     =  3          !: number of passive tracers 
     45   INTEGER, PUBLIC, PARAMETER ::   jp_cfc_2d  =  6          !: additional 2d output arrays ('key_trc_diaadd') 
    4546   INTEGER, PUBLIC, PARAMETER ::   jp_cfc_3d  =  0          !: additional 3d output arrays ('key_trc_diaadd') 
    4647   INTEGER, PUBLIC, PARAMETER ::   jp_cfc_trd =  0          !: number of sms trends for CFC 
     
    4849   ! assign an index in trc arrays for each CFC prognostic variables 
    4950   INTEGER, PUBLIC, PARAMETER ::   jpc11       = jp_lc + 1   !: CFC-11  
    50    INTEGER, PUBLIC, PARAMETER ::   jpc12       = jp_lc + 2   !: CFC-12    
     51   INTEGER, PUBLIC, PARAMETER ::   jpc12       = jp_lc + 2   !: CFC-12 (priority tracer for CMIP6) 
     52   INTEGER, PUBLIC, PARAMETER ::   jpsf6       = jp_lc + 3   !: SF6 
    5153#else 
    5254   !!--------------------------------------------------------------------- 
     
    6163 
    6264   ! Starting/ending CFC do-loop indices (N.B. no CFC : jp_cfc0 > jp_cfc1 the do-loop are never done) 
    63    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0     = jp_lc + 1       !: First index of CFC tracers 
    64    INTEGER, PUBLIC, PARAMETER ::   jp_cfc1     = jp_lc + jp_cfc  !: Last  index of CFC tracers 
    65    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_2d  = jp_lc_2d  + 1       !: First index of CFC tracers 
     65   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0     = jp_lc + 1              !: First index of CFC tracers 
     66   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1     = jp_lc + jp_cfc         !: Last  index of CFC tracers 
     67   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_2d  = jp_lc_2d  + 1          !: First index of CFC tracers 
    6668   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_2d  = jp_lc_2d  + jp_cfc_2d  !: Last  index of CFC tracers 
    67    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_3d  = jp_lc_3d  + 1       !: First index of CFC tracers 
     69   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_3d  = jp_lc_3d  + 1          !: First index of CFC tracers 
    6870   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_3d  = jp_lc_3d  + jp_cfc_3d  !: Last  index of CFC tracers 
    69    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_trd = jp_lc_trd + 1       !: First index of CFC tracers 
    70    INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_trd = jp_lc_trd + jp_cfc_trd  !: Last  index of CFC tracers 
     71   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_trd = jp_lc_trd + 1          !: First index of CFC tracers 
     72   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_trd = jp_lc_trd + jp_cfc_trd !: Last  index of CFC tracers 
    7173 
    7274   !!====================================================================== 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/CFC/trcini_cfc.F90

    r5735 r8075  
    55   !!====================================================================== 
    66   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec)  
     7   !!                  !  2017-04  (A. Yool)  Add SF6 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_cfc 
     
    2223   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module 
    2324 
    24    CHARACTER (len=34) ::   clname = 'cfc1112.atm'   ! ??? 
     25   CHARACTER (len=34) ::   clname = 'cfc1112sf6.atm'   ! ??? 
    2526 
    2627   INTEGER  ::   inum                   ! unit number 
     
    4445      !!---------------------------------------------------------------------- 
    4546      INTEGER  ::  ji, jj, jn, jl, jm, js, io, ierr 
    46       INTEGER  ::  iskip = 6   ! number of 1st descriptor lines 
     47      INTEGER  ::  iskip = 7   ! number of 1st descriptor lines 
    4748      REAL(wp) ::  zyy, zyd 
    4849      !!---------------------------------------------------------------------- 
     
    5354 
    5455 
    55       IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm' 
     56      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112sf6.atm' 
    5657       
    5758      CALL ctl_opn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     
    105106      jn = 31 
    106107      DO  
    107         READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2) 
     108        READ(inum,*, IOSTAT=io) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), & 
     109             & p_cfc(jn,1,3), p_cfc(jn,2,1) & 
     110             & p_cfc(jn,2,2), p_cfc(jn,2,3) 
    108111        IF( io < 0 ) exit 
    109112        jn = jn + 1 
    110113      END DO 
    111114 
    112       p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years 
    113       p_cfc(33,1:2,1) = 8.e-4 
    114       p_cfc(34,1:2,1) = 1.e-6 
    115       p_cfc(35,1:2,1) = 2.e-3 
    116       p_cfc(36,1:2,1) = 4.e-3 
    117       p_cfc(37,1:2,1) = 6.e-3 
    118       p_cfc(38,1:2,1) = 8.e-3 
    119       p_cfc(39,1:2,1) = 1.e-2 
     115      ! AXY (25/04/17): do not adjust 
     116      ! p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years 
     117      ! p_cfc(33,1:2,1) = 8.e-4 
     118      ! p_cfc(34,1:2,1) = 1.e-6 
     119      ! p_cfc(35,1:2,1) = 2.e-3 
     120      ! p_cfc(36,1:2,1) = 4.e-3 
     121      ! p_cfc(37,1:2,1) = 6.e-3 
     122      ! p_cfc(38,1:2,1) = 8.e-3 
     123      ! p_cfc(39,1:2,1) = 1.e-2 
    120124       
    121125      IF(lwp) THEN        ! Control print 
    122126         WRITE(numout,*) 
    123          WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS ' 
     127         WRITE(numout,*) ' Year   p11HN    p11HS    p12HN    p12HS    pSF6N    pSF6S ' 
    124128         DO jn = 30, jpyear 
    125             WRITE(numout, '( 1I4, 4F9.2)') jn, p_cfc(jn,1,1), p_cfc(jn,2,1), p_cfc(jn,1,2), p_cfc(jn,2,2) 
     129            WRITE(numout, '( 1I4, 6F9.2)') jn, p_cfc(jn,1,1), p_cfc(jn,2,1), & 
     130                 & p_cfc(jn,1,2), p_cfc(jn,2,2) & 
     131                 & p_cfc(jn,1,3), p_cfc(jn,2,3) 
    126132         END DO 
    127133      ENDIF 
    128  
    129134 
    130135      ! Interpolation factor of atmospheric partial pressure 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/CFC/trcsms_cfc.F90

    r6719 r8075  
    77   !!  NEMO      1.0  !  2004-03  (C. Ethe) free form + modularity 
    88   !!            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 
    911   !!---------------------------------------------------------------------- 
    1012#if defined key_cfc 
     
    4345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   patm     ! atmospheric function 
    4446 
    45    REAL(wp), DIMENSION(4,2) ::   soa   ! coefficient for solubility of CFC [mol/l/atm] 
    46    REAL(wp), DIMENSION(3,2) ::   sob   !    "               " 
    47    REAL(wp), DIMENSION(4,2) ::   sca   ! coefficients for schmidt number in degre Celcius 
     47   REAL(wp), DIMENSION(4,3) ::   soa   ! coefficient for solubility of CFC [mol/l/atm] 
     48   REAL(wp), DIMENSION(3,3) ::   sob   !    "               " 
     49   REAL(wp), DIMENSION(5,3) ::   sca   ! coefficients for schmidt number in degre Celcius 
    4850       
    4951   !                          ! coefficients for conversion 
     
    8587      INTEGER  ::   im1, im2, ierr 
    8688      REAL(wp) ::   ztap, zdtap         
    87       REAL(wp) ::   zt1, zt2, zt3, zv2 
     89      REAL(wp) ::   zt1, zt2, zt3, zt4, zv2 
    8890      REAL(wp) ::   zsol      ! solubility 
    8991      REAL(wp) ::   zsch      ! schmidt number  
     
    106108      ! Temporal interpolation 
    107109      ! ---------------------- 
    108       !! JPALM -- 15-06-2016 -- define 2 kind of CFC run. 
    109       !!                     we want to make cycle experiments,  
    110       !!                     to periodically compare the ocean dynamic within 
    111       !!                     1- the SPIN-UP and 2- Hincast/Projections 
     110      !! JPALM -- 15-06-2016 -- define 2 kinds of CFC run: 
     111      !!                     1- the SPIN-UP and 2- Hindcast/Projections 
    112112      !!                     -- main difference is the way to define the year of 
    113113      !!                     simulation, that determine the atm pCFC. 
    114114      !!                     1-- Spin-up: our atm forcing is of 30y we cycle on. 
    115115      !!                     So we do 90y CFC cycles to be in good 
    116       !!                     correspondance with the atmosphere 
     116      !!                     correspondence with the atmosphere 
    117117      !!                     2-- Hindcast/proj, instead of nyear-1900 we keep 
    118118      !!                     the 2 last digit, and enable 3 cycle from 1800 to 2100.   
    119119      !!---------------------------------------------------------------------- 
    120       !! 1 -- SPIN-UP 
    121120      IF (simu_type==1) THEN 
     121         !! 1 -- SPIN-UP 
    122122         iyear_tmp = nyear - nyear_res  !! JPALM -- in our spin-up, nyear_res is 1000 
    123123         iyear_beg = MOD( iyear_tmp , 90 ) 
     
    133133            iyear_beg = iyear_beg + 30 
    134134         ENDIF 
    135       !! 
    136       !! 2 -- Hindcast/proj 
    137135      ELSEIF (simu_type==2) THEN 
     136         !! 2 -- Hindcast/proj 
    138137         iyear_beg = MOD(nyear, 100) 
    139138         IF (iyear_beg < 9)  iyear_beg = iyear_beg + 100 
     
    191190               zt2  = zt1 * zt1  
    192191               zt3  = zt1 * zt2 
    193                zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 
     192               zt4  = zt1 * zt3 
     193               zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 + sca(5,jl) * zt4 
    194194 
    195195               !    speed transfert : formulae of wanninkhof 1992 
    196196               zv2     = wndm(ji,jj) * wndm(ji,jj) 
    197197               zsch    = zsch / 660. 
    198                zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
     198               ! AXY (25/04/17): OMIP protocol specifies lower Wanninkhof (2014) value 
     199               ! zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
     200               zak_cfc = ( 0.251 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
    199201 
    200202               ! Input function  : speed *( conc. at equil - concen at surface ) 
     
    226228               elseif (jl.EQ.2) then 
    227229                   WRITE(NUMOUT,*) 'Traceur = CFC12: ' 
     230               elseif (jl.EQ.3) then 
     231                   WRITE(NUMOUT,*) 'Traceur = SF6: ' 
    228232               endif 
    229233             WRITE(NUMOUT,*) 'nyear    = ', nyear 
     
    256260         CALL iom_put( "qtrCFC11"  , qtr_cfc (:,:,1) ) 
    257261         CALL iom_put( "qintCFC11" , qint_cfc(:,:,1) ) 
     262         CALL iom_put( "qtrCFC12"  , qtr_cfc (:,:,2) ) 
     263         CALL iom_put( "qintCFC12" , qint_cfc(:,:,2) ) 
     264         CALL iom_put( "qtrSF6"    , qtr_cfc (:,:,3) ) 
     265         CALL iom_put( "qintSF6"   , qint_cfc(:,:,4) ) 
    258266      ELSE 
    259267         IF( ln_diatrc ) THEN 
    260268            trc2d(:,:,jp_cfc0_2d    ) = qtr_cfc (:,:,1) 
    261269            trc2d(:,:,jp_cfc0_2d + 1) = qint_cfc(:,:,1) 
     270            trc2d(:,:,jp_cfc0_2d + 2) = qtr_cfc (:,:,2) 
     271            trc2d(:,:,jp_cfc0_2d + 3) = qint_cfc(:,:,2) 
     272            trc2d(:,:,jp_cfc0_2d + 4) = qtr_cfc (:,:,3) 
     273            trc2d(:,:,jp_cfc0_2d + 5) = qint_cfc(:,:,4) 
    262274         END IF 
    263275      END IF 
     
    293305      soa(2,1) =  319.6552 
    294306      soa(3,1) =  119.4471 
    295       soa(4,1) =  -1.39165 
    296  
    297       sob(1,1) =  -0.142382 
    298       sob(2,1) =   0.091459 
    299       sob(3,1) =  -0.0157274 
    300  
    301       ! Schmidt number  
    302       sca(1,1) = 3501.8 
    303       sca(2,1) = -210.31 
    304       sca(3,1) =  6.1851 
    305       sca(4,1) = -0.07513 
     307      soa(4,1) =   -1.39165 
     308 
     309      sob(1,1) = -0.142382 
     310      sob(2,1) =  0.091459 
     311      sob(3,1) = -0.0157274 
     312 
     313      ! Schmidt number          AXY (25/04/17) 
     314      sca(1,1) = 3579.2       ! = 3501.8 
     315      sca(2,1) = -222.63      ! = -210.31 
     316      sca(3,1) =    7.5749    ! =    6.1851 
     317      sca(4,1) =   -0.14595   ! =   -0.07513 
     318      sca(5,1) =    0.0011874 ! = absent 
    306319 
    307320      ! coefficient for CFC12  
     
    312325      soa(2,2) =  298.9702 
    313326      soa(3,2) =  113.8049 
    314       soa(4,2) =  -1.39165 
    315  
    316       sob(1,2) =  -0.143566 
    317       sob(2,2) =   0.091015 
    318       sob(3,2) =  -0.0153924 
    319  
    320       ! schmidt number  
    321       sca(1,2) =  3845.4  
    322       sca(2,2) =  -228.95 
    323       sca(3,2) =  6.1908  
    324       sca(4,2) =  -0.067430 
     327      soa(4,2) =   -1.39165 
     328 
     329      sob(1,2) = -0.143566 
     330      sob(2,2) =  0.091015 
     331      sob(3,2) = -0.0153924 
     332 
     333      ! schmidt number         AXY (25/04/17) 
     334      sca(1,2) = 3828.1      ! = 3845.4  
     335      sca(2,2) = -249.86     ! = -228.95 
     336      sca(3,2) =    8.7603   ! =    6.1908  
     337      sca(4,2) =   -0.1716   ! =   -0.067430 
     338      sca(5,2) =    0.001408 ! = absent 
     339 
     340      ! coefficients for SF6   AXY (25/04/17) 
     341      !--------------------- 
     342       
     343      ! Solubility 
     344      soa(1,3) =  -80.0343 
     345      soa(2,3) =  117.232 
     346      soa(3,3) =   29.5817 
     347      soa(4,3) =    0.0 
     348 
     349      sob(1,3) =  0.0335183 
     350      sob(2,3) = -0.0373942 
     351      sob(3,3) =  0.00774862 
     352 
     353      ! Schmidt number 
     354      sca(1,3) = 3177.5 
     355      sca(2,3) = -200.57 
     356      sca(3,3) =    6.8865 
     357      sca(4,3) =   -0.13335 
     358      sca(5,3) =    0.0010877 
    325359 
    326360      !!--------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.