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 12377 for NEMO/trunk/src/TOP/CFC – NEMO

Ignore:
Timestamp:
2020-02-12T15:39:06+01:00 (4 years ago)
Author:
acc
Message:

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

Location:
NEMO/trunk
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
  • NEMO/trunk/src/TOP/CFC/trcini_cfc.F90

    r10068 r12377  
    2424   REAL(wp) ::   ylatn =  10.           ! 10 degrees north 
    2525 
     26   !! * Substitutions 
     27#  include "do_loop_substitute.h90" 
    2628   !!---------------------------------------------------------------------- 
    2729   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
     
    3133CONTAINS 
    3234 
    33    SUBROUTINE trc_ini_cfc 
     35   SUBROUTINE trc_ini_cfc( Kmm ) 
    3436      !!---------------------------------------------------------------------- 
    3537      !!                     ***  trc_ini_cfc  ***   
     
    3941      !! ** Method  : - Read the namcfc namelist and check the parameter values 
    4042      !!---------------------------------------------------------------------- 
     43      INTEGER, INTENT(in)  ::  Kmm  ! time level indices 
    4144      INTEGER  ::  ji, jj, jn, jl, jm, js, io, ierr 
    42       INTEGER  ::  iskip = 6   ! number of 1st descriptor lines 
     45      INTEGER  ::  iskip = 6        ! number of 1st descriptor lines 
    4346      REAL(wp) ::  zyy, zyd 
    4447      CHARACTER(len = 20)  ::  cltra 
     
    9093         DO jl = 1, jp_cfc 
    9194            jn = jp_cfc0 + jl - 1 
    92             trn(:,:,:,jn) = 0._wp 
     95            tr(:,:,:,jn,Kmm) = 0._wp 
    9396         END DO 
    9497      ENDIF 
     
    129132      !--------------------------------------------------------------------------------------- 
    130133      zyd = ylatn - ylats       
    131       DO jj = 1 , jpj 
    132          DO ji = 1 , jpi 
    133             IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0 
    134             ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0 
    135             ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd 
    136             ENDIF 
    137          END DO 
    138       END DO 
     134      DO_2D_11_11 
     135         IF(     gphit(ji,jj) >= ylatn ) THEN   ;   xphem(ji,jj) = 1.e0 
     136         ELSEIF( gphit(ji,jj) <= ylats ) THEN   ;   xphem(ji,jj) = 0.e0 
     137         ELSE                                   ;   xphem(ji,jj) = ( gphit(ji,jj) - ylats) / zyd 
     138         ENDIF 
     139      END_2D 
    139140      ! 
    140141      IF(lwp) WRITE(numout,*) 'Initialization of CFC tracers done' 
  • NEMO/trunk/src/TOP/CFC/trcnam_cfc.F90

    r11536 r12377  
    5151      ENDIF 
    5252      ! 
    53       REWIND( numtrc_ref )              ! Namelist namcfcdate in reference namelist : CFC parameters 
    5453      READ  ( numtrc_ref, namcfc, IOSTAT = ios, ERR = 901) 
    5554901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfc in reference namelist' ) 
    56       REWIND( numtrc_cfg )              ! Namelist namcfcdate in configuration namelist : CFC parameters 
    5755      READ  ( numtrc_cfg, namcfc, IOSTAT = ios, ERR = 902 ) 
    5856902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfc in configuration namelist' ) 
  • NEMO/trunk/src/TOP/CFC/trcsms_cfc.F90

    r12300 r12377  
    4747   REAL(wp) ::   xconv4 = 1.0e-12      ! conversion from mol/m3/atm to mol/m3/pptv  
    4848 
     49   !! * Substitutions 
     50#  include "do_loop_substitute.h90" 
    4951   !!---------------------------------------------------------------------- 
    5052   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
     
    5456CONTAINS 
    5557 
    56    SUBROUTINE trc_sms_cfc( kt ) 
     58   SUBROUTINE trc_sms_cfc( kt, Kbb, Kmm, Krhs ) 
    5759      !!---------------------------------------------------------------------- 
    5860      !!                     ***  ROUTINE trc_sms_cfc  *** 
     
    7072      !!                CFC concentration in pico-mol/m3 
    7173      !!---------------------------------------------------------------------- 
    72       INTEGER, INTENT(in) ::   kt    ! ocean time-step index 
     74      INTEGER, INTENT(in) ::   kt               ! ocean time-step index 
     75      INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs   ! ocean time level 
    7376      ! 
    7477      INTEGER  ::   ji, jj, jn, jl, jm 
     
    122125          
    123126         !                                                         !------------! 
    124          DO jj = 1, jpj                                            !  i-j loop  ! 
    125             DO ji = 1, jpi                                         !------------! 
     127         DO_2D_11_11 
    126128  
    127                ! space interpolation 
    128                zpp_cfc  =       xphem(ji,jj)   * zpatm(1,jl)   & 
    129                   &     + ( 1.- xphem(ji,jj) ) * zpatm(2,jl) 
    130  
    131                ! Computation of concentration at equilibrium : in picomol/l 
    132                ! coefficient for solubility for CFC-11/12 in  mol/l/atm 
    133                IF( tmask(ji,jj,1) .GE. 0.5 ) THEN 
    134                   ztap  = ( tsn(ji,jj,1,jp_tem) + 273.16 ) * 0.01 
    135                   zdtap = sob(1,jl) + ztap * ( sob(2,jl) + ztap * sob(3,jl) )  
    136                   zsol  =  EXP( soa(1,jl) + soa(2,jl) / ztap + soa(3,jl) * LOG( ztap )   & 
    137                      &                    + soa(4,jl) * ztap * ztap + tsn(ji,jj,1,jp_sal) * zdtap )  
    138                ELSE 
    139                   zsol  = 0.e0 
    140                ENDIF 
    141                ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv     
    142                zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1)   
    143                ! concentration at equilibrium 
    144                zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1)              
    145    
    146                ! Computation of speed transfert 
    147                !    Schmidt number revised in Wanninkhof (2014) 
    148                zt1  = tsn(ji,jj,1,jp_tem) 
    149                zt2  = zt1 * zt1  
    150                zt3  = zt1 * zt2 
    151                zt4  = zt2 * zt2 
    152                zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 + sca(5,jl) * zt4 
    153  
    154                !    speed transfert : formulae revised in Wanninkhof (2014) 
    155                zv2     = wndm(ji,jj) * wndm(ji,jj) 
    156                zsch    = zsch / 660. 
    157                zak_cfc = ( 0.251 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
    158  
    159                ! Input function  : speed *( conc. at equil - concen at surface ) 
    160                ! trn in pico-mol/l idem qtr; ak in en m/a 
    161                qtr_cfc(ji,jj,jl) = -zak_cfc * ( trb(ji,jj,1,jn) - zca_cfc )   & 
    162                   &                         * tmask(ji,jj,1) * ( 1. - fr_i(ji,jj) ) 
    163                ! Add the surface flux to the trend 
    164                tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr_cfc(ji,jj,jl) / e3t_n(ji,jj,1)  
    165  
    166                ! cumulation of surface flux at each time step 
    167                qint_cfc(ji,jj,jl) = qint_cfc(ji,jj,jl) + qtr_cfc(ji,jj,jl) * rdt 
    168                !                                               !----------------! 
    169             END DO                                             !  end i-j loop  ! 
    170          END DO                                                !----------------! 
     129            ! space interpolation 
     130            zpp_cfc  =       xphem(ji,jj)   * zpatm(1,jl)   & 
     131               &     + ( 1.- xphem(ji,jj) ) * zpatm(2,jl) 
     132 
     133            ! Computation of concentration at equilibrium : in picomol/l 
     134            ! coefficient for solubility for CFC-11/12 in  mol/l/atm 
     135            IF( tmask(ji,jj,1) .GE. 0.5 ) THEN 
     136               ztap  = ( ts(ji,jj,1,jp_tem,Kmm) + 273.16 ) * 0.01 
     137               zdtap = sob(1,jl) + ztap * ( sob(2,jl) + ztap * sob(3,jl) )  
     138               zsol  =  EXP( soa(1,jl) + soa(2,jl) / ztap + soa(3,jl) * LOG( ztap )   & 
     139                  &                    + soa(4,jl) * ztap * ztap + ts(ji,jj,1,jp_sal,Kmm) * zdtap )  
     140            ELSE 
     141               zsol  = 0.e0 
     142            ENDIF 
     143            ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv     
     144            zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1)   
     145            ! concentration at equilibrium 
     146            zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1)              
     147            ! Computation of speed transfert 
     148            !    Schmidt number revised in Wanninkhof (2014) 
     149            zt1  = ts(ji,jj,1,jp_tem,Kmm) 
     150            zt2  = zt1 * zt1  
     151            zt3  = zt1 * zt2 
     152            zt4  = zt2 * zt2 
     153            zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 + sca(5,jl) * zt4 
     154 
     155            !    speed transfert : formulae revised in Wanninkhof (2014) 
     156            zv2     = wndm(ji,jj) * wndm(ji,jj) 
     157            zsch    = zsch / 660. 
     158            zak_cfc = ( 0.251 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
     159 
     160            ! Input function  : speed *( conc. at equil - concen at surface ) 
     161            ! tr(:,:,:,:,Kmm) in pico-mol/l idem qtr; ak in en m/a 
     162            qtr_cfc(ji,jj,jl) = -zak_cfc * ( tr(ji,jj,1,jn,Kbb) - zca_cfc )   & 
     163               &                         * tmask(ji,jj,1) * ( 1. - fr_i(ji,jj) ) 
     164            ! Add the surface flux to the trend 
     165            tr(ji,jj,1,jn,Krhs) = tr(ji,jj,1,jn,Krhs) + qtr_cfc(ji,jj,jl) / e3t(ji,jj,1,Kmm)  
     166 
     167            ! cumulation of surface flux at each time step 
     168            qint_cfc(ji,jj,jl) = qint_cfc(ji,jj,jl) + qtr_cfc(ji,jj,jl) * rdt 
     169            !                                               !----------------! 
     170         END_2D 
    171171         !                                                  !----------------! 
    172172      END DO                                                !  end CFC loop  ! 
     
    195195      IF( l_trdtrc ) THEN 
    196196          DO jn = jp_cfc0, jp_cfc1 
    197             CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt )   ! save trends 
     197            CALL trd_trc( tr(:,:,:,jn,Krhs), jn, jptra_sms, kt, Kmm )   ! save trends 
    198198          END DO 
    199199      END IF 
  • NEMO/trunk/src/TOP/CFC/trcwri_cfc.F90

    r10069 r12377  
    2020CONTAINS 
    2121 
    22    SUBROUTINE trc_wri_cfc 
     22   SUBROUTINE trc_wri_cfc( Kmm ) 
    2323      !!--------------------------------------------------------------------- 
    2424      !!                     ***  ROUTINE trc_wri_trc  *** 
     
    2626      !! ** Purpose :   output passive tracers fields  
    2727      !!--------------------------------------------------------------------- 
     28      INTEGER, INTENT(in)  :: Kmm   ! time level indices 
    2829      CHARACTER (len=20)   :: cltra 
    2930      INTEGER              :: jn 
     
    3435      DO jn = jp_cfc0, jp_cfc1 
    3536         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer 
    36          CALL iom_put( cltra, trn(:,:,:,jn) ) 
     37         CALL iom_put( cltra, tr(:,:,:,jn,Kmm) ) 
    3738      END DO 
    3839      ! 
Note: See TracChangeset for help on using the changeset viewer.