diff --git a/src/NST/agrif_ice_interp.F90 b/src/NST/agrif_ice_interp.F90
index 7281e5608711b3e031dd38ef76df211d7c9c8c26..eea3d9477c3de17c4f11bb900afa685c3a0e0fe3 100644
--- a/src/NST/agrif_ice_interp.F90
+++ b/src/NST/agrif_ice_interp.F90
@@ -26,13 +26,17 @@ MODULE agrif_ice_interp
    USE phycst , ONLY: rt0
    USE icevar
    USE sbc_ice, ONLY : tn_ice
-   USE lbclnk  
+   USE lbclnk
+   USE iceistate, ONLY : rsshadj
+   USE traqsr, ONLY : ln_traqsr
+   USE lib_mpp  
  
    IMPLICIT NONE
    PRIVATE
 
-   PUBLIC   agrif_interp_ice   ! called by agrif_user.F90
-   PUBLIC   agrif_istate_ice   ! called by icerst.F90
+   PUBLIC   agrif_interp_ice     ! called by agrif_user.F90
+   PUBLIC   agrif_istate_ice     ! called by icerst.F90
+   PUBLIC   agrif_istate_icevol  ! called by restart.F90
 
    !!----------------------------------------------------------------------
    !! NEMO/NST 4.0 , NEMO Consortium (2018)
@@ -87,6 +91,60 @@ CONTAINS
       !
    END SUBROUTINE agrif_istate_ice
 
+
+   SUBROUTINE agrif_istate_icevol( Kbb, Kmm, Kaa )
+      !!-----------------------------------------------------------------------
+      !!           *** ROUTINE agrif_istate_icevol  ***
+      !!
+      !!  ** Method  : Set initial ssh over child grids from the ice volume
+      !!               computed over the parent grid.
+      !!               This routine is call only if nn_ice/=2 (no ice), over
+      !!               the child grid, hence it needs to know nn_ice
+      !!
+      !!-----------------------------------------------------------------------
+      INTEGER, INTENT(in) ::   Kbb, Kmm, Kaa   ! ocean time level indices
+      !
+      INTEGER ::   ios
+      !!
+      NAMELIST/namsbc/ nn_fsbc  ,                                                    &
+         &             ln_usr   , ln_flx   , ln_blk   , ln_abl,                      &
+         &             ln_cpl   , ln_mixcpl, nn_components,                          &
+         &             nn_ice   , ln_ice_embd,                                       &
+         &             ln_traqsr, ln_dm2dc ,                                         &
+         &             ln_rnf   , nn_fwb     , ln_ssr   , ln_apr_dyn,                &
+         &             ln_wave  , nn_lsm
+      !!----------------------------------------------------------------------
+      !
+      IF ( Agrif_Root() ) RETURN
+      !
+      !                       !**  read Surface Module namelist
+      !                       (we only need nn_ice actually which is unknown at the 
+      !                        time this subroutine is called)
+      READ  ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901)
+901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc in reference namelist' )
+      READ  ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 )
+902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc in configuration namelist' )
+      !
+      IF ( (nn_ice/=2).AND.((Agrif_Parent(nn_ice)==2).AND.           &
+                  &   (.NOT.(Agrif_Parent(ln_rstart)                 & 
+                  &     .OR.(Agrif_Parent(nn_iceini_file)==2))).AND. &
+                  &   (.NOT.Agrif_Parent(ln_ice_embd))               &
+                  &  )) THEN
+
+         IF(lwp) WRITE(numout,*) ' ' 
+         IF(lwp) WRITE(numout,*) 'Agrif_istate_icevol : Add an ssh increment coming from the parent grid sea-ice volume'
+         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~'
+         IF(lwp) WRITE(numout,*) ' '
+
+         WHERE( ssmask(:,:) == 1._wp )
+             ssh(:,:,Kmm) = ssh(:,:,Kmm) - Agrif_Parent(rsshadj)
+             ssh(:,:,Kbb) = ssh(:,:,Kbb) - Agrif_Parent(rsshadj) 
+         ENDWHERE
+      ENDIF
+      !
+   END SUBROUTINE agrif_istate_icevol
+
+
    SUBROUTINE agrif_interp_ice( cd_type, kiter, kitermax )
       !!-----------------------------------------------------------------------
       !!                 *** ROUTINE agrif_interp_ice  ***
