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 11954 for NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src – NEMO

Ignore:
Timestamp:
2019-11-22T17:15:18+01:00 (4 years ago)
Author:
acc
Message:

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Merge in trunk changes up to 11943 in preparation for end of year merge

Location:
NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src
Files:
1 deleted
14 edited
2 copied

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/ice.F90

    r11536 r11954  
    328328   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sz_i     !: ice salinity          [PSS] 
    329329 
    330    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip       !: melt pond fraction per grid cell area 
     330   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip       !: melt pond concentration 
    331331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_ip       !: melt pond volume per grid cell area      [m] 
    332    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip_frac  !: melt pond volume per ice area 
    333    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_ip       !: melt pond thickness                      [m] 
    334  
    335    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   at_ip      !: total melt pond fraction 
     332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip_frac  !: melt pond fraction (a_ip/a_i) 
     333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_ip       !: melt pond depth                          [m] 
     334 
     335   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   at_ip      !: total melt pond concentration 
    336336   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hm_ip      !: mean melt pond depth                     [m] 
    337    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vt_ip      !: total melt pond volume per unit area    [m] 
     337   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vt_ip      !: total melt pond volume per gridcell area [m] 
    338338 
    339339   !!---------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/icedyn_adv_pra.F90

    r11612 r11954  
    1616   !!   adv_pra_rst     : read/write Prather field in ice restart file, or initialized to zero 
    1717   !!---------------------------------------------------------------------- 
     18   USE phycst         ! physical constant 
    1819   USE dom_oce        ! ocean domain 
    1920   USE ice            ! sea-ice variables 
     
    3637   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxice, syice, sxxice, syyice, sxyice   ! ice thickness  
    3738   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsn , sysn , sxxsn , syysn , sxysn    ! snow thickness 
    38    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxa  , sya  , sxxa  , syya  , sxya     ! lead fraction 
     39   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxa  , sya  , sxxa  , syya  , sxya     ! ice concentration 
    3940   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsal, sysal, sxxsal, syysal, sxysal   ! ice salinity 
    4041   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxage, syage, sxxage, syyage, sxyage   ! ice age 
    41    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxopw, syopw, sxxopw, syyopw, sxyopw   ! open water in sea ice 
    4242   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxc0 , syc0 , sxxc0 , syyc0 , sxyc0    ! snow layers heat content 
    4343   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxe  , sye  , sxxe  , syye  , sxye     ! ice layers heat content 
     
    8181      REAL(wp), DIMENSION(:,:,:,:), INTENT(inout) ::   pe_i       ! ice heat content 
    8282      ! 
    83       INTEGER  ::   jk, jl, jt              ! dummy loop indices 
     83      INTEGER  ::   ji,jj, jk, jl, jt       ! dummy loop indices 
    8484      INTEGER  ::   icycle                  ! number of sub-timestep for the advection 
    8585      REAL(wp) ::   zdt                     !   -      - 
    8686      REAL(wp), DIMENSION(1)                  ::   zcflprv, zcflnow   ! for global communication 
     87      REAL(wp), DIMENSION(jpi,jpj)            ::   zati1, zati2 
     88      REAL(wp), DIMENSION(jpi,jpj)            ::   zudy, zvdx 
    8789      REAL(wp), DIMENSION(jpi,jpj,jpl)        ::   zarea 
    88       REAL(wp), DIMENSION(jpi,jpj,1)          ::   z0opw 
    8990      REAL(wp), DIMENSION(jpi,jpj,jpl)        ::   z0ice, z0snw, z0ai, z0smi, z0oi 
    9091      REAL(wp), DIMENSION(jpi,jpj,jpl)        ::   z0ap , z0vp 
     
    109110      zdt = rdt_ice / REAL(icycle) 
    110111       
    111       !------------------------- 
    112       ! transported fields                                         
    113       !------------------------- 
    114       z0opw(:,:,1) = pato_i(:,:) * e1e2t(:,:)              ! Open water area  
    115       DO jl = 1, jpl 
    116          zarea(:,:,jl) = e1e2t(:,:) 
    117          z0snw(:,:,jl) = pv_s (:,:,jl) * e1e2t(:,:)        ! Snow volume 
    118          z0ice(:,:,jl) = pv_i (:,:,jl) * e1e2t(:,:)        ! Ice  volume 
    119          z0ai (:,:,jl) = pa_i (:,:,jl) * e1e2t(:,:)        ! Ice area 
    120          z0smi(:,:,jl) = psv_i(:,:,jl) * e1e2t(:,:)        ! Salt content 
    121          z0oi (:,:,jl) = poa_i(:,:,jl) * e1e2t(:,:)        ! Age content 
    122          DO jk = 1, nlay_s 
    123             z0es(:,:,jk,jl) = pe_s(:,:,jk,jl) * e1e2t(:,:) ! Snow heat content 
    124          END DO 
    125          DO jk = 1, nlay_i 
    126             z0ei(:,:,jk,jl) = pe_i(:,:,jk,jl) * e1e2t(:,:) ! Ice  heat content 
    127          END DO 
    128          IF ( ln_pnd_H12 ) THEN 
    129             z0ap(:,:,jl)  = pa_ip(:,:,jl) * e1e2t(:,:)     ! Melt pond fraction 
    130             z0vp(:,:,jl)  = pv_ip(:,:,jl) * e1e2t(:,:)     ! Melt pond volume 
    131          ENDIF 
    132       END DO 
    133  
    134       !                                                    !--------------------------------------------! 
    135       IF( MOD( ( kt - 1) / nn_fsbc , 2 ) == 0 ) THEN       !==  odd ice time step:  adv_x then adv_y  ==! 
    136          !                                                 !--------------------------------------------! 
    137          DO jt = 1, icycle 
    138             CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0opw , sxopw , sxxopw , syopw , syyopw , sxyopw ) !--- open water 
    139             CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0opw , sxopw , sxxopw , syopw , syyopw , sxyopw ) 
    140             CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) !--- ice volume 
    141             CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) 
    142             CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) !--- snow volume 
    143             CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) 
    144             CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) !--- ice salinity 
    145             CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) 
    146             CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) !--- ice concentration 
    147             CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) 
    148             CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) !--- ice age 
    149             CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) 
     112      ! --- transport --- ! 
     113      zudy(:,:) = pu_ice(:,:) * e2u(:,:) 
     114      zvdx(:,:) = pv_ice(:,:) * e1v(:,:) 
     115 
     116      DO jt = 1, icycle 
     117 
     118         ! record at_i before advection (for open water) 
     119         zati1(:,:) = SUM( pa_i(:,:,:), dim=3 ) 
     120          
     121         ! --- transported fields --- !                                         
     122         DO jl = 1, jpl 
     123            zarea(:,:,jl) = e1e2t(:,:) 
     124            z0snw(:,:,jl) = pv_s (:,:,jl) * e1e2t(:,:)        ! Snow volume 
     125            z0ice(:,:,jl) = pv_i (:,:,jl) * e1e2t(:,:)        ! Ice  volume 
     126            z0ai (:,:,jl) = pa_i (:,:,jl) * e1e2t(:,:)        ! Ice area 
     127            z0smi(:,:,jl) = psv_i(:,:,jl) * e1e2t(:,:)        ! Salt content 
     128            z0oi (:,:,jl) = poa_i(:,:,jl) * e1e2t(:,:)        ! Age content 
     129            DO jk = 1, nlay_s 
     130               z0es(:,:,jk,jl) = pe_s(:,:,jk,jl) * e1e2t(:,:) ! Snow heat content 
     131            END DO 
     132            DO jk = 1, nlay_i 
     133               z0ei(:,:,jk,jl) = pe_i(:,:,jk,jl) * e1e2t(:,:) ! Ice  heat content 
     134            END DO 
     135            IF ( ln_pnd_H12 ) THEN 
     136               z0ap(:,:,jl)  = pa_ip(:,:,jl) * e1e2t(:,:)     ! Melt pond fraction 
     137               z0vp(:,:,jl)  = pv_ip(:,:,jl) * e1e2t(:,:)     ! Melt pond volume 
     138            ENDIF 
     139         END DO 
     140         ! 
     141         !                                                                  !--------------------------------------------! 
     142         IF( MOD( (kt - 1) / nn_fsbc , 2 ) ==  MOD( (jt - 1) , 2 ) ) THEN   !==  odd ice time step:  adv_x then adv_y  ==! 
     143            !                                                               !--------------------------------------------! 
     144            CALL adv_x( zdt , zudy , 1._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) !--- ice volume 
     145            CALL adv_y( zdt , zvdx , 0._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) 
     146            CALL adv_x( zdt , zudy , 1._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) !--- snow volume 
     147            CALL adv_y( zdt , zvdx , 0._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) 
     148            CALL adv_x( zdt , zudy , 1._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) !--- ice salinity 
     149            CALL adv_y( zdt , zvdx , 0._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) 
     150            CALL adv_x( zdt , zudy , 1._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) !--- ice concentration 
     151            CALL adv_y( zdt , zvdx , 0._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) 
     152            CALL adv_x( zdt , zudy , 1._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) !--- ice age 
     153            CALL adv_y( zdt , zvdx , 0._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) 
    150154            ! 
    151             DO jk = 1, nlay_s                                                                             !--- snow heat content 
    152                CALL adv_x( zdt, pu_ice, 1._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
    153                   &                                   sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
    154                CALL adv_y( zdt, pv_ice, 0._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
    155                   &                                   sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
    156             END DO 
    157             DO jk = 1, nlay_i                                                                             !--- ice heat content 
    158                CALL adv_x( zdt, pu_ice, 1._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
    159                   &                                   sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
    160                CALL adv_y( zdt, pv_ice, 0._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
    161                   &                                   sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
     155            DO jk = 1, nlay_s                                                                           !--- snow heat content 
     156               CALL adv_x( zdt, zudy, 1._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
     157                  &                                 sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
     158               CALL adv_y( zdt, zvdx, 0._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
     159                  &                                 sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
     160            END DO 
     161            DO jk = 1, nlay_i                                                                           !--- ice heat content 
     162               CALL adv_x( zdt, zudy, 1._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
     163                  &                                 sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
     164               CALL adv_y( zdt, zvdx, 0._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
     165                  &                                 sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
    162166            END DO 
    163167            ! 
    164168            IF ( ln_pnd_H12 ) THEN 
    165                CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap )    !--- melt pond fraction 
    166                CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap )  
    167                CALL adv_x( zdt , pu_ice , 1._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp )    !--- melt pond volume 
    168                CALL adv_y( zdt , pv_ice , 0._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp )  
     169               CALL adv_x( zdt , zudy , 1._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap )    !--- melt pond fraction 
     170               CALL adv_y( zdt , zvdx , 0._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap )  
     171               CALL adv_x( zdt , zudy , 1._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp )    !--- melt pond volume 
     172               CALL adv_y( zdt , zvdx , 0._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp )  
    169173            ENDIF 
    170          END DO 
    171       !                                                    !--------------------------------------------! 
    172       ELSE                                                 !== even ice time step:  adv_y then adv_x  ==! 
    173          !                                                 !--------------------------------------------! 
    174          DO jt = 1, icycle 
    175             CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0opw , sxopw , sxxopw , syopw , syyopw , sxyopw ) !--- open water 
    176             CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0opw , sxopw , sxxopw , syopw , syyopw , sxyopw ) 
    177             CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) !--- ice volume 
    178             CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) 
    179             CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) !--- snow volume 
    180             CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) 
    181             CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) !--- ice salinity 
    182             CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) 
    183             CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) !--- ice concentration 
    184             CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) 
    185             CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) !--- ice age 
    186             CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) 
    187             DO jk = 1, nlay_s                                                                             !--- snow heat content 
    188                CALL adv_y( zdt, pv_ice, 1._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
    189                   &                                   sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
    190                CALL adv_x( zdt, pu_ice, 0._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
    191                   &                                   sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
    192             END DO 
    193             DO jk = 1, nlay_i                                                                             !--- ice heat content 
    194                CALL adv_y( zdt, pv_ice, 1._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
    195                   &                                   sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
    196                CALL adv_x( zdt, pu_ice, 0._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
    197                   &                                   sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
     174            !                                                               !--------------------------------------------! 
     175         ELSE                                                               !== even ice time step:  adv_y then adv_x  ==! 
     176            !                                                               !--------------------------------------------! 
     177            CALL adv_y( zdt , zvdx , 1._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) !--- ice volume 
     178            CALL adv_x( zdt , zudy , 0._wp , zarea , z0ice , sxice , sxxice , syice , syyice , sxyice ) 
     179            CALL adv_y( zdt , zvdx , 1._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) !--- snow volume 
     180            CALL adv_x( zdt , zudy , 0._wp , zarea , z0snw , sxsn  , sxxsn  , sysn  , syysn  , sxysn  ) 
     181            CALL adv_y( zdt , zvdx , 1._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) !--- ice salinity 
     182            CALL adv_x( zdt , zudy , 0._wp , zarea , z0smi , sxsal , sxxsal , sysal , syysal , sxysal ) 
     183            CALL adv_y( zdt , zvdx , 1._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) !--- ice concentration 
     184            CALL adv_x( zdt , zudy , 0._wp , zarea , z0ai  , sxa   , sxxa   , sya   , syya   , sxya   ) 
     185            CALL adv_y( zdt , zvdx , 1._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) !--- ice age 
     186            CALL adv_x( zdt , zudy , 0._wp , zarea , z0oi  , sxage , sxxage , syage , syyage , sxyage ) 
     187            DO jk = 1, nlay_s                                                                           !--- snow heat content 
     188               CALL adv_y( zdt, zvdx, 1._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
     189                  &                                 sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
     190               CALL adv_x( zdt, zudy, 0._wp, zarea, z0es (:,:,jk,:), sxc0(:,:,jk,:),   & 
     191                  &                                 sxxc0(:,:,jk,:), syc0(:,:,jk,:), syyc0(:,:,jk,:), sxyc0(:,:,jk,:) ) 
     192            END DO 
     193            DO jk = 1, nlay_i                                                                           !--- ice heat content 
     194               CALL adv_y( zdt, zvdx, 1._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
     195                  &                                 sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
     196               CALL adv_x( zdt, zudy, 0._wp, zarea, z0ei(:,:,jk,:), sxe(:,:,jk,:),   &  
     197                  &                                 sxxe(:,:,jk,:), sye(:,:,jk,:), syye(:,:,jk,:), sxye(:,:,jk,:) ) 
    198198            END DO 
    199199            IF ( ln_pnd_H12 ) THEN 
    200                CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap )    !--- melt pond fraction 
    201                CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap ) 
    202                CALL adv_y( zdt , pv_ice , 1._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp )    !--- melt pond volume 
    203                CALL adv_x( zdt , pu_ice , 0._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp ) 
     200               CALL adv_y( zdt , zvdx , 1._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap )    !--- melt pond fraction 
     201               CALL adv_x( zdt , zudy , 0._wp , zarea , z0ap , sxap , sxxap , syap , syyap , sxyap ) 
     202               CALL adv_y( zdt , zvdx , 1._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp )    !--- melt pond volume 
     203               CALL adv_x( zdt , zudy , 0._wp , zarea , z0vp , sxvp , sxxvp , syvp , syyvp , sxyvp ) 
    204204            ENDIF 
    205          END DO 
    206       ENDIF 
    207  
    208       !------------------------------------------- 
    209       ! Recover the properties from their contents 
    210       !------------------------------------------- 
    211       pato_i(:,:) = z0opw(:,:,1) * r1_e1e2t(:,:) * tmask(:,:,1) 
    212       DO jl = 1, jpl 
    213          pv_i (:,:,jl) = z0ice(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    214          pv_s (:,:,jl) = z0snw(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    215          psv_i(:,:,jl) = z0smi(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    216          poa_i(:,:,jl) = z0oi (:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    217          pa_i (:,:,jl) = z0ai (:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    218          DO jk = 1, nlay_s 
    219             pe_s(:,:,jk,jl) = z0es(:,:,jk,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    220          END DO 
    221          DO jk = 1, nlay_i 
    222             pe_i(:,:,jk,jl) = z0ei(:,:,jk,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    223          END DO 
    224          IF ( ln_pnd_H12 ) THEN 
    225             pa_ip(:,:,jl) = z0ap(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
    226             pv_ip(:,:,jl) = z0vp(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     205            ! 
    227206         ENDIF 
     207 
     208         ! --- Recover the properties from their contents --- ! 
     209         DO jl = 1, jpl 
     210            pv_i (:,:,jl) = z0ice(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     211            pv_s (:,:,jl) = z0snw(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     212            psv_i(:,:,jl) = z0smi(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     213            poa_i(:,:,jl) = z0oi (:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     214            pa_i (:,:,jl) = z0ai (:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     215            DO jk = 1, nlay_s 
     216               pe_s(:,:,jk,jl) = z0es(:,:,jk,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     217            END DO 
     218            DO jk = 1, nlay_i 
     219               pe_i(:,:,jk,jl) = z0ei(:,:,jk,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     220            END DO 
     221            IF ( ln_pnd_H12 ) THEN 
     222               pa_ip(:,:,jl) = z0ap(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     223               pv_ip(:,:,jl) = z0vp(:,:,jl) * r1_e1e2t(:,:) * tmask(:,:,1) 
     224            ENDIF 
     225         END DO 
     226         ! 
     227         ! derive open water from ice concentration 
     228         zati2(:,:) = SUM( pa_i(:,:,:), dim=3 ) 
     229         DO jj = 2, jpjm1 
     230            DO ji = fs_2, fs_jpim1 
     231               pato_i(ji,jj) = pato_i(ji,jj) - ( zati2(ji,jj) - zati1(ji,jj) ) &                        !--- open water 
     232                  &                          - ( zudy(ji,jj) - zudy(ji-1,jj) + zvdx(ji,jj) - zvdx(ji,jj-1) ) * r1_e1e2t(ji,jj) * zdt 
     233            END DO 
     234         END DO 
     235         CALL lbc_lnk( 'icedyn_adv_pra', pato_i, 'T',  1. ) 
     236         ! 
     237         ! --- Ensure non-negative fields --- ! 
     238         !     Remove negative values (conservation is ensured) 
     239         !     (because advected fields are not perfectly bounded and tiny negative values can occur, e.g. -1.e-20) 
     240         CALL ice_var_zapneg( zdt, pato_i, pv_i, pv_s, psv_i, poa_i, pa_i, pa_ip, pv_ip, pe_s, pe_i ) 
     241         ! 
     242         ! --- Ensure snow load is not too big --- ! 
     243         CALL Hsnow( zdt, pv_i, pv_s, pa_i, pa_ip, pe_s ) 
     244         ! 
    228245      END DO 
    229       ! 
    230       ! --- Ensure non-negative fields --- ! 
    231       ! Remove negative values (conservation is ensured) 
    232       !    (because advected fields are not perfectly bounded and tiny negative values can occur, e.g. -1.e-20) 
    233       CALL ice_var_zapneg( zdt, pato_i, pv_i, pv_s, psv_i, poa_i, pa_i, pa_ip, pv_ip, pe_s, pe_i ) 
    234246      ! 
    235247      IF( lrst_ice )   CALL adv_pra_rst( 'WRITE', kt )   !* write Prather fields in the restart file 
     
    293305            DO ji = 1, jpi 
    294306               zbet(ji,jj)  =  MAX( 0._wp, SIGN( 1._wp, put(ji,jj) ) ) 
    295                zalf         =  MAX( 0._wp, put(ji,jj) ) * pdt * e2u(ji,jj) / psm(ji,jj,jl) 
     307               zalf         =  MAX( 0._wp, put(ji,jj) ) * pdt / psm(ji,jj,jl) 
    296308               zalfq        =  zalf * zalf 
    297309               zalf1        =  1.0 - zalf 
     
    319331         DO jj = 2, jpjm1                      !  Flux from i+1 to i when u LT 0. 
    320332            DO ji = 1, fs_jpim1 
    321                zalf          = MAX( 0._wp, -put(ji,jj) ) * pdt * e2u(ji,jj) / psm(ji+1,jj,jl)  
     333               zalf          = MAX( 0._wp, -put(ji,jj) ) * pdt / psm(ji+1,jj,jl)  
    322334               zalg  (ji,jj) = zalf 
    323335               zalfq         = zalf * zalf 
     
    462474            DO ji = fs_2, fs_jpim1 
    463475               zbet(ji,jj)  =  MAX( 0._wp, SIGN( 1._wp, pvt(ji,jj) ) ) 
    464                zalf         =  MAX( 0._wp, pvt(ji,jj) ) * pdt * e1v(ji,jj) / psm(ji,jj,jl) 
     476               zalf         =  MAX( 0._wp, pvt(ji,jj) ) * pdt / psm(ji,jj,jl) 
    465477               zalfq        =  zalf * zalf 
    466478               zalf1        =  1.0 - zalf 
     
    488500         DO jj = 1, jpjm1                   !  Flux from j+1 to j when v LT 0. 
    489501            DO ji = fs_2, fs_jpim1 
    490                zalf          = ( MAX(0._wp, -pvt(ji,jj) ) * pdt * e1v(ji,jj) ) / psm(ji,jj+1,jl)  
     502               zalf          = MAX( 0._wp, -pvt(ji,jj) ) * pdt / psm(ji,jj+1,jl)  
    491503               zalg  (ji,jj) = zalf 
    492504               zalfq         = zalf * zalf 
     
    578590 
    579591 
     592   SUBROUTINE Hsnow( pdt, pv_i, pv_s, pa_i, pa_ip, pe_s ) 
     593      !!------------------------------------------------------------------- 
     594      !!                  ***  ROUTINE Hsnow  *** 
     595      !! 
     596      !! ** Purpose : 1- Check snow load after advection 
     597      !!              2- Correct pond concentration to avoid a_ip > a_i 
     598      !! 
     599      !! ** Method :  If snow load makes snow-ice interface to deplet below the ocean surface 
     600      !!              then put the snow excess in the ocean 
     601      !! 
     602      !! ** Notes :   This correction is crucial because of the call to routine icecor afterwards 
     603      !!              which imposes a mini of ice thick. (rn_himin). This imposed mini can artificially 
     604      !!              make the snow very thick (if concentration decreases drastically) 
     605      !!              This behavior has been seen in Ultimate-Macho and supposedly it can also be true for Prather 
     606      !!------------------------------------------------------------------- 
     607      REAL(wp)                    , INTENT(in   ) ::   pdt   ! tracer time-step 
     608      REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pv_i, pv_s, pa_i, pa_ip 
     609      REAL(wp), DIMENSION(:,:,:,:), INTENT(inout) ::   pe_s 
     610      ! 
     611      INTEGER  ::   ji, jj, jl   ! dummy loop indices 
     612      REAL(wp) ::   z1_dt, zvs_excess, zfra 
     613      !!------------------------------------------------------------------- 
     614      ! 
     615      z1_dt = 1._wp / pdt 
     616      ! 
     617      ! -- check snow load -- ! 
     618      DO jl = 1, jpl 
     619         DO jj = 1, jpj 
     620            DO ji = 1, jpi 
     621               IF ( pv_i(ji,jj,jl) > 0._wp ) THEN 
     622                  ! 
     623                  zvs_excess = MAX( 0._wp, pv_s(ji,jj,jl) - pv_i(ji,jj,jl) * (rau0-rhoi) * r1_rhos ) 
     624                  ! 
     625                  IF( zvs_excess > 0._wp ) THEN   ! snow-ice interface deplets below the ocean surface 
     626                     ! put snow excess in the ocean 
     627                     zfra = ( pv_s(ji,jj,jl) - zvs_excess ) / MAX( pv_s(ji,jj,jl), epsi20 ) 
     628                     wfx_res(ji,jj) = wfx_res(ji,jj) + zvs_excess * rhos * z1_dt 
     629                     hfx_res(ji,jj) = hfx_res(ji,jj) - SUM( pe_s(ji,jj,1:nlay_s,jl) ) * ( 1._wp - zfra ) * z1_dt ! W.m-2 <0 
     630                     ! correct snow volume and heat content 
     631                     pe_s(ji,jj,1:nlay_s,jl) = pe_s(ji,jj,1:nlay_s,jl) * zfra 
     632                     pv_s(ji,jj,jl)          = pv_s(ji,jj,jl) - zvs_excess 
     633                  ENDIF 
     634                  ! 
     635               ENDIF 
     636            END DO 
     637         END DO 
     638      END DO 
     639      ! 
     640      !-- correct pond concentration to avoid a_ip > a_i -- ! 
     641      WHERE( pa_ip(:,:,:) > pa_i(:,:,:) )   pa_ip(:,:,:) = pa_i(:,:,:) 
     642      ! 
     643   END SUBROUTINE Hsnow 
     644 
     645 
    580646   SUBROUTINE adv_pra_init 
    581647      !!------------------------------------------------------------------- 
     
    588654      ! 
    589655      !                             !* allocate prather fields 
    590       ALLOCATE( sxopw(jpi,jpj,1)   , syopw(jpi,jpj,1)   , sxxopw(jpi,jpj,1)   , syyopw(jpi,jpj,1)   , sxyopw(jpi,jpj,1)   ,   & 
    591          &      sxice(jpi,jpj,jpl) , syice(jpi,jpj,jpl) , sxxice(jpi,jpj,jpl) , syyice(jpi,jpj,jpl) , sxyice(jpi,jpj,jpl) ,   & 
     656      ALLOCATE( sxice(jpi,jpj,jpl) , syice(jpi,jpj,jpl) , sxxice(jpi,jpj,jpl) , syyice(jpi,jpj,jpl) , sxyice(jpi,jpj,jpl) ,   & 
    592657         &      sxsn (jpi,jpj,jpl) , sysn (jpi,jpj,jpl) , sxxsn (jpi,jpj,jpl) , syysn (jpi,jpj,jpl) , sxysn (jpi,jpj,jpl) ,   & 
    593658         &      sxa  (jpi,jpj,jpl) , sya  (jpi,jpj,jpl) , sxxa  (jpi,jpj,jpl) , syya  (jpi,jpj,jpl) , sxya  (jpi,jpj,jpl) ,   & 
     
    635700         !                                   !==========================! 
    636701         ! 
    637          IF( ln_rstart ) THEN   ;   id1 = iom_varid( numrir, 'sxopw' , ldstop = .FALSE. )    ! file exist: id1>0 
     702         IF( ln_rstart ) THEN   ;   id1 = iom_varid( numrir, 'sxice' , ldstop = .FALSE. )    ! file exist: id1>0 
    638703         ELSE                   ;   id1 = 0                                                  ! no restart: id1=0 
    639704         ENDIF 
     
    653718            CALL iom_get( numrir, jpdom_autoglo, 'syysn' , syysn  ) 
    654719            CALL iom_get( numrir, jpdom_autoglo, 'sxysn' , sxysn  ) 
    655             !                                                        ! lead fraction 
     720            !                                                        ! ice concentration 
    656721            CALL iom_get( numrir, jpdom_autoglo, 'sxa'   , sxa    ) 
    657722            CALL iom_get( numrir, jpdom_autoglo, 'sya'   , sya    ) 
     
    671736            CALL iom_get( numrir, jpdom_autoglo, 'syyage', syyage ) 
    672737            CALL iom_get( numrir, jpdom_autoglo, 'sxyage', sxyage ) 
    673             !                                                        ! open water in sea ice 
    674             CALL iom_get( numrir, jpdom_autoglo, 'sxopw' , sxopw  ) 
    675             CALL iom_get( numrir, jpdom_autoglo, 'syopw' , syopw  ) 
    676             CALL iom_get( numrir, jpdom_autoglo, 'sxxopw', sxxopw ) 
    677             CALL iom_get( numrir, jpdom_autoglo, 'syyopw', syyopw ) 
    678             CALL iom_get( numrir, jpdom_autoglo, 'sxyopw', sxyopw ) 
    679738            !                                                        ! snow layers heat content 
    680739            DO jk = 1, nlay_s 
     
    716775            sxice = 0._wp   ;   syice = 0._wp   ;   sxxice = 0._wp   ;   syyice = 0._wp   ;   sxyice = 0._wp      ! ice thickness 
    717776            sxsn  = 0._wp   ;   sysn  = 0._wp   ;   sxxsn  = 0._wp   ;   syysn  = 0._wp   ;   sxysn  = 0._wp      ! snow thickness 
    718             sxa   = 0._wp   ;   sya   = 0._wp   ;   sxxa   = 0._wp   ;   syya   = 0._wp   ;   sxya   = 0._wp      ! lead fraction 
     777            sxa   = 0._wp   ;   sya   = 0._wp   ;   sxxa   = 0._wp   ;   syya   = 0._wp   ;   sxya   = 0._wp      ! ice concentration 
    719778            sxsal = 0._wp   ;   sysal = 0._wp   ;   sxxsal = 0._wp   ;   syysal = 0._wp   ;   sxysal = 0._wp      ! ice salinity 
    720779            sxage = 0._wp   ;   syage = 0._wp   ;   sxxage = 0._wp   ;   syyage = 0._wp   ;   sxyage = 0._wp      ! ice age 
    721             sxopw = 0._wp   ;   syopw = 0._wp   ;   sxxopw = 0._wp   ;   syyopw = 0._wp   ;   sxyopw = 0._wp      ! open water in sea ice 
    722780            sxc0  = 0._wp   ;   syc0  = 0._wp   ;   sxxc0  = 0._wp   ;   syyc0  = 0._wp   ;   sxyc0  = 0._wp      ! snow layers heat content 
    723781            sxe   = 0._wp   ;   sye   = 0._wp   ;   sxxe   = 0._wp   ;   syye   = 0._wp   ;   sxye   = 0._wp      ! ice layers heat content 
     
    750808         CALL iom_rstput( iter, nitrst, numriw, 'syysn' , syysn  ) 
    751809         CALL iom_rstput( iter, nitrst, numriw, 'sxysn' , sxysn  ) 
    752          !                                                           ! lead fraction 
     810         !                                                           ! ice concentration 
    753811         CALL iom_rstput( iter, nitrst, numriw, 'sxa'   , sxa    ) 
    754812         CALL iom_rstput( iter, nitrst, numriw, 'sya'   , sya    ) 
     
    768826         CALL iom_rstput( iter, nitrst, numriw, 'syyage', syyage ) 
    769827         CALL iom_rstput( iter, nitrst, numriw, 'sxyage', sxyage ) 
    770          !                                                           ! open water in sea ice 
    771          CALL iom_rstput( iter, nitrst, numriw, 'sxopw' , sxopw  ) 
    772          CALL iom_rstput( iter, nitrst, numriw, 'syopw' , syopw  ) 
    773          CALL iom_rstput( iter, nitrst, numriw, 'sxxopw', sxxopw ) 
    774          CALL iom_rstput( iter, nitrst, numriw, 'syyopw', syyopw ) 
    775          CALL iom_rstput( iter, nitrst, numriw, 'sxyopw', sxyopw ) 
    776828         !                                                           ! snow layers heat content 
    777829         DO jk = 1, nlay_s 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/icedyn_adv_umx.F90

    r11612 r11954  
    8383      REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   poa_i      ! age content 
    8484      REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pa_i       ! ice concentration 
    85       REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pa_ip      ! melt pond fraction 
     85      REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pa_ip      ! melt pond concentration 
    8686      REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pv_ip      ! melt pond volume 
    8787      REAL(wp), DIMENSION(:,:,:,:), INTENT(inout) ::   pe_s       ! snw heat content 
     
    325325         !== melt ponds ==! 
    326326         IF ( ln_pnd_H12 ) THEN 
    327             ! fraction 
     327            ! concentration 
    328328            zamsk = 1._wp 
    329329            CALL adv_umx( zamsk, kn_umx, jt, kt, zdt, zudy , zvdx , zu_cat , zv_cat , zcu_box, zcv_box, & 
     
    15271527      !!              3- check whether snow load deplets the snow-ice interface below sea level$ 
    15281528      !!                 and reduce it by sending the excess in the ocean 
    1529       !!              4- correct pond fraction to avoid a_ip > a_i 
     1529      !!              4- correct pond concentration to avoid a_ip > a_i 
    15301530      !! 
    15311531      !! ** input   : Max thickness of the surrounding 9-points 
     
    15971597         END DO 
    15981598      END DO  
    1599       !                                           !-- correct pond fraction to avoid a_ip > a_i 
     1599      !                                           !-- correct pond concentration to avoid a_ip > a_i 
    16001600      WHERE( pa_ip(:,:,:) > pa_i(:,:,:) )   pa_ip(:,:,:) = pa_i(:,:,:) 
    16011601      ! 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/icedyn_rdgrft.F90

    r11671 r11954  
    8686      !!                ***  ROUTINE ice_dyn_rdgrft_alloc *** 
    8787      !!------------------------------------------------------------------- 
    88       ALLOCATE( closing_net(jpij), opning(jpij)   , closing_gross(jpij),   & 
    89          &      apartf(jpij,0:jpl), hrmin(jpij,jpl), hraft(jpij,jpl)    , aridge(jpij,jpl),  & 
    90          &      hrmax(jpij,jpl), hi_hrdg(jpij,jpl)  , araft (jpij,jpl),  & 
     88      ALLOCATE( closing_net(jpij)  , opning(jpij)      , closing_gross(jpij) ,               & 
     89         &      apartf(jpij,0:jpl) , hrmin  (jpij,jpl) , hraft(jpij,jpl) , aridge(jpij,jpl), & 
     90         &      hrmax (jpij,jpl)   , hi_hrdg(jpij,jpl) , araft(jpij,jpl) ,                   & 
    9191         &      ze_i_2d(jpij,nlay_i,jpl), ze_s_2d(jpij,nlay_s,jpl), STAT=ice_dyn_rdgrft_alloc ) 
    9292 
     
    137137      REAL(wp) ::   zfac                       ! local scalar 
    138138      INTEGER , DIMENSION(jpij) ::   iptidx        ! compute ridge/raft or not 
    139       REAL(wp), DIMENSION(jpij) ::   zdivu_adv     ! divu as implied by transport scheme  (1/s) 
    140139      REAL(wp), DIMENSION(jpij) ::   zdivu, zdelt  ! 1D divu_i & delta_i 
    141140      ! 
     
    175174         
    176175         ! just needed here 
    177          CALL tab_2d_1d( npti, nptidx(1:npti), zdivu   (1:npti)      , divu_i  ) 
    178176         CALL tab_2d_1d( npti, nptidx(1:npti), zdelt   (1:npti)      , delta_i ) 
    179177         ! needed here and in the iteration loop 
     178         CALL tab_2d_1d( npti, nptidx(1:npti), zdivu   (1:npti)      , divu_i) ! zdivu is used as a work array here (no change in divu_i) 
    180179         CALL tab_3d_2d( npti, nptidx(1:npti), a_i_2d  (1:npti,1:jpl), a_i   ) 
    181180         CALL tab_3d_2d( npti, nptidx(1:npti), v_i_2d  (1:npti,1:jpl), v_i   ) 
     
    187186            closing_net(ji) = rn_csrdg * 0.5_wp * ( zdelt(ji) - ABS( zdivu(ji) ) ) - MIN( zdivu(ji), 0._wp ) 
    188187            ! 
    189             ! divergence given by the advection scheme 
    190             !   (which may not be equal to divu as computed from the velocity field) 
    191             IF    ( ln_adv_Pra ) THEN 
    192                zdivu_adv(ji) = ( 1._wp - ato_i_1d(ji) - SUM( a_i_2d(ji,:) ) ) * r1_rdtice 
    193             ELSEIF( ln_adv_UMx ) THEN 
    194                zdivu_adv(ji) = zdivu(ji) 
    195             ENDIF 
    196             ! 
    197             IF( zdivu_adv(ji) < 0._wp )   closing_net(ji) = MAX( closing_net(ji), -zdivu_adv(ji) )   ! make sure the closing rate is large enough 
    198             !                                                                                        ! to give asum = 1.0 after ridging 
     188            IF( zdivu(ji) < 0._wp )   closing_net(ji) = MAX( closing_net(ji), -zdivu(ji) )   ! make sure the closing rate is large enough 
     189            !                                                                                ! to give asum = 1.0 after ridging 
    199190            ! Opening rate (non-negative) that will give asum = 1.0 after ridging. 
    200             opning(ji) = closing_net(ji) + zdivu_adv(ji) 
     191            opning(ji) = closing_net(ji) + zdivu(ji) 
    201192         END DO 
    202193         ! 
     
    215206               ato_i_1d   (ipti)   = ato_i_1d   (ji) 
    216207               closing_net(ipti)   = closing_net(ji) 
    217                zdivu_adv  (ipti)   = zdivu_adv  (ji) 
     208               zdivu      (ipti)   = zdivu      (ji) 
    218209               opning     (ipti)   = opning     (ji) 
    219210            ENDIF 
     
    259250               ELSE 
    260251                  iterate_ridging  = 1 
    261                   zdivu_adv  (ji) = zfac * r1_rdtice 
    262                   closing_net(ji) = MAX( 0._wp, -zdivu_adv(ji) ) 
    263                   opning     (ji) = MAX( 0._wp,  zdivu_adv(ji) ) 
     252                  zdivu      (ji) = zfac * r1_rdtice 
     253                  closing_net(ji) = MAX( 0._wp, -zdivu(ji) ) 
     254                  opning     (ji) = MAX( 0._wp,  zdivu(ji) ) 
    264255               ENDIF 
    265256            END DO 
     
    309300 
    310301      !                       ! Ice thickness needed for rafting 
    311       WHERE( pa_i(1:npti,:) > epsi20 )   ;   zhi(1:npti,:) = pv_i(1:npti,:) / pa_i(1:npti,:) 
     302      WHERE( pa_i(1:npti,:) > epsi10 )   ;   zhi(1:npti,:) = pv_i(1:npti,:) / pa_i(1:npti,:) 
    312303      ELSEWHERE                          ;   zhi(1:npti,:) = 0._wp 
    313304      END WHERE 
     
    328319      zasum(1:npti) = pato_i(1:npti) + SUM( pa_i(1:npti,:), dim=2 ) 
    329320      ! 
    330       WHERE( zasum(1:npti) > epsi20 )   ;   z1_asum(1:npti) = 1._wp / zasum(1:npti) 
     321      WHERE( zasum(1:npti) > epsi10 )   ;   z1_asum(1:npti) = 1._wp / zasum(1:npti) 
    331322      ELSEWHERE                         ;   z1_asum(1:npti) = 0._wp 
    332323      END WHERE 
     
    454445      ! Based on the ITD of ridging and ridged ice, convert the net closing rate to a gross closing rate.   
    455446      ! NOTE: 0 < aksum <= 1 
    456       WHERE( zaksum(1:npti) > epsi20 )   ;   closing_gross(1:npti) = pclosing_net(1:npti) / zaksum(1:npti) 
     447      WHERE( zaksum(1:npti) > epsi10 )   ;   closing_gross(1:npti) = pclosing_net(1:npti) / zaksum(1:npti) 
    457448      ELSEWHERE                          ;   closing_gross(1:npti) = 0._wp 
    458449      END WHERE 
     
    537528            IF( apartf(ji,jl1) > 0._wp .AND. closing_gross(ji) > 0._wp ) THEN   ! only if ice is ridging 
    538529 
    539                IF( a_i_2d(ji,jl1) > epsi20 ) THEN   ;   z1_ai(ji) = 1._wp / a_i_2d(ji,jl1) 
     530               IF( a_i_2d(ji,jl1) > epsi10 ) THEN   ;   z1_ai(ji) = 1._wp / a_i_2d(ji,jl1) 
    540531               ELSE                                 ;   z1_ai(ji) = 0._wp 
    541532               ENDIF 
     
    595586               ! virtual salt flux to keep salinity constant 
    596587               IF( nn_icesal /= 2 )  THEN 
    597                   sirdg2(ji)     = sirdg2(ji)     - vsw * ( sss_1d(ji) - s_i_1d(ji) )        ! ridge salinity = s_i 
     588                  sirdg2(ji)     = sirdg2(ji)     - vsw * ( sss_1d(ji) - s_i_1d(ji) )       ! ridge salinity = s_i 
    598589                  sfx_bri_1d(ji) = sfx_bri_1d(ji) + sss_1d(ji) * vsw * rhoi * r1_rdtice  &  ! put back sss_m into the ocean 
    599590                     &                            - s_i_1d(ji) * vsw * rhoi * r1_rdtice     ! and get  s_i  from the ocean  
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/iceitd.F90

    r11671 r11954  
    211211               CALL itd_glinear( zhb0(1:npti)  , zhb1(1:npti)  , h_ib_1d(1:npti)  , a_i_1d(1:npti)  ,  &   ! in 
    212212                  &              g0  (1:npti,1), g1  (1:npti,1), hL     (1:npti,1), hR    (1:npti,1)   )   ! out 
    213                   ! 
     213               ! 
    214214               ! Area lost due to melting of thin ice 
    215215               DO ji = 1, npti 
     
    218218                     ! 
    219219                     zdh0 =  h_i_1d(ji) - h_ib_1d(ji)                 
    220                      IF( zdh0 < 0.0 ) THEN      !remove area from category 1 
     220                     IF( zdh0 < 0.0 ) THEN      ! remove area from category 1 
    221221                        zdh0 = MIN( -zdh0, hi_max(1) ) 
    222222                        !Integrate g(1) from 0 to dh0 to estimate area melted 
     
    226226                           zx1    = zetamax 
    227227                           zx2    = 0.5 * zetamax * zetamax  
    228                            zda0   = g1(ji,1) * zx2 + g0(ji,1) * zx1                        ! ice area removed 
     228                           zda0   = g1(ji,1) * zx2 + g0(ji,1) * zx1                ! ice area removed 
    229229                           zdamax = a_i_1d(ji) * (1.0 - h_i_1d(ji) / h_ib_1d(ji) ) ! Constrain new thickness <= h_i                 
    230                            zda0   = MIN( zda0, zdamax )                                                  ! ice area lost due to melting  
    231                            !     of thin ice (zdamax > 0) 
     230                           zda0   = MIN( zda0, zdamax )                            ! ice area lost due to melting of thin ice (zdamax > 0) 
    232231                           ! Remove area, conserving volume 
    233232                           h_i_1d(ji) = h_i_1d(ji) * a_i_1d(ji) / ( a_i_1d(ji) - zda0 ) 
     
    349348      DO ji = 1, npti 
    350349         ! 
    351          IF( paice(ji) > epsi10  .AND. phice(ji) > 0._wp )  THEN 
     350         IF( paice(ji) > epsi10  .AND. phice(ji) > epsi10 )  THEN 
    352351            ! 
    353352            ! Initialize hL and hR 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/ICE/icevar.F90

    r11560 r11954  
    622622                  pv_s   (ji,jj,jl) = 0._wp 
    623623               ENDIF 
    624                IF( psv_i(ji,jj,jl) < 0._wp .OR. pa_i(ji,jj,jl) <= 0._wp ) THEN 
     624               IF( psv_i(ji,jj,jl) < 0._wp .OR. pa_i(ji,jj,jl) <= 0._wp .OR. pv_i(ji,jj,jl) <= 0._wp ) THEN 
    625625                  sfx_res(ji,jj)    = sfx_res(ji,jj) + psv_i(ji,jj,jl) * rhoi * z1_dt 
    626626                  psv_i  (ji,jj,jl) = 0._wp 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/BDY/bdydta.F90

    r11642 r11954  
    461461               ELSE                                                            ;   ipl = 1            ! xy or xyt 
    462462               ENDIF 
     463               bf(jp_bdya_i,jbdy)%clrootname = 'NOT USED'   ! reset to default value as this subdomain may not need to read this bdy 
    463464            ENDIF 
    464465         ENDIF 
     
    629630            ENDIF 
    630631 
    631             IF( llneed ) THEN                                              ! dta_bdy(jbdy)%xxx will be needed 
     632            IF( llneed .AND. iszdim > 0 ) THEN                             ! dta_bdy(jbdy)%xxx will be needed 
    632633               !                                                           !   -> must be associated with an allocated target 
    633634               ALLOCATE( bf_alias(1)%fnow( iszdim, 1, ipk ) )              ! allocate the target 
     
    638639                  bf_alias(1)%imap    => idx_bdy(jbdy)%nbmap(1:iszdim,igrd)   ! associate the mapping used for this bdy 
    639640                  bf_alias(1)%igrd    = igrd                                  ! used only for vertical integration of 3D arrays 
     641                  bf_alias(1)%ibdy    = jbdy                                  !  "    "    "     "          "      "  "    "     
    640642                  bf_alias(1)%ltotvel = ln_full_vel                           ! T if u3d is full velocity 
    641643                  bf_alias(1)%lzint   = ln_zinterp                            ! T if it requires a vertical interpolation 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/CRS/README.rst

    r10279 r11954  
    22On line biogeochemistry coarsening 
    33********************************** 
     4 
     5.. todo:: 
     6 
     7 
    48 
    59.. contents:: 
     
    6367                              ! 1, MAX of KZ 
    6468                              ! 2, MIN of KZ 
    65                               ! 3, 10^(MEAN(LOG(KZ))  
    66                               ! 4, MEDIANE of KZ  
     69                              ! 3, 10^(MEAN(LOG(KZ)) 
     70                              ! 4, MEDIANE of KZ 
    6771      ln_crs_wn   = .false.   ! wn coarsened (T) or computed using horizontal divergence ( F ) 
    6872                              !                           ! 
     
    7377  the north-fold lateral boundary condition (ORCA025, ORCA12, ORCA36, ...). 
    7478- ``nn_msh_crs = 1`` will activate the generation of the coarsened grid meshmask. 
    75 - ``nn_crs_kz`` is the operator to coarsen the vertical mixing coefficient.  
     79- ``nn_crs_kz`` is the operator to coarsen the vertical mixing coefficient. 
    7680- ``ln_crs_wn`` 
    7781 
     
    8084  - when ``key_vvl`` is not activated, 
    8185 
    82     - coarsened vertical velocities are computed using horizontal divergence (``ln_crs_wn = .false.``)  
     86    - coarsened vertical velocities are computed using horizontal divergence (``ln_crs_wn = .false.``) 
    8387    - or coarsened vertical velocities are computed with an average operator (``ln_crs_wn = .true.``) 
    8488- ``ln_crs_top = .true.``: should be activated to run BCG model in coarsened space; 
     
    97101 
    98102In the [attachment:iodef.xml iodef.xml]  file, a "nemo" context is defined and 
    99 some variable defined in [attachment:file_def.xml file_def.xml] are writted on the ocean-dynamic grid.   
     103some variable defined in [attachment:file_def.xml file_def.xml] are writted on the ocean-dynamic grid. 
    100104To write variables on the coarsened grid, and in particular the passive tracers, 
    101105a "nemo_crs" context should be defined in [attachment:iodef.xml iodef.xml] and 
     
    111115  interpolated `on-the-fly <http://forge.ipsl.jussieu.fr/nemo/wiki/Users/SetupNewConfiguration/Weight-creator>`_. 
    112116  Example of namelist for PISCES : 
    113    
     117 
    114118   .. code-block:: fortran 
    115119 
     
    134138         rn_trfac(14)  =   1.0e-06  !  -      -      -     - 
    135139         rn_trfac(23)  =   7.6e-06  !  -      -      -     - 
    136        
     140 
    137141         cn_dir        =  './'      !  root directory for the location of the data files 
    138142 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/FLO/flodom.F90

    r11536 r11954  
    433433      IF( ABS(dlx) > 1.0_wp ) dlx = 1.0_wp 
    434434      ! 
    435       dld = ATAN(DSQRT( 1._wp * ( 1._wp-dlx )/( 1._wp+dlx ) )) * 222.24_wp / dls 
     435      dld = ATAN(SQRT( 1._wp * ( 1._wp-dlx )/( 1._wp+dlx ) )) * 222.24_wp / dls 
    436436      flo_dstnce = dld * 1000._wp 
    437437      ! 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/FLO/flowri.F90

    r11536 r11954  
    221221               clname=TRIM(clname)//".nc" 
    222222 
    223                CALL fliocrfd( clname , (/ 'ntraj' , 't' /), (/ jpnfl , -1  /) , numflo ) 
     223               CALL fliocrfd( clname , (/'ntraj' , '    t' /), (/ jpnfl , -1/) , numflo ) 
    224224    
    225225               CALL fliodefv( numflo, 'traj_lon'    , (/1,2/), v_t=flio_r8, long_name="Longitude"           , units="degrees_east"  ) 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/LBC/mppini.F90

    r11671 r11954  
    534534 9401    FORMAT('              '   ,20('   ',i3,'          ') ) 
    535535 9402    FORMAT('       ',i3,' *  ',20(i3,'  x',i3,'   *   ') ) 
    536  9404    FORMAT('           *  '   ,20('      ',i3,'   *   ') ) 
     536 9404    FORMAT('           *  '   ,20('     ' ,i4,'   *   ') ) 
    537537      ENDIF 
    538538          
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/LDF/ldfdyn.F90

    r11671 r11954  
    313313            DO jj = 1, jpj             ! Set local gridscale values 
    314314               DO ji = 1, jpi 
    315                   esqt(ji,jj) = ( e1e2t(ji,jj) / ( e1t(ji,jj) + e2t(ji,jj) ) )**2  
    316                   esqf(ji,jj) = ( e1e2f(ji,jj) / ( e1f(ji,jj) + e2f(ji,jj) ) )**2  
     315                  esqt(ji,jj) = ( 2._wp * e1e2t(ji,jj) / ( e1t(ji,jj) + e2t(ji,jj) ) )**2  
     316                  esqf(ji,jj) = ( 2._wp * e1e2f(ji,jj) / ( e1f(ji,jj) + e2f(ji,jj) ) )**2  
    317317               END DO 
    318318            END DO 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/README.rst

    r10549 r11954  
    33*************** 
    44 
     5.. todo:: 
     6 
     7 
     8 
    59.. contents:: 
    6    :local: 
    7  
    8 TOP (Tracers in the Ocean Paradigm) is the NEMO hardwired interface toward biogeochemical models and 
    9 provide the physical constraints/boundaries for oceanic tracers. 
    10 It consists of a modular framework to handle multiple ocean tracers, including also a variety of built-in modules. 
     10   :local: 
     11 
     12TOP (Tracers in the Ocean Paradigm) is the NEMO hardwired interface toward 
     13biogeochemical models and provide the physical constraints/boundaries for oceanic tracers. 
     14It consists of a modular framework to handle multiple ocean tracers, 
     15including also a variety of built-in modules. 
    1116 
    1217This component of the NEMO framework allows one to exploit available modules (see below) and 
    1318further develop a range of applications, spanning from the implementation of a dye passive tracer to 
    1419evaluate dispersion processes (by means of MY_TRC), track water masses age (AGE module), 
    15 assess the ocean interior penetration of persistent chemical compounds (e.g., gases like CFC or even PCBs), 
    16 up to the full set of equations involving marine biogeochemical cycles. 
     20assess the ocean interior penetration of persistent chemical compounds 
     21(e.g., gases like CFC or even PCBs), up to the full set of equations involving 
     22marine biogeochemical cycles. 
    1723 
    1824Structure 
    1925========= 
    2026 
    21 TOP interface has the following location in the source code ``./src/MBG/`` and 
     27TOP interface has the following location in the source code :file:`./src/TOP` and 
    2228the following modules are available: 
    2329 
    24 ``TRP`` 
    25    Interface to NEMO physical core for computing tracers transport 
    26  
    27 ``CFC`` 
    28    Inert carbon tracers (CFC11,CFC12,SF6) 
    29  
    30 ``C14`` 
    31    Radiocarbon passive tracer 
    32  
    33 ``AGE`` 
    34    Water age tracking 
    35  
    36 ``MY_TRC`` 
    37    Template for creation of new modules and external BGC models coupling 
    38  
    39 ``PISCES`` 
    40    Built in BGC model. 
    41    See [https://www.geosci-model-dev.net/8/2465/2015/gmd-8-2465-2015-discussion.html Aumont et al. (2015)] for 
    42    a throughout description. | 
    43  
    44 The usage of TOP is activated i) by including in the configuration definition  the component ``MBG`` and 
    45 ii) by adding the macro ``key_top`` in the configuration CPP file 
    46 (see for more details [http://forge.ipsl.jussieu.fr/nemo/wiki/Users "Learn more about the model"]). 
     30:file:`TRP` 
     31   Interface to NEMO physical core for computing tracers transport 
     32 
     33:file:`CFC` 
     34   Inert carbon tracers (CFC11,CFC12,SF6) 
     35 
     36:file:`C14` 
     37   Radiocarbon passive tracer 
     38 
     39:file:`AGE` 
     40   Water age tracking 
     41 
     42:file:`MY_TRC` 
     43   Template for creation of new modules and external BGC models coupling 
     44 
     45:file:`PISCES` 
     46   Built in BGC model. See :cite:`gmd-8-2465-2015` for a throughout description. 
     47 
     48The usage of TOP is activated 
     49*i)* by including in the configuration definition the component ``TOP`` and 
     50*ii)* by adding the macro ``key_top`` in the configuration CPP file 
     51(see for more details :forge:`"Learn more about the model" <wiki/Users>`). 
    4752 
    4853As an example, the user can refer to already available configurations in the code, 
     
    5156(see also Section 4) . 
    5257 
    53 Note that, since version 4.0, TOP interface core functionalities are activated by means of logical keys and 
     58Note that, since version 4.0, 
     59TOP interface core functionalities are activated by means of logical keys and 
    5460all submodules preprocessing macros from previous versions were removed. 
    5561 
     
    5763 
    5864``key_iomput`` 
    59    use XIOS I/O 
     65   use XIOS I/O 
    6066 
    6167``key_agrif`` 
    62    enable AGRIF coupling 
     68   enable AGRIF coupling 
    6369 
    6470``key_trdtrc`` & ``key_trdmxl_trc`` 
    65    trend computation for tracers 
     71   trend computation for tracers 
    6672 
    6773Synthetic Workflow 
    6874================== 
    6975 
    70 A synthetic description of the TOP interface workflow is given below to summarize the steps involved in 
    71 the computation of biogeochemical and physical trends and their time integration and outputs, 
     76A synthetic description of the TOP interface workflow is given below to 
     77summarize the steps involved in the computation of biogeochemical and physical trends and 
     78their time integration and outputs, 
    7279by reporting also the principal Fortran subroutine herein involved. 
    7380 
    74 **Model initialization (OPA_SRC/nemogcm.F90)** 
    75  
    76 call to trc_init (trcini.F90) 
    77  
    78   ↳ call trc_nam (trcnam.F90) to initialize TOP tracers and run setting 
    79  
    80   ↳ call trc_ini_sms, to initialize each submodule 
    81  
    82   ↳ call trc_ini_trp, to initialize transport for tracers 
    83  
    84   ↳ call trc_ice_ini, to initialize tracers in seaice 
    85  
    86   ↳ call trc_ini_state, read passive tracers from a restart or input data 
    87  
    88   ↳ call trc_sub_ini, setup substepping if {{{nn_dttrc /= 1}}} 
    89  
    90 **Time marching procedure (OPA_SRC/stp.F90)** 
    91  
    92 call to trc_stp.F90 (trcstp.F90) 
    93  
    94   ↳ call trc_sub_stp, averaging physical variables for sub-stepping 
    95  
    96   ↳ call trc_wri, call XIOS for output of data 
    97  
    98   ↳ call trc_sms, compute BGC trends for each submodule 
    99  
    100     ↳ call trc_sms_my_trc, includes also surface and coastal BCs trends 
    101  
    102   ↳ call trc_trp (TRP/trctrp.F90), compute physical trends 
    103  
    104     ↳ call trc_sbc, get trend due to surface concentration/dilution 
    105  
    106     ↳ call trc_adv, compute tracers advection 
    107  
    108     ↳ call to trc_ldf, compute tracers lateral diffusion 
    109  
    110     ↳ call to trc_zdf, vertical mixing and after tracer fields 
    111  
    112     ↳ call to trc_nxt, tracer fields at next time step. Lateral Boundary Conditions are solved in here. 
    113  
    114     ↳ call to trc_rad, Correct artificial negative concentrations 
    115  
    116   ↳ call trc_rst_wri, output tracers restart files 
     81Model initialization (:file:`./src/OCE/nemogcm.F90`) 
     82---------------------------------------------------- 
     83 
     84Call to ``trc_init`` subroutine (:file:`./src/TOP/trcini.F90`) to initialize TOP. 
     85 
     86.. literalinclude:: ../../../src/TOP/trcini.F90 
     87   :language:        fortran 
     88   :lines:           41-86 
     89   :emphasize-lines: 21,30-32,38-40 
     90   :caption:         ``trc_init`` subroutine 
     91 
     92Time marching procedure (:file:`./src/OCE/step.F90`) 
     93---------------------------------------------------- 
     94 
     95Call to ``trc_stp`` subroutine (:file:`./src/TOP/trcstp.F90`) to compute/update passive tracers. 
     96 
     97.. literalinclude:: ../../../src/TOP/trcstp.F90 
     98   :language:        fortran 
     99   :lines:           46-125 
     100   :emphasize-lines: 42,55-57 
     101   :caption:         ``trc_stp`` subroutine 
     102 
     103BGC trends computation for each submodule (:file:`./src/TOP/trcsms.F90`) 
     104------------------------------------------------------------------------ 
     105 
     106.. literalinclude:: ../../../src/TOP/trcsms.F90 
     107   :language:        fortran 
     108   :lines:           21 
     109   :caption:         :file:`trcsms` snippet 
     110 
     111Physical trends computation (:file:`./src/TOP/TRP/trctrp.F90`) 
     112-------------------------------------------------------------- 
     113 
     114.. literalinclude:: ../../../src/TOP/TRP/trctrp.F90 
     115   :language:        fortran 
     116   :lines:           46-95 
     117   :emphasize-lines: 17,21,29,33-35 
     118   :caption:         ``trc_trp`` subroutine 
    117119 
    118120Namelists walkthrough 
    119121===================== 
    120122 
    121 namelist_top 
    122 ------------ 
    123  
    124 Here below are listed the features/options of the TOP interface accessible through the namelist_top_ref and 
    125 modifiable by means of namelist_top_cfg (as for NEMO physical ones). 
    126  
    127 Note that ## is used to refer to a number in an array field. 
     123:file:`namelist_top` 
     124-------------------- 
     125 
     126Here below are listed the features/options of the TOP interface accessible through 
     127the :file:`namelist_top_ref` and modifiable by means of :file:`namelist_top_cfg` 
     128(as for NEMO physical ones). 
     129 
     130Note that ``##`` is used to refer to a number in an array field. 
    128131 
    129132.. literalinclude:: ../../namelists/namtrc_run 
     133   :language: fortran 
    130134 
    131135.. literalinclude:: ../../namelists/namtrc 
     136   :language: fortran 
    132137 
    133138.. literalinclude:: ../../namelists/namtrc_dta 
     139   :language: fortran 
    134140 
    135141.. literalinclude:: ../../namelists/namtrc_adv 
     142   :language: fortran 
    136143 
    137144.. literalinclude:: ../../namelists/namtrc_ldf 
     145   :language: fortran 
    138146 
    139147.. literalinclude:: ../../namelists/namtrc_rad 
     148   :language: fortran 
    140149 
    141150.. literalinclude:: ../../namelists/namtrc_snk 
     151   :language: fortran 
    142152 
    143153.. literalinclude:: ../../namelists/namtrc_dmp 
     154   :language: fortran 
    144155 
    145156.. literalinclude:: ../../namelists/namtrc_ice 
     157   :language: fortran 
    146158 
    147159.. literalinclude:: ../../namelists/namtrc_trd 
     160   :language: fortran 
    148161 
    149162.. literalinclude:: ../../namelists/namtrc_bc 
     163   :language: fortran 
    150164 
    151165.. literalinclude:: ../../namelists/namtrc_bdy 
     166   :language: fortran 
    152167 
    153168.. literalinclude:: ../../namelists/namage 
    154  
    155 Two main types of data structure are used within TOP interface to initialize tracer properties (1) and 
     169   :language: fortran 
     170 
     171Two main types of data structure are used within TOP interface 
     172to initialize tracer properties (1) and 
    156173to provide related initial and boundary conditions (2). 
    157174 
    158 **1. TOP tracers initialization**: sn_tracer (namtrc) 
     1751. TOP tracers initialization: ``sn_tracer`` (``&namtrc``) 
     176^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 
    159177 
    160178Beside providing name and metadata for tracers, 
    161 here are also defined the use of initial ({{{sn_tracer%llinit}}}) and 
    162 boundary ({{{sn_tracer%llsbc, sn_tracer%llcbc, sn_tracer%llobc}}}) conditions. 
    163  
    164 In the following, an example of the full structure definition is given for two idealized tracers both with 
    165 initial conditions given, while the first has only surface boundary forcing and 
     179here are also defined the use of initial (``sn_tracer%llinit``) and 
     180boundary (``sn_tracer%llsbc, sn_tracer%llcbc, sn_tracer%llobc``) conditions. 
     181 
     182In the following, an example of the full structure definition is given for 
     183two idealized tracers both with initial conditions given, 
     184while the first has only surface boundary forcing and 
    166185the second both surface and coastal forcings: 
    167186 
    168187.. code-block:: fortran 
    169188 
    170    !             !    name   !           title of the field            !   units    ! initial data ! sbc   !   cbc  !   obc  ! 
    171    sn_tracer(1)  = 'TRC1'    , 'Tracer 1 Concentration                ',   ' - '    ,  .true.      , .true., .false., .true. 
    172    sn_tracer(2)  = 'TRC2 '   , 'Tracer 2 Concentration                ',   ' - '    ,  .true.      , .true., .true. , .false. 
     189   !             !    name   !           title of the field            !   units    ! initial data ! sbc   !   cbc  !   obc  ! 
     190   sn_tracer(1)  = 'TRC1'    , 'Tracer 1 Concentration                ',   ' - '    ,  .true.      , .true., .false., .true. 
     191   sn_tracer(2)  = 'TRC2 '   , 'Tracer 2 Concentration                ',   ' - '    ,  .true.      , .true., .true. , .false. 
    173192 
    174193As tracers in BGC models are increasingly growing, 
     
    177196.. code-block:: fortran 
    178197 
    179    !             !    name   !           title of the field            !   units    ! initial data ! 
    180    sn_tracer(1)  = 'TRC1'    , 'Tracer 1 Concentration                ',   ' - '    ,   .true. 
    181    sn_tracer(2)  = 'TRC2 '   , 'Tracer 2 Concentration                ',   ' - '    ,   .true. 
    182    ! sbc 
    183    sn_tracer(1)%llsbc = .true. 
    184    sn_tracer(2)%llsbc = .true. 
    185    ! cbc 
    186    sn_tracer(2)%llcbc = .true. 
     198   !             !    name   !           title of the field            !   units    ! initial data ! 
     199   sn_tracer(1)  = 'TRC1'    , 'Tracer 1 Concentration                ',   ' - '    ,   .true. 
     200   sn_tracer(2)  = 'TRC2 '   , 'Tracer 2 Concentration                ',   ' - '    ,   .true. 
     201   ! sbc 
     202   sn_tracer(1)%llsbc = .true. 
     203   sn_tracer(2)%llsbc = .true. 
     204   ! cbc 
     205   sn_tracer(2)%llcbc = .true. 
    187206 
    188207The data structure is internally initialized by code with dummy names and 
    189 all initialization/forcing logical fields set to .false. . 
    190  
    191 **2. Structures to read input initial and boundary conditions**: namtrc_dta (sn_trcdta), namtrc_bc (sn_trcsbc/sn_trccbc/sn_trcobc) 
     208all initialization/forcing logical fields set to ``.false.`` . 
     209 
     2102. Structures to read input initial and boundary conditions: ``&namtrc_dta`` (``sn_trcdta``), ``&namtrc_bc`` (``sn_trcsbc`` / ``sn_trccbc`` / ``sn_trcobc``) 
     211^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 
    192212 
    193213The overall data structure (Fortran type) is based on the general one defined for NEMO core in the SBC component 
    194 (see details in User Manual SBC Chapter on Input Data specification). 
    195  
    196 Input fields are prescribed within namtrc_dta (with sn_trcdta structure), 
    197 while Boundary Conditions are applied to the model by means of namtrc_bc, 
    198 with dedicated structure fields for surface (sn_trcsbc), riverine (sn_trccbc), and 
    199 lateral open (sn_trcobc) boundaries. 
     214(see details in ``SBC`` Chapter of :doc:`Reference Manual <cite>` on Input Data specification). 
     215 
     216Input fields are prescribed within ``&namtrc_dta`` (with ``sn_trcdta`` structure), 
     217while Boundary Conditions are applied to the model by means of ``&namtrc_bc``, 
     218with dedicated structure fields for surface (``sn_trcsbc``), riverine (``sn_trccbc``), and 
     219lateral open (``sn_trcobc``) boundaries. 
    200220 
    201221The following example illustrates the data structure in the case of initial condition for 
    202 a single tracer contained in the file named tracer_1_data.nc (.nc is implicitly assumed in namelist filename), 
    203 with a doubled initial value, and located in the usr/work/model/inputdata/ folder: 
     222a single tracer contained in the file named :file:`tracer_1_data.nc` 
     223(``.nc`` is implicitly assumed in namelist filename), 
     224with a doubled initial value, and located in the :file:`usr/work/model/inputdata` folder: 
    204225 
    205226.. code-block:: fortran 
    206227 
    207    !               !  file name             ! frequency (hours) ! variable  ! time interp. !  clim  ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
    208    !               !                        !  (if <0  months)  !   name    !   (logical)  !  (T/F) ! 'monthly' ! filename ! pairing  ! filename      ! 
    209      sn_trcdta(1)  = 'tracer_1_data'        ,        -12        ,  'TRC1'   ,    .false.   , .true. , 'yearly'  , ''       , ''       , '' 
    210      rf_trfac(1) = 2.0 
    211      cn_dir = “usr/work/model/inputdata/” 
    212  
    213 Note that, the Lateral Open Boundaries conditions are applied on the segments defined for the physical core of NEMO 
    214 (see BDY description in the User Manual). 
    215  
    216 namelist_trc 
    217 ------------ 
    218  
    219 Here below the description of namelist_trc_ref used to handle Carbon tracers modules, namely CFC and C14. 
    220  
    221 |||| &'''namcfc'''     !   CFC || 
    222  
    223 |||| &'''namc14_typ'''     !  C14 - type of C14 tracer, default values of C14/C and pco2 || 
    224  
    225 |||| &'''namc14_sbc'''     !  C14 - surface BC || 
    226  
    227 |||| &'''namc14_fcg'''     !  files & dates || 
     228   !               !  file name             ! frequency (hours) ! variable  ! time interp. !  clim  ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
     229   !               !                        !  (if <0  months)  !   name    !   (logical)  !  (T/F) ! 'monthly' ! filename ! pairing  ! filename      ! 
     230     sn_trcdta(1)  = 'tracer_1_data'        ,        -12        ,  'TRC1'   ,    .false.   , .true. , 'yearly'  , ''       , ''       , '' 
     231     rf_trfac(1) = 2.0 
     232     cn_dir = 'usr/work/model/inputdata/' 
     233 
     234Note that, the Lateral Open Boundaries conditions are applied on 
     235the segments defined for the physical core of NEMO 
     236(see ``BDY`` description in the :doc:`Reference Manual <cite>`). 
     237 
     238:file:`namelist_trc` 
     239-------------------- 
     240 
     241Here below the description of :file:`namelist_trc_ref` used to handle Carbon tracers modules, 
     242namely CFC and C14. 
     243 
     244.. literalinclude:: ../../../cfgs/SHARED/namelist_trc_ref 
     245   :language: fortran 
     246   :lines: 7,17,26,34 
     247   :caption: :file:`namelist_trc_ref` snippet 
    228248 
    229249``MY_TRC`` interface for coupling external BGC models 
    230250===================================================== 
    231251 
    232 The generalized interface is pivoted on MY_TRC module that contains template files to build the coupling between 
     252The generalized interface is pivoted on MY_TRC module that contains template files to 
     253build the coupling between 
    233254NEMO and any external BGC model. 
    234255 
    235 The call to MY_TRC is activated by setting ``ln_my_trc = .true.`` (in namtrc) 
     256The call to MY_TRC is activated by setting ``ln_my_trc = .true.`` (in ``&namtrc``) 
    236257 
    237258The following 6 fortran files are available in MY_TRC with the specific purposes here described. 
    238259 
    239 ``par_my_trc.F90`` 
    240    This module allows to define additional arrays and public variables to be used within the MY_TRC interface 
    241  
    242 ``trcini_my_trc.F90`` 
    243    Here are initialized user defined namelists and the call to the external BGC model initialization procedures to 
    244    populate general tracer array (trn and trb). Here are also likely to be defined suport arrays related to 
    245    system metrics that could be needed by the BGC model. 
    246  
    247 ``trcnam_my_trc.F90`` 
    248    This routine is called at the beginning of trcini_my_trc and should contain the initialization of 
    249    additional namelists for the BGC model or user-defined code. 
    250  
    251 ``trcsms_my_trc.F90`` 
    252    The routine performs the call to Boundary Conditions and its main purpose is to 
    253    contain the Source-Minus-Sinks terms due to the biogeochemical processes of the external model. 
    254    Be aware that lateral boundary conditions are applied in trcnxt routine. 
    255    IMPORTANT: the routines to compute the light penetration along the water column and 
    256    the tracer vertical sinking should be defined/called in here, as generalized modules are still missing in 
    257    the code. 
    258  
    259 ``trcice_my_trc.F90`` 
    260    Here it is possible to prescribe the tracers concentrations in the seaice that will be used as 
    261    boundary conditions when ice melting occurs (nn_ice_tr =1 in namtrc_ice). 
    262    See e.g. the correspondent PISCES subroutine. 
    263  
    264 ``trcwri_my_trc.F90`` 
    265    This routine performs the output of the model tracers (only those defined in namtrc) using IOM module 
    266    (see Manual Chapter “Output and Diagnostics”). 
    267    It is possible to place here the output of additional variables produced by the model, 
    268    if not done elsewhere in the code, using the call to iom_put. 
     260:file:`par_my_trc.F90` 
     261   This module allows to define additional arrays and public variables to 
     262   be used within the MY_TRC interface 
     263 
     264:file:`trcini_my_trc.F90` 
     265   Here are initialized user defined namelists and 
     266   the call to the external BGC model initialization procedures to populate general tracer array 
     267   (``trn`` and ``trb``). 
     268   Here are also likely to be defined support arrays related to system metrics that 
     269   could be needed by the BGC model. 
     270 
     271:file:`trcnam_my_trc.F90` 
     272   This routine is called at the beginning of ``trcini_my_trc`` and 
     273   should contain the initialization of additional namelists for the BGC model or user-defined code. 
     274 
     275:file:`trcsms_my_trc.F90` 
     276   The routine performs the call to Boundary Conditions and its main purpose is to 
     277   contain the Source-Minus-Sinks terms due to the biogeochemical processes of the external model. 
     278   Be aware that lateral boundary conditions are applied in trcnxt routine. 
     279 
     280   .. warning:: 
     281      The routines to compute the light penetration along the water column and 
     282      the tracer vertical sinking should be defined/called in here, 
     283      as generalized modules are still missing in the code. 
     284 
     285:file:`trcice_my_trc.F90` 
     286   Here it is possible to prescribe the tracers concentrations in the sea-ice that 
     287   will be used as boundary conditions when ice melting occurs (``nn_ice_tr = 1`` in ``&namtrc_ice``). 
     288   See e.g. the correspondent PISCES subroutine. 
     289 
     290:file:`trcwri_my_trc.F90` 
     291   This routine performs the output of the model tracers (only those defined in ``&namtrc``) using 
     292   IOM module (see chapter “Output and Diagnostics” in the :doc:`Reference Manual <cite>`). 
     293   It is possible to place here the output of additional variables produced by the model, 
     294   if not done elsewhere in the code, using the call to ``iom_put``. 
    269295 
    270296Coupling an external BGC model using NEMO framework 
     
    273299The coupling with an external BGC model through the NEMO compilation framework can be achieved in 
    274300different ways according to the degree of coding complexity of the Biogeochemical model, like e.g., 
    275 the whole code is made only by one file or it has multiple modules and interfaces spread across several subfolders. 
    276  
    277 Beside the 6 core files of MY_TRC module, let’s assume an external BGC model named *MYBGC* and constituted by 
    278 a rather essential coding structure, likely few Fortran files. 
     301the whole code is made only by one file or 
     302it has multiple modules and interfaces spread across several subfolders. 
     303 
     304Beside the 6 core files of MY_TRC module, let’s assume an external BGC model named *MYBGC* and 
     305constituted by a rather essential coding structure, likely few Fortran files. 
    279306The new coupled configuration name is *NEMO_MYBGC*. 
    280307 
    281 The best solution is to have all files (the modified ``MY_TRC`` routines and the BGC model ones) placed in 
    282 a unique folder with root ``MYBGCPATH`` and to use the makenemo external readdressing of ``MY_SRC`` folder. 
    283  
    284 The coupled configuration listed in ``work_cfgs.txt`` will look like 
     308The best solution is to have all files (the modified ``MY_TRC`` routines and the BGC model ones) 
     309placed in a unique folder with root ``MYBGCPATH`` and 
     310to use the makenemo external readdressing of ``MY_SRC`` folder. 
     311 
     312The coupled configuration listed in :file:`work_cfgs.txt` will look like 
    285313 
    286314:: 
    287315 
    288    NEMO_MYBGC OPA_SRC TOP_SRC 
     316   NEMO_MYBGC OCE TOP 
    289317 
    290318and the related ``cpp_MYBGC.fcm`` content will be 
     
    292320.. code-block:: perl 
    293321 
    294    bld::tool::fppkeys key_iomput key_mpp_mpi key_top 
    295  
    296 the compilation with ``makenemo`` will be executed through the following syntax 
     322   bld::tool::fppkeys key_iomput key_mpp_mpi key_top 
     323 
     324the compilation with :file:`makenemo` will be executed through the following syntax 
    297325 
    298326.. code-block:: console 
    299327 
    300    $ makenemo -n 'NEMO_MYBGC' -m '<arch_my_machine>' -j 8 -e '<MYBGCPATH>' 
    301  
    302 The makenemo feature “-e” was introduced to readdress at compilation time the standard MY_SRC folder 
    303 (usually found in NEMO configurations) with a user defined external one. 
    304  
    305 The compilation of more articulated BGC model code & infrastructure, like in the case of BFM 
    306 ([http://www.bfm-community.eu/publications/bfmnemomanual_r1.0_201508.pdf BFM-NEMO coupling manual]), 
    307 requires some additional features. 
     328   $ makenemo -n 'NEMO_MYBGC' -m '<arch_my_machine>' -j 8 -e '<MYBGCPATH>' 
     329 
     330The makenemo feature ``-e`` was introduced to 
     331readdress at compilation time the standard MY_SRC folder (usually found in NEMO configurations) with 
     332a user defined external one. 
     333 
     334The compilation of more articulated BGC model code & infrastructure, 
     335like in the case of BFM (|BFM man|_), requires some additional features. 
    308336 
    309337As before, let’s assume a coupled configuration name *NEMO_MYBGC*, 
    310 but in this case MYBGC model root becomes ``<MYBGCPATH>`` that contains 4 different subfolders for 
    311 biogeochemistry, named ``initialization``, ``pelagic``, and ``benthic``, and 
    312 a separate one named ``nemo_coupling`` including the modified ``MY_SRC`` routines. 
     338but in this case MYBGC model root becomes :file:`MYBGC` path that 
     339contains 4 different subfolders for biogeochemistry, 
     340named :file:`initialization`, :file:`pelagic`, and :file:`benthic`, 
     341and a separate one named :file:`nemo_coupling` including the modified `MY_SRC` routines. 
    313342The latter folder containing the modified NEMO coupling interface will be still linked using 
    314 the makenemo “-e” option. 
     343the makenemo ``-e`` option. 
    315344 
    316345In order to include the BGC model subfolders in the compilation of NEMO code, 
    317 it will be necessary to extend the configuration ``cpp_NEMO_MYBGC.fcm`` file to include the specific paths of 
    318 ``MYBGC`` folders, as in the following example 
     346it will be necessary to extend the configuration :file:`cpp_NEMO_MYBGC.fcm` file to include the specific paths of :file:`MYBGC` folders, as in the following example 
    319347 
    320348.. code-block:: perl 
    321349 
    322    bld::tool::fppkeys  key_iomput key_mpp_mpi key_top 
    323     
    324    src::MYBGC::initialization         <MYBGCPATH>/initialization 
    325    src::MYBGC::pelagic                <MYBGCPATH>/pelagic 
    326    src::MYBGC::benthic                <MYBGCPATH>/benthic 
    327     
    328    bld::pp::MYBGC      1 
    329    bld::tool::fppflags::MYBGC   %FPPFLAGS 
    330    bld::tool::fppkeys           %bld::tool::fppkeys MYBGC_MACROS 
     350   bld::tool::fppkeys  key_iomput key_mpp_mpi key_top 
     351 
     352   src::MYBGC::initialization         <MYBGCPATH>/initialization 
     353   src::MYBGC::pelagic                <MYBGCPATH>/pelagic 
     354   src::MYBGC::benthic                <MYBGCPATH>/benthic 
     355 
     356   bld::pp::MYBGC      1 
     357   bld::tool::fppflags::MYBGC   %FPPFLAGS 
     358   bld::tool::fppkeys           %bld::tool::fppkeys MYBGC_MACROS 
    331359 
    332360where *MYBGC_MACROS* is the space delimited list of macros used in *MYBGC* model for 
    333361selecting/excluding specific parts of the code. 
    334 The BGC model code will be preprocessed in the configuration ``BLD`` folder as for NEMO, 
    335 but with an independent path, like ``NEMO_MYBGC/BLD/MYBGC/<subforlders>``. 
     362The BGC model code will be preprocessed in the configuration :file:`BLD` folder as for NEMO, 
     363but with an independent path, like :file:`NEMO_MYBGC/BLD/MYBGC/<subforlders>`. 
    336364 
    337365The compilation will be performed similarly to in the previous case with the following 
     
    339367.. code-block:: console 
    340368 
    341    $ makenemo -n 'NEMO_MYBGC' -m '<arch_my_machine>' -j 8 -e '<MYBGCPATH>/nemo_coupling' 
    342  
    343 Note that, the additional lines specific for the BGC model source and build paths can be written into 
    344 a separate file, e.g. named ``MYBGC.fcm``, and then simply included in the ``cpp_NEMO_MYBGC.fcm`` as follow 
    345  
    346 .. code-block:: perl 
    347  
    348    bld::tool::fppkeys  key_zdftke key_dynspg_ts key_iomput key_mpp_mpi key_top 
    349    inc <MYBGCPATH>/MYBGC.fcm 
    350  
    351 This will enable a more portable compilation structure for all MYBGC related configurations. 
    352  
    353 **Important**: the coupling interface contained in nemo_coupling cannot be added using the FCM syntax, 
    354 as the same files already exists in NEMO and they are overridden only with the readdressing of MY_SRC contents to 
    355 avoid compilation conflicts due to duplicate routines. 
    356  
    357 All modifications illustrated above, can be easily implemented using shell or python scripting to 
    358 edit the NEMO configuration CPP.fcm file and to create the BGC model specific FCM compilation file with code paths. 
     369   $ makenemo -n 'NEMO_MYBGC' -m '<arch_my_machine>' -j 8 -e '<MYBGCPATH>/nemo_coupling' 
     370 
     371.. note:: 
     372   The additional lines specific for the BGC model source and build paths can be written into 
     373   a separate file, e.g. named :file:`MYBGC.fcm`, 
     374   and then simply included in the :file:`cpp_NEMO_MYBGC.fcm` as follow 
     375 
     376   .. code-block:: perl 
     377 
     378      bld::tool::fppkeys  key_zdftke key_dynspg_ts key_iomput key_mpp_mpi key_top 
     379      inc <MYBGCPATH>/MYBGC.fcm 
     380 
     381   This will enable a more portable compilation structure for all MYBGC related configurations. 
     382 
     383.. warning:: 
     384   The coupling interface contained in :file:`nemo_coupling` cannot be added using the FCM syntax, 
     385   as the same files already exists in NEMO and they are overridden only with 
     386   the readdressing of MY_SRC contents to avoid compilation conflicts due to duplicate routines. 
     387 
     388All modifications illustrated above, can be easily implemented using shell or python scripting 
     389to edit the NEMO configuration :file:`CPP.fcm` file and 
     390to create the BGC model specific FCM compilation file with code paths. 
     391 
     392.. |BFM man| replace:: BFM-NEMO coupling manual 
  • NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/trcbdy.F90

    r11536 r11954  
    9595         END DO 
    9696         IF( ANY(llsend1) .OR. ANY(llrecv1) ) THEN   ! if need to send/recv in at least one direction 
    97             CALL lbc_lnk( 'bdytra', tsa, 'T',  1., kfillmode=jpfillnothing ,lsend=llsend1, lrecv=llrecv1 ) 
     97            CALL lbc_lnk( 'trcbdy', tra, 'T',  1., kfillmode=jpfillnothing ,lsend=llsend1, lrecv=llrecv1 ) 
    9898         END IF 
    9999         ! 
Note: See TracChangeset for help on using the changeset viewer.