Skip to content
Snippets Groups Projects
sbcice_cice.F90 43.5 KiB
Newer Older
Guillaume Samson's avatar
Guillaume Samson committed
         png(:,:,:)=0.0
         DO jn=1,jpnij
            DO jj=njs0all(jn),nje0all(jn)
               DO ji=nis0all(jn),nie0all(jn)
                  png(ji,jj,jn)=pcg(ji+nimppt(jn)-1-ji_off,jj+njmppt(jn)-1-jj_off)
               ENDDO
            ENDDO
         ENDDO
      ENDIF

!     C. Scatter png into NEMO field (pn) for each processor

      IF( jpnij > 1) THEN
         CALL mppsync
         CALL mppscatter (png,0,pn) 
         CALL mppsync
      ELSE
         pn(:,:)=png(:,:,1)
      ENDIF

#endif

!     D. Ensure all haloes are filled in pn

      CALL lbc_lnk( 'sbcice_cice', pn , cd_type, psgn )

   END SUBROUTINE cice2nemo

#else
   !!----------------------------------------------------------------------
   !!   Default option           Dummy module         NO CICE sea-ice model
   !!----------------------------------------------------------------------
CONTAINS

   SUBROUTINE sbc_ice_cice ( kt, ksbc )     ! Dummy routine
      IMPLICIT NONE
      INTEGER, INTENT( in ) :: kt, ksbc
      WRITE(*,*) 'sbc_ice_cice: You should not have seen this print! error?', kt
   END SUBROUTINE sbc_ice_cice

   SUBROUTINE cice_sbc_init (ksbc, Kbb, Kmm)    ! Dummy routine
      IMPLICIT NONE
      INTEGER, INTENT( in ) :: ksbc
      INTEGER, INTENT( in ) :: Kbb, Kmm
      WRITE(*,*) 'cice_sbc_init: You should not have seen this print! error?', ksbc
   END SUBROUTINE cice_sbc_init

   SUBROUTINE cice_sbc_final     ! Dummy routine
      IMPLICIT NONE
      WRITE(*,*) 'cice_sbc_final: You should not have seen this print! error?'
   END SUBROUTINE cice_sbc_final

#endif

   !!======================================================================
END MODULE sbcice_cice