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.
isfrst.F90 in NEMO/trunk/src/OCE/ISF – NEMO

source: NEMO/trunk/src/OCE/ISF/isfrst.F90 @ 13286

Last change on this file since 13286 was 13286, checked in by smasson, 4 years ago

trunk: merge extra halos branch in trunk, see #2366

File size: 4.7 KB
RevLine 
[11395]1MODULE isfrst
2   !!======================================================================
3   !!                       ***  MODULE  isfrst  ***
[11403]4   !! iceshelf restart module :read/write iceshelf variables from/in restart
[11395]5   !!======================================================================
6   !! History :  4.1  !  2019-07  (P. Mathiot) Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   isfrst : read/write iceshelf variables in/from restart
11   !!----------------------------------------------------------------------
12   !
[11931]13   USE par_oce, ONLY: jpi,jpj,jpk,jpts ! time and space domain
[11852]14   !
[11395]15   USE in_out_manager ! I/O manager
16   USE iom            ! I/O library
17   !
18   IMPLICIT NONE
19
20   PRIVATE
21
[11423]22   PUBLIC isfrst_read, isfrst_write ! iceshelf restart read and write
[11395]23
24   !!----------------------------------------------------------------------
25   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
26   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
27   !! Software governed by the CeCILL license (see ./LICENSE)
28   !!----------------------------------------------------------------------
29CONTAINS
30   !
31   SUBROUTINE isfrst_read(cdisf, ptsc, pfwf, ptsc_b, pfwf_b )
[11403]32      !!---------------------------------------------------------------------
[11931]33      !!
[11395]34      !!   isfrst_read : read iceshelf variables from restart
[11931]35      !!
[11403]36      !!-------------------------- OUT --------------------------------------
37      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(  out) :: pfwf_b
38      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(  out) :: ptsc_b
39      !!-------------------------- IN  --------------------------------------
[11931]40      CHARACTER(LEN=3)                 , INTENT(in   ) :: cdisf
[11395]41      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) :: pfwf
42      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) :: ptsc
43      !!----------------------------------------------------------------------
44      CHARACTER(LEN=256) :: cfwf_b, chc_b, csc_b
45      !!----------------------------------------------------------------------
46      !
47      ! define variable name
48      cfwf_b = 'fwfisf_'//TRIM(cdisf)//'_b'
49      chc_b  = 'isf_hc_'//TRIM(cdisf)//'_b'
50      csc_b  = 'isf_sc_'//TRIM(cdisf)//'_b'
51      !
52      ! read restart
53      IF( iom_varid( numror, cfwf_b, ldstop = .FALSE. ) > 0 ) THEN
54         IF(lwp) WRITE(numout,*) '          nit000-1 isf tracer content forcing fields read in the restart file'
[13286]55         CALL iom_get( numror, jpdom_auto, cfwf_b, pfwf_b(:,:)        , ldxios = lrxios )   ! before ice shelf melt
56         CALL iom_get( numror, jpdom_auto, chc_b , ptsc_b (:,:,jp_tem), ldxios = lrxios )   ! before ice shelf heat flux
57         CALL iom_get( numror, jpdom_auto, csc_b , ptsc_b (:,:,jp_sal), ldxios = lrxios )   ! before ice shelf heat flux
[11395]58      ELSE
59         pfwf_b(:,:)   = pfwf(:,:)
60         ptsc_b(:,:,:) = ptsc(:,:,:)
61      ENDIF
62      !
63      IF( lwxios ) THEN
[11852]64         CALL iom_set_rstw_var_active(TRIM(chc_b ))
65         CALL iom_set_rstw_var_active(TRIM(csc_b ))
66         CALL iom_set_rstw_var_active(TRIM(cfwf_b))
[11395]67      ENDIF
68
69   END SUBROUTINE isfrst_read
70   !
71   SUBROUTINE isfrst_write(kt, cdisf, ptsc, pfwf )
[11403]72      !!---------------------------------------------------------------------
[11931]73      !!
[11395]74      !!   isfrst_write : write iceshelf variables in restart
[11931]75      !!
[11403]76      !!-------------------------- IN  --------------------------------------
[11852]77      INTEGER                          , INTENT(in   ) :: kt
[11931]78      CHARACTER(LEN=3)                 , INTENT(in   ) :: cdisf
[11395]79      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) :: pfwf
80      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) :: ptsc
[11403]81      !!---------------------------------------------------------------------
[11395]82      CHARACTER(LEN=256) :: cfwf_b, chc_b, csc_b
[11403]83      !!---------------------------------------------------------------------
[11395]84      !
85      ! ocean output print
86      IF(lwp) WRITE(numout,*)
87      IF(lwp) WRITE(numout,*) 'isf : isf fwf and heat fluxes written in ocean restart file ',   &
88         &                    'at it= ', kt,' date= ', ndastp
89      IF(lwp) WRITE(numout,*) '~~~~'
90      !
91      ! define variable name
92      cfwf_b = 'fwfisf_'//TRIM(cdisf)//'_b'
93      chc_b  = 'isf_hc_'//TRIM(cdisf)//'_b'
94      csc_b  = 'isf_sc_'//TRIM(cdisf)//'_b'
95      !
96      ! write restart variable
97      IF( lwxios ) CALL iom_swap( cwxios_context )
98      CALL iom_rstput( kt, nitrst, numrow, cfwf_b, pfwf(:,:)       , ldxios = lwxios )
99      CALL iom_rstput( kt, nitrst, numrow, chc_b , ptsc(:,:,jp_tem), ldxios = lwxios )
100      CALL iom_rstput( kt, nitrst, numrow, csc_b , ptsc(:,:,jp_sal), ldxios = lwxios )
101      IF( lwxios ) CALL iom_swap( cxios_context )
102      !
103   END SUBROUTINE isfrst_write
104   !
105END MODULE isfrst
Note: See TracBrowser for help on using the repository browser.