diff --git a/src/OCE/DOM/domain.F90 b/src/OCE/DOM/domain.F90
index 5288311db4074a8562c078b2621038823e97efd2..dbbe4a9031aa13452c7ef3a83f7ad708b72407d1 100644
--- a/src/OCE/DOM/domain.F90
+++ b/src/OCE/DOM/domain.F90
@@ -36,6 +36,9 @@ MODULE domain
 #endif
 #if defined key_agrif
    USE agrif_oce_interp, ONLY : Agrif_istate_ssh ! ssh interpolated from parent
+#if defined key_si3
+   USE agrif_ice_interp, ONLY : agrif_istate_icevol ! ssh increment from ice
+#endif
 #endif
    USE sbc_oce        ! surface boundary condition: ocean
    USE trc_oce        ! shared ocean & passive tracers variab
@@ -176,6 +179,11 @@ CONTAINS
       ELSEIF( .NOT.Agrif_root() .AND.    &
          &     ln_init_chfrpar ) THEN        !* Interpolate initial ssh from parent
          CALL Agrif_istate_ssh( Kbb, Kmm, Kaa )
+#if defined key_si3
+         ! Possibly add ssh increment from parent grid
+         ! only if there is no ice model in the child grid
+         CALL Agrif_istate_icevol( Kbb, Kmm, Kaa ) 
+#endif
 #endif
       ELSE                                   !* Read in restart file or set by user
          CALL rst_read_ssh( Kbb, Kmm, Kaa )
diff --git a/src/OCE/IOM/restart.F90 b/src/OCE/IOM/restart.F90
index 88a8a9ad3697117a036ecd600fcd6c35c7166600..f39619ad225e08fc3ac32af8872370330c933db7 100644
--- a/src/OCE/IOM/restart.F90
+++ b/src/OCE/IOM/restart.F90
@@ -32,8 +32,7 @@ MODULE restart
    USE diu_bulk       ! ???
 #if defined key_agrif
 #if defined key_si3
-   USE iceistate, ONLY: rsshadj, nn_iceini_file
-   USE sbc_oce, ONLY: ln_ice_embd
+   USE agrif_ice_interp
 #endif
    USE agrif_oce_interp
 #endif
@@ -440,18 +439,12 @@ CONTAINS
 #if defined key_agrif
          ! Set ghosts points from parent 
          IF (.NOT.Agrif_Root()) THEN 
+            ! Set ghosts points from parent 
             CALL Agrif_istate_ssh( Kbb, Kmm, Kaa, .true. ) 
 #if defined key_si3
-            IF ( (nn_ice/=2).AND.((Agrif_Parent(nn_ice)==2).AND.                 &
-                              &   (.NOT.(Agrif_Parent(ln_rstart)                 & 
-                              &     .OR.(Agrif_Parent(nn_iceini_file)==2))).AND. &
-                              &   (.NOT.Agrif_Parent(ln_ice_embd))               &
-                              &  )) THEN
-               WHERE( ssmask(:,:) == 1._wp )
-                  ssh(:,:,Kmm) = ssh(:,:,Kmm) - Agrif_Parent(rsshadj)
-                  ssh(:,:,Kbb) = ssh(:,:,Kbb) - Agrif_Parent(rsshadj) 
-               ENDWHERE
-            ENDIF
+            ! Possibly add ssh increment from parent grid
+            ! only if there is no ice model in the child grid
+            CALL Agrif_istate_icevol( Kbb, Kmm, Kaa ) 
 #endif
          ENDIF
 #endif