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 12937 for NEMO/branches/UKMO/NEMO_4.0.1_fix_cpl_v2/src/OCE/BDY – NEMO

Ignore:
Timestamp:
2020-05-15T18:15:25+02:00 (4 years ago)
Author:
dancopsey
Message:

Merge in Clem's branch. It was originally here:

svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/UKMO/NEMO_4.0.1_dan_test_clems_branch

Location:
NEMO/branches/UKMO/NEMO_4.0.1_fix_cpl_v2/src/OCE/BDY
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0.1_fix_cpl_v2/src/OCE/BDY/bdy_oce.F90

    r11715 r12937  
    6363      REAL(wp), POINTER, DIMENSION(:,:) ::  aip    !: now ice  pond concentration 
    6464      REAL(wp), POINTER, DIMENSION(:,:) ::  hip    !: now ice  pond depth 
     65      REAL(wp), POINTER, DIMENSION(:,:) ::  hil    !: now ice  pond lid depth 
    6566#if defined key_top 
    6667      CHARACTER(LEN=20)                   :: cn_obc  !: type of boundary condition to apply 
     
    115116   REAL(wp), DIMENSION(jp_bdy) ::   rice_apnd               !: pond conc.  of incoming sea ice 
    116117   REAL(wp), DIMENSION(jp_bdy) ::   rice_hpnd               !: pond thick. of incoming sea ice 
     118   REAL(wp), DIMENSION(jp_bdy) ::   rice_hlid               !: pond lid thick. of incoming sea ice 
    117119   ! 
    118120   !!---------------------------------------------------------------------- 
  • NEMO/branches/UKMO/NEMO_4.0.1_fix_cpl_v2/src/OCE/BDY/bdydta.F90

    r11715 r12937  
    4343   PUBLIC   bdy_dta_init     ! routine called by nemogcm.F90 
    4444 
    45    INTEGER , PARAMETER ::   jpbdyfld  = 16    ! maximum number of files to read  
     45   INTEGER , PARAMETER ::   jpbdyfld  = 17    ! maximum number of files to read  
    4646   INTEGER , PARAMETER ::   jp_bdyssh = 1     !  
    4747   INTEGER , PARAMETER ::   jp_bdyu2d = 2     !  
     
    6060   INTEGER , PARAMETER ::   jp_bdyaip = 15    !  
    6161   INTEGER , PARAMETER ::   jp_bdyhip = 16    !  
     62   INTEGER , PARAMETER ::   jp_bdyhil = 17    !  
    6263#if ! defined key_si3 
    6364   INTEGER , PARAMETER ::   jpl = 1 
     
    197198                        dta_bdy(jbdy)%aip(ib,jl) =  a_ip(ii,ij,jl) * tmask(ii,ij,1)  
    198199                        dta_bdy(jbdy)%hip(ib,jl) =  h_ip(ii,ij,jl) * tmask(ii,ij,1)  
     200                        dta_bdy(jbdy)%hil(ib,jl) =  h_il(ii,ij,jl) * tmask(ii,ij,1)  
    199201                     END DO 
    200202                  END DO 
     
    302304               &                                                                         bf_alias(jp_bdya_i)%fnow(:,1,:)     !   ( a_ip = rice_apnd * a_i ) 
    303305            IF( TRIM(bf_alias(jp_bdyhip)%clrootname) == 'NOT USED' )   bf_alias(jp_bdyhip)%fnow(:,1,:) = rice_hpnd(jbdy) 
     306            IF( TRIM(bf_alias(jp_bdyhil)%clrootname) == 'NOT USED' )   bf_alias(jp_bdyhil)%fnow(:,1,:) = rice_hlid(jbdy) 
    304307            ! if T_su is read and not T_i, set T_i = (T_su + T_freeze)/2 
    305308            IF( TRIM(bf_alias(jp_bdytsu)%clrootname) /= 'NOT USED' .AND. TRIM(bf_alias(jp_bdyt_i)%clrootname) == 'NOT USED' ) & 
     
    319322               bf_alias(jp_bdyaip)%fnow(:,1,:) = 0._wp 
    320323               bf_alias(jp_bdyhip)%fnow(:,1,:) = 0._wp 
     324               bf_alias(jp_bdyhil)%fnow(:,1,:) = 0._wp 
     325            ENDIF 
     326            IF ( .NOT.ln_pnd_lids ) THEN 
     327               bf_alias(jp_bdyhil)%fnow(:,1,:) = 0._wp 
    321328            ENDIF 
    322329             
     
    324331            ipl = SIZE(bf_alias(jp_bdya_i)%fnow, 3)             
    325332            IF( ipl /= jpl ) THEN      ! ice: convert N-cat fields (input) into jpl-cat (output) 
    326                CALL ice_var_itd( bf_alias(jp_bdyh_i)%fnow(:,1,:), bf_alias(jp_bdyh_s)%fnow(:,1,:), bf_alias(jp_bdya_i)%fnow(:,1,:), & 
    327                   &              dta_alias%h_i                  , dta_alias%h_s                  , dta_alias%a_i                  , & 
    328                   &              bf_alias(jp_bdyt_i)%fnow(:,1,:), bf_alias(jp_bdyt_s)%fnow(:,1,:), & 
    329                   &              bf_alias(jp_bdytsu)%fnow(:,1,:), bf_alias(jp_bdys_i)%fnow(:,1,:), & 
    330                   &              bf_alias(jp_bdyaip)%fnow(:,1,:), bf_alias(jp_bdyhip)%fnow(:,1,:), & 
    331                   &              dta_alias%t_i                  , dta_alias%t_s                  , & 
    332                   &              dta_alias%tsu                  , dta_alias%s_i                  , & 
    333                   &              dta_alias%aip                  , dta_alias%hip ) 
     333               CALL ice_var_itd( bf_alias(jp_bdyh_i)%fnow(:,1,:), bf_alias(jp_bdyh_s)%fnow(:,1,:), bf_alias(jp_bdya_i)%fnow(:,1,:), & ! in 
     334                  &              dta_alias%h_i                  , dta_alias%h_s                  , dta_alias%a_i                  , & ! out 
     335                  &              bf_alias(jp_bdyt_i)%fnow(:,1,:), bf_alias(jp_bdyt_s)%fnow(:,1,:), &                                  ! in (optional) 
     336                  &              bf_alias(jp_bdytsu)%fnow(:,1,:), bf_alias(jp_bdys_i)%fnow(:,1,:), &                                  ! in     - 
     337                  &              bf_alias(jp_bdyaip)%fnow(:,1,:), bf_alias(jp_bdyhip)%fnow(:,1,:), bf_alias(jp_bdyhil)%fnow(:,1,:), & ! in     - 
     338                  &              dta_alias%t_i                  , dta_alias%t_s                  , &                                  ! out    - 
     339                  &              dta_alias%tsu                  , dta_alias%s_i                  , &                                  ! out    - 
     340                  &              dta_alias%aip                  , dta_alias%hip                  , dta_alias%hil )                    ! out    - 
    334341            ENDIF 
    335342         ENDIF 
     
    378385      !                                                         ! =F => baroclinic velocities in 3D boundary data 
    379386      LOGICAL                                ::   ln_zinterp    ! =T => requires a vertical interpolation of the bdydta 
    380       REAL(wp)                               ::   rn_ice_tem, rn_ice_sal, rn_ice_age, rn_ice_apnd, rn_ice_hpnd  
     387      REAL(wp)                               ::   rn_ice_tem, rn_ice_sal, rn_ice_age, rn_ice_apnd, rn_ice_hpnd, rn_ice_hlid 
    381388      INTEGER                                ::   ipk,ipl       ! 
    382389      INTEGER                                ::   idvar         ! variable ID 
     
    390397      TYPE(FLD_N), DIMENSION(1), TARGET  ::   bn_tem, bn_sal, bn_u3d, bn_v3d   ! must be an array to be used with fld_fill 
    391398      TYPE(FLD_N), DIMENSION(1), TARGET  ::   bn_ssh, bn_u2d, bn_v2d           ! informations about the fields to be read 
    392       TYPE(FLD_N), DIMENSION(1), TARGET  ::   bn_a_i, bn_h_i, bn_h_s, bn_t_i, bn_t_s, bn_tsu, bn_s_i, bn_aip, bn_hip        
     399      TYPE(FLD_N), DIMENSION(1), TARGET  ::   bn_a_i, bn_h_i, bn_h_s, bn_t_i, bn_t_s, bn_tsu, bn_s_i, bn_aip, bn_hip, bn_hil        
    393400      TYPE(FLD_N), DIMENSION(:), POINTER ::   bn_alias                        ! must be an array to be used with fld_fill 
    394401      TYPE(FLD  ), DIMENSION(:), POINTER ::   bf_alias 
    395402      ! 
    396403      NAMELIST/nambdy_dta/ cn_dir, bn_tem, bn_sal, bn_u3d, bn_v3d, bn_ssh, bn_u2d, bn_v2d  
    397       NAMELIST/nambdy_dta/ bn_a_i, bn_h_i, bn_h_s, bn_t_i, bn_t_s, bn_tsu, bn_s_i, bn_aip, bn_hip 
    398       NAMELIST/nambdy_dta/ rn_ice_tem, rn_ice_sal, rn_ice_age, rn_ice_apnd, rn_ice_hpnd 
     404      NAMELIST/nambdy_dta/ bn_a_i, bn_h_i, bn_h_s, bn_t_i, bn_t_s, bn_tsu, bn_s_i, bn_aip, bn_hip, bn_hil 
     405      NAMELIST/nambdy_dta/ rn_ice_tem, rn_ice_sal, rn_ice_age, rn_ice_apnd, rn_ice_hpnd, rn_ice_hlid 
    399406      NAMELIST/nambdy_dta/ ln_full_vel, ln_zinterp 
    400407      !!--------------------------------------------------------------------------- 
     
    452459#if defined key_si3 
    453460         IF( .NOT.ln_pnd ) THEN 
    454             rn_ice_apnd = 0. ; rn_ice_hpnd = 0. 
    455             CALL ctl_warn( 'rn_ice_apnd & rn_ice_hpnd = 0 when no ponds' ) 
     461            rn_ice_apnd = 0. ; rn_ice_hpnd = 0. ; rn_ice_hlid = 0. 
     462            CALL ctl_warn( 'rn_ice_apnd & rn_ice_hpnd = 0 & rn_ice_hlid = 0 when no ponds' ) 
     463         ENDIF 
     464         IF( .NOT.ln_pnd_lids ) THEN 
     465            rn_ice_hlid = 0. 
    456466         ENDIF 
    457467#endif 
     
    463473         rice_apnd(jbdy) = rn_ice_apnd 
    464474         rice_hpnd(jbdy) = rn_ice_hpnd 
    465           
     475         rice_hlid(jbdy) = rn_ice_hlid 
     476 
    466477          
    467478         DO jfld = 1, jpbdyfld 
     
    562573            IF(  jfld == jp_bdya_i .OR. jfld == jp_bdyh_i .OR. jfld == jp_bdyh_s .OR. & 
    563574               & jfld == jp_bdyt_i .OR. jfld == jp_bdyt_s .OR. jfld == jp_bdytsu .OR. & 
    564                & jfld == jp_bdys_i .OR. jfld == jp_bdyaip .OR. jfld == jp_bdyhip     ) THEN 
     575               & jfld == jp_bdys_i .OR. jfld == jp_bdyaip .OR. jfld == jp_bdyhip .OR. jfld == jp_bdyhil ) THEN 
    565576               igrd = 1                                                    ! T point 
    566577               ipk = ipl                                                   ! jpl-cat data 
     
    613624               bf_alias => bf(jp_bdyhip,jbdy:jbdy)                         ! alias for hip structure of bdy number jbdy 
    614625               bn_alias => bn_hip                                          ! alias for hip structure of nambdy_dta  
     626            ENDIF 
     627            IF( jfld == jp_bdyhil ) THEN 
     628               cl3 = 'hil' 
     629               bf_alias => bf(jp_bdyhil,jbdy:jbdy)                         ! alias for hil structure of bdy number jbdy 
     630               bn_alias => bn_hil                                          ! alias for hil structure of nambdy_dta  
    615631            ENDIF 
    616632 
     
    681697                  ENDIF 
    682698               ENDIF 
     699               IF( jfld == jp_bdyhil ) THEN 
     700                  IF( ipk == jpl ) THEN   ;   dta_bdy(jbdy)%hil => bf_alias(1)%fnow(:,1,:) 
     701                  ELSE                    ;   ALLOCATE( dta_bdy(jbdy)%hil(iszdim,jpl) ) 
     702                  ENDIF 
     703               ENDIF 
    683704            ENDIF 
    684705 
  • NEMO/branches/UKMO/NEMO_4.0.1_fix_cpl_v2/src/OCE/BDY/bdyice.F90

    r11715 r12937  
    9494         IF( ANY(llsend1) .OR. ANY(llrecv1) ) THEN   ! if need to send/recv in at least one direction 
    9595            ! exchange 3d arrays 
    96             CALL lbc_lnk_multi( 'bdyice', a_i , 'T', 1., h_i , 'T', 1., h_s , 'T', 1., oa_i, 'T', 1. & 
    97                  &                      , a_ip, 'T', 1., v_ip, 'T', 1., s_i , 'T', 1., t_su, 'T', 1. & 
    98                  &                      , v_i , 'T', 1., v_s , 'T', 1., sv_i, 'T', 1.                & 
    99                  &                      , kfillmode=jpfillnothing ,lsend=llsend1, lrecv=llrecv1      ) 
     96            CALL lbc_lnk_multi( 'bdyice', a_i , 'T', 1., h_i , 'T', 1., h_s , 'T', 1., oa_i, 'T', 1.                 & 
     97               &                        , s_i , 'T', 1., t_su, 'T', 1., v_i , 'T', 1., v_s , 'T', 1., sv_i, 'T', 1. & 
     98               &                        , a_ip, 'T', 1., v_ip, 'T', 1., v_il, 'T', 1.                                & 
     99               &                        , kfillmode=jpfillnothing ,lsend=llsend1, lrecv=llrecv1 ) 
    100100            ! exchange 4d arrays :   third dimension = 1   and then   third dimension = jpk 
    101101            CALL lbc_lnk_multi( 'bdyice', t_s , 'T', 1., e_s , 'T', 1., kfillmode=jpfillnothing ,lsend=llsend1, lrecv=llrecv1 ) 
     
    163163            a_ip(ji,jj,  jl) = ( a_ip(ji,jj,  jl) * zwgt1 + dta%aip(i_bdy,jl) * zwgt ) * tmask(ji,jj,1)  ! Ice  pond concentration 
    164164            h_ip(ji,jj,  jl) = ( h_ip(ji,jj,  jl) * zwgt1 + dta%hip(i_bdy,jl) * zwgt ) * tmask(ji,jj,1)  ! Ice  pond depth 
     165            h_il(ji,jj,  jl) = ( h_il(ji,jj,  jl) * zwgt1 + dta%hil(i_bdy,jl) * zwgt ) * tmask(ji,jj,1)  ! Ice  pond lid depth 
    165166            ! 
    166167            sz_i(ji,jj,:,jl) = s_i(ji,jj,jl) 
     
    170171               a_ip(ji,jj,jl) = 0._wp 
    171172               h_ip(ji,jj,jl) = 0._wp 
     173               h_il(ji,jj,jl) = 0._wp 
     174            ENDIF 
     175 
     176            IF( .NOT.ln_pnd_lids ) THEN 
     177               h_il(ji,jj,jl) = 0._wp 
    172178            ENDIF 
    173179            ! 
     
    231237               a_ip(ji,jj,  jl) = a_ip(ib,jb,  jl) 
    232238               h_ip(ji,jj,  jl) = h_ip(ib,jb,  jl) 
     239               h_il(ji,jj,  jl) = h_il(ib,jb,  jl) 
    233240               ! 
    234241               sz_i(ji,jj,:,jl) = sz_i(ib,jb,:,jl) 
     
    265272               ! 
    266273               ! melt ponds 
    267                IF( a_i(ji,jj,jl) > epsi10 ) THEN 
    268                   a_ip_frac(ji,jj,jl) = a_ip(ji,jj,jl) / a_i (ji,jj,jl) 
    269                ELSE 
    270                   a_ip_frac(ji,jj,jl) = 0._wp 
    271                ENDIF 
    272274               v_ip(ji,jj,jl) = h_ip(ji,jj,jl) * a_ip(ji,jj,jl) 
     275               v_il(ji,jj,jl) = h_il(ji,jj,jl) * a_ip(ji,jj,jl) 
    273276               ! 
    274277            ELSE   ! no ice at the boundary 
     
    278281               h_s (ji,jj,  jl) = 0._wp 
    279282               oa_i(ji,jj,  jl) = 0._wp 
    280                a_ip(ji,jj,  jl) = 0._wp 
    281                v_ip(ji,jj,  jl) = 0._wp 
    282283               t_su(ji,jj,  jl) = rt0 
    283284               t_s (ji,jj,:,jl) = rt0 
    284285               t_i (ji,jj,:,jl) = rt0  
    285286 
    286                a_ip_frac(ji,jj,jl) = 0._wp 
    287                h_ip     (ji,jj,jl) = 0._wp 
    288                a_ip     (ji,jj,jl) = 0._wp 
    289                v_ip     (ji,jj,jl) = 0._wp 
     287               a_ip(ji,jj,jl) = 0._wp 
     288               h_ip(ji,jj,jl) = 0._wp 
     289               h_il(ji,jj,jl) = 0._wp 
    290290                
    291291               IF( nn_icesal == 1 ) THEN     ! if constant salinity 
     
    303303               e_s (ji,jj,:,jl) = 0._wp 
    304304               e_i (ji,jj,:,jl) = 0._wp 
     305               v_ip(ji,jj,  jl) = 0._wp 
     306               v_il(ji,jj,  jl) = 0._wp 
    305307 
    306308            ENDIF 
Note: See TracChangeset for help on using the changeset viewer.