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 8817 for branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/LIM_SRC_3/icedyn_adv_pra.F90 – NEMO

Ignore:
Timestamp:
2017-11-27T12:03:07+01:00 (6 years ago)
Author:
clem
Message:

make ice restart file shorter (this commit is on behalf of Madec)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/LIM_SRC_3/icedyn_adv_pra.F90

    r8637 r8817  
    1212   !!   'key_lim3'                                       ESIM sea-ice model 
    1313   !!---------------------------------------------------------------------- 
    14    !!   ice_dyn_adv_pra   : advection of sea ice using Prather scheme 
     14   !!   ice_dyn_adv_pra : advection of sea ice using Prather scheme 
     15   !!   adv_x, adv_y    : Prather scheme applied in i- and j-direction, resp. 
     16   !!   adv_pra_init    : initialisation of the Prather scheme 
     17   !!   adv_pra_rst     : read/write Prather field in ice restart file, or initialized to zero 
    1518   !!---------------------------------------------------------------------- 
    1619   USE dom_oce        ! ocean domain 
     
    3235 
    3336   ! Moments for advection 
    34    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sxopw, syopw, sxxopw, syyopw, sxyopw   ! open water in sea ice 
    3537   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxice, syice, sxxice, syyice, sxyice   ! ice thickness  
    3638   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsn , sysn , sxxsn , syysn , sxysn    ! snow thickness 
     
    3941   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsal, sysal, sxxsal, syysal, sxysal   ! ice salinity 
    4042   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxage, syage, sxxage, syyage, sxyage   ! ice age 
     43   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sxopw, syopw, sxxopw, syyopw, sxyopw   ! open water in sea ice 
     44   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxe  , sye  , sxxe  , syye  , sxye     ! ice layers heat content 
    4145   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxap , syap , sxxap , syyap , sxyap    ! melt pond fraction 
    4246   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxvp , syvp , sxxvp , syyvp , sxyvp    ! melt pond volume 
    43    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxe  , sye  , sxxe  , syye  , sxye     ! ice layers heat content 
    44    ! 
     47 
    4548   !! * Substitutions 
    4649#  include "vectopt_loop_substitute.h90" 
     
    262265   END SUBROUTINE ice_dyn_adv_pra 
    263266    
     267    
    264268   SUBROUTINE adv_x( pdf, put , pcrh, psm , ps0 ,   & 
    265269      &              psx, psxx, psy , psyy, psxy ) 
     
    608612   END SUBROUTINE adv_y 
    609613 
     614 
    610615   SUBROUTINE adv_pra_init 
    611616      !!------------------------------------------------------------------- 
     
    616621      INTEGER ::   ierr 
    617622      !!------------------------------------------------------------------- 
     623      ! 
     624      !                             !* allocate prather fields 
    618625      ALLOCATE( sxopw(jpi,jpj)     , syopw(jpi,jpj)     , sxxopw(jpi,jpj)     , syyopw(jpi,jpj)     , sxyopw(jpi,jpj)     ,   & 
    619626         &      sxice(jpi,jpj,jpl) , syice(jpi,jpj,jpl) , sxxice(jpi,jpj,jpl) , syyice(jpi,jpj,jpl) , sxyice(jpi,jpj,jpl) ,   & 
     
    632639      IF( ierr /= 0 )   CALL ctl_stop('STOP', 'adv_pra_init : unable to allocate ice arrays for Prather advection scheme') 
    633640      ! 
    634       CALL adv_pra_rst( 'READ' )  !* read or initialize all required files 
     641      CALL adv_pra_rst( 'READ' )    !* read or initialize all required files 
    635642      ! 
    636643   END SUBROUTINE adv_pra_init 
     644 
    637645 
    638646   SUBROUTINE adv_pra_rst( cdrw, kt ) 
     
    652660      CHARACTER(len=25) ::   znam 
    653661      CHARACTER(len=2)  ::   zchar, zchar1 
    654       REAL(wp), DIMENSION(jpi,jpj) :: z2d 
     662      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z3d   ! 3D workspace 
    655663      !!---------------------------------------------------------------------- 
    656664      ! 
    657       IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialize 
    658          !                                   ! --------------- 
    659          IF( ln_rstart ) THEN                   !* Read the restart file 
    660             ! 
    661             id1 = iom_varid( numrir, 'sxopw' , ldstop = .FALSE. ) 
    662             ! 
    663             IF( id1 > 0 ) THEN      ! fields exist 
    664                DO jl = 1, jpl  
    665                   WRITE(zchar,'(I2.2)') jl 
    666                   znam = 'sxice'//'_htc'//zchar 
    667                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    668                   sxice(:,:,jl) = z2d(:,:) 
    669                   znam = 'syice'//'_htc'//zchar 
    670                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    671                   syice(:,:,jl) = z2d(:,:) 
    672                   znam = 'sxxice'//'_htc'//zchar 
    673                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    674                   sxxice(:,:,jl) = z2d(:,:) 
    675                   znam = 'syyice'//'_htc'//zchar 
    676                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    677                   syyice(:,:,jl) = z2d(:,:) 
    678                   znam = 'sxyice'//'_htc'//zchar 
    679                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    680                   sxyice(:,:,jl) = z2d(:,:) 
    681                   znam = 'sxsn'//'_htc'//zchar 
    682                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    683                   sxsn(:,:,jl) = z2d(:,:) 
    684                   znam = 'sysn'//'_htc'//zchar 
    685                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    686                   sysn(:,:,jl) = z2d(:,:) 
    687                   znam = 'sxxsn'//'_htc'//zchar 
    688                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    689                   sxxsn(:,:,jl) = z2d(:,:) 
    690                   znam = 'syysn'//'_htc'//zchar 
    691                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    692                   syysn(:,:,jl) = z2d(:,:) 
    693                   znam = 'sxysn'//'_htc'//zchar 
    694                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    695                   sxysn(:,:,jl) = z2d(:,:) 
    696                   znam = 'sxa'//'_htc'//zchar 
    697                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    698                   sxa(:,:,jl) = z2d(:,:) 
    699                   znam = 'sya'//'_htc'//zchar 
    700                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    701                   sya(:,:,jl) = z2d(:,:) 
    702                   znam = 'sxxa'//'_htc'//zchar 
    703                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    704                   sxxa(:,:,jl) = z2d(:,:) 
    705                   znam = 'syya'//'_htc'//zchar 
    706                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    707                   syya(:,:,jl) = z2d(:,:) 
    708                   znam = 'sxya'//'_htc'//zchar 
    709                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    710                   sxya(:,:,jl) = z2d(:,:) 
    711                   znam = 'sxc0'//'_htc'//zchar 
    712                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    713                   sxc0(:,:,jl) = z2d(:,:) 
    714                   znam = 'syc0'//'_htc'//zchar 
    715                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    716                   syc0(:,:,jl) = z2d(:,:) 
    717                   znam = 'sxxc0'//'_htc'//zchar 
    718                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    719                   sxxc0(:,:,jl) = z2d(:,:) 
    720                   znam = 'syyc0'//'_htc'//zchar 
    721                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    722                   syyc0(:,:,jl) = z2d(:,:) 
    723                   znam = 'sxyc0'//'_htc'//zchar 
    724                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    725                   sxyc0(:,:,jl) = z2d(:,:) 
    726                   znam = 'sxsal'//'_htc'//zchar 
    727                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    728                   sxsal(:,:,jl) = z2d(:,:) 
    729                   znam = 'sysal'//'_htc'//zchar 
    730                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    731                   sysal(:,:,jl) = z2d(:,:) 
    732                   znam = 'sxxsal'//'_htc'//zchar 
    733                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    734                   sxxsal(:,:,jl) = z2d(:,:) 
    735                   znam = 'syysal'//'_htc'//zchar 
    736                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    737                   syysal(:,:,jl) = z2d(:,:) 
    738                   znam = 'sxysal'//'_htc'//zchar 
    739                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    740                   sxysal(:,:,jl) = z2d(:,:) 
    741                   znam = 'sxage'//'_htc'//zchar 
    742                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    743                   sxage(:,:,jl) = z2d(:,:) 
    744                   znam = 'syage'//'_htc'//zchar 
    745                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    746                   syage(:,:,jl) = z2d(:,:) 
    747                   znam = 'sxxage'//'_htc'//zchar 
    748                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    749                   sxxage(:,:,jl) = z2d(:,:) 
    750                   znam = 'syyage'//'_htc'//zchar 
    751                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    752                   syyage(:,:,jl) = z2d(:,:) 
    753                   znam = 'sxyage'//'_htc'//zchar 
    754                   CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    755                   sxyage(:,:,jl)= z2d(:,:) 
    756                END DO 
    757                IF ( ln_pnd_H12 ) THEN 
    758                   DO jl = 1, jpl  
    759                      WRITE(zchar,'(I2.2)') jl 
    760                      znam = 'sxap'//'_htc'//zchar 
    761                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    762                      sxap(:,:,jl) = z2d(:,:) 
    763                      znam = 'syap'//'_htc'//zchar 
    764                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    765                      syap(:,:,jl) = z2d(:,:) 
    766                      znam = 'sxxap'//'_htc'//zchar 
    767                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    768                      sxxap(:,:,jl) = z2d(:,:) 
    769                      znam = 'syyap'//'_htc'//zchar 
    770                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    771                      syyap(:,:,jl) = z2d(:,:) 
    772                      znam = 'sxyap'//'_htc'//zchar 
    773                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    774                      sxyap(:,:,jl) = z2d(:,:) 
    775  
    776                      znam = 'sxvp'//'_htc'//zchar 
    777                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    778                      sxvp(:,:,jl) = z2d(:,:) 
    779                      znam = 'syvp'//'_htc'//zchar 
    780                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    781                      syvp(:,:,jl) = z2d(:,:) 
    782                      znam = 'sxxvp'//'_htc'//zchar 
    783                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    784                      sxxvp(:,:,jl) = z2d(:,:) 
    785                      znam = 'syyvp'//'_htc'//zchar 
    786                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    787                      syyvp(:,:,jl) = z2d(:,:) 
    788                      znam = 'sxyvp'//'_htc'//zchar 
    789                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    790                      sxyvp(:,:,jl) = z2d(:,:) 
    791                   END DO 
    792                ENDIF 
    793  
    794                CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  ) 
    795                CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  ) 
    796                CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw ) 
    797                CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw ) 
    798                CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw ) 
    799  
    800                DO jl = 1, jpl  
    801                   WRITE(zchar,'(I2.2)') jl 
    802                   DO jk = 1, nlay_i  
    803                      WRITE(zchar1,'(I2.2)') jk 
    804                      znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
    805                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    806                      sxe(:,:,jk,jl) = z2d(:,:) 
    807                      znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
    808                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    809                      sye(:,:,jk,jl) = z2d(:,:) 
    810                      znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
    811                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    812                      sxxe(:,:,jk,jl) = z2d(:,:) 
    813                      znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
    814                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    815                      syye(:,:,jk,jl) = z2d(:,:) 
    816                      znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
    817                      CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    818                      sxye(:,:,jk,jl) = z2d(:,:) 
    819                   END DO 
    820                END DO 
    821                ! 
    822             ELSE                                     ! start rheology from rest 
    823                IF(lwp) WRITE(numout,*) '   ==>>   previous run without Prather, set moments to 0' 
    824                sxopw (:,:) = 0._wp   ;   sxice (:,:,:) = 0._wp   ;   sxsn (:,:,:)  = 0._wp   ;   sxa  (:,:,:) = 0._wp 
    825                syopw (:,:) = 0._wp   ;   syice (:,:,:) = 0._wp   ;   sysn (:,:,:)  = 0._wp   ;   sya  (:,:,:) = 0._wp 
    826                sxxopw(:,:) = 0._wp   ;   sxxice(:,:,:) = 0._wp   ;   sxxsn(:,:,:)  = 0._wp   ;   sxxa (:,:,:) = 0._wp 
    827                syyopw(:,:) = 0._wp   ;   syyice(:,:,:) = 0._wp   ;   syysn(:,:,:)  = 0._wp   ;   syya (:,:,:) = 0._wp 
    828                sxyopw(:,:) = 0._wp   ;   sxyice(:,:,:) = 0._wp   ;   sxysn(:,:,:)  = 0._wp   ;   sxya (:,:,:) = 0._wp 
    829                ! 
    830                sxc0  (:,:,:) = 0._wp   ;   sxe  (:,:,:,:) = 0._wp   ;   sxsal  (:,:,:) = 0._wp   ;   sxage  (:,:,:) = 0._wp 
    831                syc0  (:,:,:) = 0._wp   ;   sye  (:,:,:,:) = 0._wp   ;   sysal  (:,:,:) = 0._wp   ;   syage  (:,:,:) = 0._wp 
    832                sxxc0 (:,:,:) = 0._wp   ;   sxxe (:,:,:,:) = 0._wp   ;   sxxsal (:,:,:) = 0._wp   ;   sxxage (:,:,:) = 0._wp 
    833                syyc0 (:,:,:) = 0._wp   ;   syye (:,:,:,:) = 0._wp   ;   syysal (:,:,:) = 0._wp   ;   syyage (:,:,:) = 0._wp 
    834                sxyc0 (:,:,:) = 0._wp   ;   sxye (:,:,:,:) = 0._wp   ;   sxysal (:,:,:) = 0._wp   ;   sxyage (:,:,:) = 0._wp 
    835                IF ( ln_pnd_H12 ) THEN 
    836                   sxap  (:,:,:) = 0._wp    ; sxvp  (:,:,:) = 0._wp  
    837                   syap  (:,:,:) = 0._wp    ; syvp  (:,:,:) = 0._wp  
    838                   sxxap (:,:,:) = 0._wp    ; sxxvp (:,:,:) = 0._wp  
    839                   syyap (:,:,:) = 0._wp    ; syyvp (:,:,:) = 0._wp  
    840                   sxyap (:,:,:) = 0._wp    ; sxyvp (:,:,:) = 0._wp 
    841                ENDIF 
     665      !                                      !==========================! 
     666      IF( TRIM(cdrw) == 'READ' ) THEN        !==  Read or initialize  ==! 
     667         !                                   !==========================! 
     668         ! 
     669         IF( ln_rstart ) THEN   ;   id1 = iom_varid( numrir, 'sxopw' , ldstop = .FALSE. )    ! file exist: id1>0 
     670         ELSE                   ;   id1 = 0                                                  ! no restart: id1=0 
     671         ENDIF 
     672         ! 
     673         IF( id1 > 0 ) THEN                     !**  Read the restart file  **! 
     674            ! 
     675            !                                                        ! ice thickness 
     676            CALL iom_get( numrir, jpdom_autoglo, 'sxice' , sxice  ) 
     677            CALL iom_get( numrir, jpdom_autoglo, 'syice' , syice  ) 
     678            CALL iom_get( numrir, jpdom_autoglo, 'sxxice', sxxice ) 
     679            CALL iom_get( numrir, jpdom_autoglo, 'syyice', syyice ) 
     680            CALL iom_get( numrir, jpdom_autoglo, 'sxyice', sxyice ) 
     681            !                                                        ! snow thickness 
     682            CALL iom_get( numrir, jpdom_autoglo, 'sxsn'  , sxsn   ) 
     683            CALL iom_get( numrir, jpdom_autoglo, 'sysn'  , sysn   ) 
     684            CALL iom_get( numrir, jpdom_autoglo, 'sxxsn' , sxxsn  ) 
     685            CALL iom_get( numrir, jpdom_autoglo, 'syysn' , syysn  ) 
     686            CALL iom_get( numrir, jpdom_autoglo, 'sxysn' , sxysn  ) 
     687            !                                                        ! lead fraction 
     688            CALL iom_get( numrir, jpdom_autoglo, 'sxa'   , sxa    ) 
     689            CALL iom_get( numrir, jpdom_autoglo, 'sya'   , sya    ) 
     690            CALL iom_get( numrir, jpdom_autoglo, 'sxxa'  , sxxa   ) 
     691            CALL iom_get( numrir, jpdom_autoglo, 'syya'  , syya   ) 
     692            CALL iom_get( numrir, jpdom_autoglo, 'sxya'  , sxya   ) 
     693            !                                                        ! snow thermal content 
     694            CALL iom_get( numrir, jpdom_autoglo, 'sxc0'  , sxc0   ) 
     695            CALL iom_get( numrir, jpdom_autoglo, 'syc0'  , syc0   ) 
     696            CALL iom_get( numrir, jpdom_autoglo, 'sxxc0' , sxxc0  ) 
     697            CALL iom_get( numrir, jpdom_autoglo, 'syyc0' , syyc0  ) 
     698            CALL iom_get( numrir, jpdom_autoglo, 'sxyc0' , sxyc0  ) 
     699            !                                                        ! ice salinity 
     700            CALL iom_get( numrir, jpdom_autoglo, 'sxsal' , sxsal  ) 
     701            CALL iom_get( numrir, jpdom_autoglo, 'sysal' , sysal  ) 
     702            CALL iom_get( numrir, jpdom_autoglo, 'sxxsal', sxxsal ) 
     703            CALL iom_get( numrir, jpdom_autoglo, 'syysal', syysal ) 
     704            CALL iom_get( numrir, jpdom_autoglo, 'sxysal', sxysal ) 
     705            !                                                        ! ice age 
     706            CALL iom_get( numrir, jpdom_autoglo, 'sxage' , sxage  ) 
     707            CALL iom_get( numrir, jpdom_autoglo, 'syage' , syage  ) 
     708            CALL iom_get( numrir, jpdom_autoglo, 'sxxage', sxxage ) 
     709            CALL iom_get( numrir, jpdom_autoglo, 'syyage', syyage ) 
     710            CALL iom_get( numrir, jpdom_autoglo, 'sxyage', sxyage ) 
     711            !                                                        ! open water in sea ice 
     712            CALL iom_get( numrir, jpdom_autoglo, 'sxopw ', sxopw  ) 
     713            CALL iom_get( numrir, jpdom_autoglo, 'syopw ', syopw  ) 
     714            CALL iom_get( numrir, jpdom_autoglo, 'sxxopw', sxxopw ) 
     715            CALL iom_get( numrir, jpdom_autoglo, 'syyopw', syyopw ) 
     716            CALL iom_get( numrir, jpdom_autoglo, 'sxyopw', sxyopw ) 
     717            !                                                        ! ice layers heat content 
     718            DO jk = 1, nlay_i  
     719               WRITE(zchar1,'(I2.2)') jk 
     720               znam = 'sxe'//'_il'//zchar1   ;   CALL iom_get( numrir, jpdom_autoglo, znam , z3d )   ;   sxe (:,:,jk,:) = z3d(:,:,:) 
     721               znam = 'sye'//'_il'//zchar1   ;   CALL iom_get( numrir, jpdom_autoglo, znam , z3d )   ;   sye (:,:,jk,:) = z3d(:,:,:) 
     722               znam = 'sxxe'//'_il'//zchar1  ;   CALL iom_get( numrir, jpdom_autoglo, znam , z3d )   ;   sxxe(:,:,jk,:) = z3d(:,:,:) 
     723               znam = 'syye'//'_il'//zchar1  ;   CALL iom_get( numrir, jpdom_autoglo, znam , z3d )   ;   syye(:,:,jk,:) = z3d(:,:,:) 
     724               znam = 'sxye'//'_il'//zchar1  ;   CALL iom_get( numrir, jpdom_autoglo, znam , z3d )   ;   sxye(:,:,jk,:) = z3d(:,:,:) 
     725            END DO 
     726            ! 
     727            IF( ln_pnd_H12 ) THEN                                    ! melt pond fraction 
     728               CALL iom_get( numrir, jpdom_autoglo, 'sxap' , sxap  ) 
     729               CALL iom_get( numrir, jpdom_autoglo, 'syap' , syap  ) 
     730               CALL iom_get( numrir, jpdom_autoglo, 'sxxap', sxxap ) 
     731               CALL iom_get( numrir, jpdom_autoglo, 'syyap', syyap ) 
     732               CALL iom_get( numrir, jpdom_autoglo, 'sxyap', sxyap ) 
     733               !                                                     ! melt pond volume 
     734               CALL iom_get( numrir, jpdom_autoglo, 'sxvp' , sxvp  ) 
     735               CALL iom_get( numrir, jpdom_autoglo, 'syvp' , syvp  ) 
     736               CALL iom_get( numrir, jpdom_autoglo, 'sxxvp', sxxvp ) 
     737               CALL iom_get( numrir, jpdom_autoglo, 'syyvp', syyvp ) 
     738               CALL iom_get( numrir, jpdom_autoglo, 'sxyvp', sxyvp ) 
    842739            ENDIF 
    843          ELSE                                   !* Start from rest 
    844             IF(lwp) WRITE(numout,*) '   ==>>   start from rest: set moments to 0' 
    845             sxopw (:,:) = 0._wp   ;   sxice (:,:,:) = 0._wp   ;   sxsn (:,:,:)  = 0._wp   ;   sxa  (:,:,:) = 0._wp 
    846             syopw (:,:) = 0._wp   ;   syice (:,:,:) = 0._wp   ;   sysn (:,:,:)  = 0._wp   ;   sya  (:,:,:) = 0._wp 
    847             sxxopw(:,:) = 0._wp   ;   sxxice(:,:,:) = 0._wp   ;   sxxsn(:,:,:)  = 0._wp   ;   sxxa (:,:,:) = 0._wp 
    848             syyopw(:,:) = 0._wp   ;   syyice(:,:,:) = 0._wp   ;   syysn(:,:,:)  = 0._wp   ;   syya (:,:,:) = 0._wp 
    849             sxyopw(:,:) = 0._wp   ;   sxyice(:,:,:) = 0._wp   ;   sxysn(:,:,:)  = 0._wp   ;   sxya (:,:,:) = 0._wp 
    850             ! 
    851             sxc0  (:,:,:) = 0._wp   ;   sxe  (:,:,:,:) = 0._wp   ;   sxsal  (:,:,:) = 0._wp   ;   sxage  (:,:,:) = 0._wp 
    852             syc0  (:,:,:) = 0._wp   ;   sye  (:,:,:,:) = 0._wp   ;   sysal  (:,:,:) = 0._wp   ;   syage  (:,:,:) = 0._wp 
    853             sxxc0 (:,:,:) = 0._wp   ;   sxxe (:,:,:,:) = 0._wp   ;   sxxsal (:,:,:) = 0._wp   ;   sxxage (:,:,:) = 0._wp 
    854             syyc0 (:,:,:) = 0._wp   ;   syye (:,:,:,:) = 0._wp   ;   syysal (:,:,:) = 0._wp   ;   syyage (:,:,:) = 0._wp 
    855             sxyc0 (:,:,:) = 0._wp   ;   sxye (:,:,:,:) = 0._wp   ;   sxysal (:,:,:) = 0._wp   ;   sxyage (:,:,:) = 0._wp 
    856             IF ( ln_pnd_H12 ) THEN 
    857                sxap  (:,:,:) = 0._wp    ; sxvp  (:,:,:) = 0._wp  
    858                syap  (:,:,:) = 0._wp    ; syvp  (:,:,:) = 0._wp  
    859                sxxap (:,:,:) = 0._wp    ; sxxvp (:,:,:) = 0._wp  
    860                syyap (:,:,:) = 0._wp    ; syyvp (:,:,:) = 0._wp  
    861                sxyap (:,:,:) = 0._wp    ; sxyvp (:,:,:) = 0._wp 
     740            ! 
     741         ELSE                                   !**  start rheology from rest  **! 
     742            ! 
     743            IF(lwp) WRITE(numout,*) '   ==>>   start from rest OR previous run without Prather, set moments to 0' 
     744            ! 
     745            sxice = 0._wp   ;   syice = 0._wp   ;   sxxice = 0._wp   ;   syyice = 0._wp   ;   sxyice = 0._wp      ! ice thickness 
     746            sxsn  = 0._wp   ;   sysn  = 0._wp   ;   sxxsn  = 0._wp   ;   syysn  = 0._wp   ;   sxysn  = 0._wp      ! snow thickness 
     747            sxa   = 0._wp   ;   sya   = 0._wp   ;   sxxa   = 0._wp   ;   syya   = 0._wp   ;   sxya   = 0._wp      ! lead fraction 
     748            sxc0  = 0._wp   ;   syc0  = 0._wp   ;   sxxc0  = 0._wp   ;   syyc0  = 0._wp   ;   sxyc0  = 0._wp      ! snow thermal content 
     749            sxsal = 0._wp   ;   sysal = 0._wp   ;   sxxsal = 0._wp   ;   syysal = 0._wp   ;   sxysal = 0._wp      ! ice salinity 
     750            sxage = 0._wp   ;   syage = 0._wp   ;   sxxage = 0._wp   ;   syyage = 0._wp   ;   sxyage = 0._wp      ! ice age 
     751            sxopw = 0._wp   ;   syopw = 0._wp   ;   sxxopw = 0._wp   ;   syyopw = 0._wp   ;   sxyopw = 0._wp      ! open water in sea ice 
     752            sxe   = 0._wp   ;   sye   = 0._wp   ;   sxxe   = 0._wp   ;   syye   = 0._wp   ;   sxye   = 0._wp      ! ice layers heat content 
     753            IF( ln_pnd_H12 ) THEN 
     754               sxap  = 0._wp   ;   syap  = 0._wp   ;   sxxap  = 0._wp   ;   syyap  = 0._wp   ;   sxyap  = 0._wp   ! melt pond fraction 
     755               sxvp  = 0._wp   ;   syvp  = 0._wp   ;   sxxvp  = 0._wp   ;   syyvp  = 0._wp   ;   sxyvp  = 0._wp   ! melt pond volume 
    862756            ENDIF 
    863757         ENDIF 
    864758         ! 
    865       ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
    866          !                                   ! ------------------- 
    867          IF(lwp) WRITE(numout,*) '---- adv-rst ----' 
     759         !                                   !=====================================! 
     760      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   !==  write in the ice restart file  ==! 
     761         !                                   !=====================================! 
     762         IF(lwp) WRITE(numout,*) '----  ice-adv-rst  ----' 
    868763         iter = kt + nn_fsbc - 1             ! ice restarts are written at kt == nitrst - nn_fsbc + 1 
    869764         ! 
    870          DO jl = 1, jpl  
    871             WRITE(zchar,'(I2.2)') jl 
    872             znam = 'sxice'//'_htc'//zchar 
    873             z2d(:,:) = sxice(:,:,jl) 
    874             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    875             znam = 'syice'//'_htc'//zchar 
    876             z2d(:,:) = syice(:,:,jl) 
    877             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    878             znam = 'sxxice'//'_htc'//zchar 
    879             z2d(:,:) = sxxice(:,:,jl) 
    880             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    881             znam = 'syyice'//'_htc'//zchar 
    882             z2d(:,:) = syyice(:,:,jl) 
    883             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    884             znam = 'sxyice'//'_htc'//zchar 
    885             z2d(:,:) = sxyice(:,:,jl) 
    886             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    887             znam = 'sxsn'//'_htc'//zchar 
    888             z2d(:,:) = sxsn(:,:,jl) 
    889             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    890             znam = 'sysn'//'_htc'//zchar 
    891             z2d(:,:) = sysn(:,:,jl) 
    892             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    893             znam = 'sxxsn'//'_htc'//zchar 
    894             z2d(:,:) = sxxsn(:,:,jl) 
    895             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    896             znam = 'syysn'//'_htc'//zchar 
    897             z2d(:,:) = syysn(:,:,jl) 
    898             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    899             znam = 'sxysn'//'_htc'//zchar 
    900             z2d(:,:) = sxysn(:,:,jl) 
    901             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    902             znam = 'sxa'//'_htc'//zchar 
    903             z2d(:,:) = sxa(:,:,jl) 
    904             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    905             znam = 'sya'//'_htc'//zchar 
    906             z2d(:,:) = sya(:,:,jl) 
    907             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    908             znam = 'sxxa'//'_htc'//zchar 
    909             z2d(:,:) = sxxa(:,:,jl) 
    910             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    911             znam = 'syya'//'_htc'//zchar 
    912             z2d(:,:) = syya(:,:,jl) 
    913             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    914             znam = 'sxya'//'_htc'//zchar 
    915             z2d(:,:) = sxya(:,:,jl) 
    916             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    917             znam = 'sxc0'//'_htc'//zchar 
    918             z2d(:,:) = sxc0(:,:,jl) 
    919             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    920             znam = 'syc0'//'_htc'//zchar 
    921             z2d(:,:) = syc0(:,:,jl) 
    922             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    923             znam = 'sxxc0'//'_htc'//zchar 
    924             z2d(:,:) = sxxc0(:,:,jl) 
    925             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    926             znam = 'syyc0'//'_htc'//zchar 
    927             z2d(:,:) = syyc0(:,:,jl) 
    928             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    929             znam = 'sxyc0'//'_htc'//zchar 
    930             z2d(:,:) = sxyc0(:,:,jl) 
    931             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    932             znam = 'sxsal'//'_htc'//zchar 
    933             z2d(:,:) = sxsal(:,:,jl) 
    934             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    935             znam = 'sysal'//'_htc'//zchar 
    936             z2d(:,:) = sysal(:,:,jl) 
    937             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    938             znam = 'sxxsal'//'_htc'//zchar 
    939             z2d(:,:) = sxxsal(:,:,jl) 
    940             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    941             znam = 'syysal'//'_htc'//zchar 
    942             z2d(:,:) = syysal(:,:,jl) 
    943             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    944             znam = 'sxysal'//'_htc'//zchar 
    945             z2d(:,:) = sxysal(:,:,jl) 
    946             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    947             znam = 'sxage'//'_htc'//zchar 
    948             z2d(:,:) = sxage(:,:,jl) 
    949             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    950             znam = 'syage'//'_htc'//zchar 
    951             z2d(:,:) = syage(:,:,jl) 
    952             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    953             znam = 'sxxage'//'_htc'//zchar 
    954             z2d(:,:) = sxxage(:,:,jl) 
    955             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    956             znam = 'syyage'//'_htc'//zchar 
    957             z2d(:,:) = syyage(:,:,jl) 
    958             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    959             znam = 'sxyage'//'_htc'//zchar 
    960             z2d(:,:) = sxyage(:,:,jl) 
    961             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    962          END DO 
    963  
    964          CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  ) 
    965          CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  ) 
    966          CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw ) 
    967          CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw ) 
    968          CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw ) 
    969           
    970          DO jl = 1, jpl  
    971             WRITE(zchar,'(I2.2)') jl 
    972             DO jk = 1, nlay_i  
    973                WRITE(zchar1,'(I2.2)') jk 
    974                znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
    975                z2d(:,:) = sxe(:,:,jk,jl) 
    976                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    977                znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
    978                z2d(:,:) = sye(:,:,jk,jl) 
    979                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    980                znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
    981                z2d(:,:) = sxxe(:,:,jk,jl) 
    982                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    983                znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
    984                z2d(:,:) = syye(:,:,jk,jl) 
    985                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    986                znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
    987                z2d(:,:) = sxye(:,:,jk,jl) 
    988                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    989             END DO 
    990          END DO 
    991          IF ( ln_pnd_H12 ) THEN 
    992             DO jl = 1, jpl  
    993                WRITE(zchar,'(I2.2)') jl 
    994                znam = 'sxap'//'_htc'//zchar 
    995                z2d(:,:) = sxap(:,:,jl) 
    996                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    997                znam = 'syap'//'_htc'//zchar 
    998                z2d(:,:) = syap(:,:,jl) 
    999                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1000                znam = 'sxxap'//'_htc'//zchar 
    1001                z2d(:,:) = sxxap(:,:,jl) 
    1002                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1003                znam = 'syyap'//'_htc'//zchar 
    1004                z2d(:,:) = syyap(:,:,jl) 
    1005                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1006                znam = 'sxyap'//'_htc'//zchar 
    1007                z2d(:,:) = sxyap(:,:,jl) 
    1008                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1009     
    1010                znam = 'sxvp'//'_htc'//zchar 
    1011                z2d(:,:) = sxvp(:,:,jl) 
    1012                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1013                znam = 'syvp'//'_htc'//zchar 
    1014                z2d(:,:) = syvp(:,:,jl) 
    1015                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1016                znam = 'sxxvp'//'_htc'//zchar 
    1017                z2d(:,:) = sxxvp(:,:,jl) 
    1018                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1019                znam = 'syyvp'//'_htc'//zchar 
    1020                z2d(:,:) = syyvp(:,:,jl) 
    1021                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1022                znam = 'sxyvp'//'_htc'//zchar 
    1023                z2d(:,:) = sxyvp(:,:,jl) 
    1024                CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    1025             END DO 
     765         ! 
     766         ! In case Prather scheme is used for advection, write second order moments 
     767         ! ------------------------------------------------------------------------ 
     768         ! 
     769         !                                                           ! ice thickness 
     770         CALL iom_rstput( iter, nitrst, numriw, 'sxice' , sxice  ) 
     771         CALL iom_rstput( iter, nitrst, numriw, 'syice' , syice  ) 
     772         CALL iom_rstput( iter, nitrst, numriw, 'sxxice', sxxice ) 
     773         CALL iom_rstput( iter, nitrst, numriw, 'syyice', syyice ) 
     774         CALL iom_rstput( iter, nitrst, numriw, 'sxyice', sxyice ) 
     775         !                                                           ! snow thickness 
     776         CALL iom_rstput( iter, nitrst, numriw, 'sxsn'  , sxsn   ) 
     777         CALL iom_rstput( iter, nitrst, numriw, 'sysn'  , sysn   ) 
     778         CALL iom_rstput( iter, nitrst, numriw, 'sxxsn' , sxxsn  ) 
     779         CALL iom_rstput( iter, nitrst, numriw, 'syysn' , syysn  ) 
     780         CALL iom_rstput( iter, nitrst, numriw, 'sxysn' , sxysn  ) 
     781         !                                                           ! lead fraction 
     782         CALL iom_rstput( iter, nitrst, numriw, 'sxa'   , sxa    ) 
     783         CALL iom_rstput( iter, nitrst, numriw, 'sya'   , sya    ) 
     784         CALL iom_rstput( iter, nitrst, numriw, 'sxxa'  , sxxa   ) 
     785         CALL iom_rstput( iter, nitrst, numriw, 'syya'  , syya   ) 
     786         CALL iom_rstput( iter, nitrst, numriw, 'sxya'  , sxya   ) 
     787         !                                                           ! snow thermal content 
     788         CALL iom_rstput( iter, nitrst, numriw, 'sxc0'  , sxc0   ) 
     789         CALL iom_rstput( iter, nitrst, numriw, 'syc0'  , syc0   ) 
     790         CALL iom_rstput( iter, nitrst, numriw, 'sxxc0' , sxxc0  ) 
     791         CALL iom_rstput( iter, nitrst, numriw, 'syyc0' , syyc0  ) 
     792         CALL iom_rstput( iter, nitrst, numriw, 'sxyc0' , sxyc0  ) 
     793         !                                                           ! ice salinity 
     794         CALL iom_rstput( iter, nitrst, numriw, 'sxsal' , sxsal  ) 
     795         CALL iom_rstput( iter, nitrst, numriw, 'sysal' , sysal  ) 
     796         CALL iom_rstput( iter, nitrst, numriw, 'sxxsal', sxxsal ) 
     797         CALL iom_rstput( iter, nitrst, numriw, 'syysal', syysal ) 
     798         CALL iom_rstput( iter, nitrst, numriw, 'sxysal', sxysal ) 
     799         !                                                           ! ice age 
     800         CALL iom_rstput( iter, nitrst, numriw, 'sxage' , sxage  ) 
     801         CALL iom_rstput( iter, nitrst, numriw, 'syage' , syage  ) 
     802         CALL iom_rstput( iter, nitrst, numriw, 'sxxage', sxxage ) 
     803         CALL iom_rstput( iter, nitrst, numriw, 'syyage', syyage ) 
     804         CALL iom_rstput( iter, nitrst, numriw, 'sxyage', sxyage ) 
     805         !                                                           ! open water in sea ice 
     806         CALL iom_rstput( iter, nitrst, numriw, 'sxopw ', sxopw  ) 
     807         CALL iom_rstput( iter, nitrst, numriw, 'syopw ', syopw  ) 
     808         CALL iom_rstput( iter, nitrst, numriw, 'sxxopw', sxxopw ) 
     809         CALL iom_rstput( iter, nitrst, numriw, 'syyopw', syyopw ) 
     810         CALL iom_rstput( iter, nitrst, numriw, 'sxyopw', sxyopw ) 
     811         !                                                           ! ice layers heat content 
     812         DO jk = 1, nlay_i  
     813            WRITE(zchar1,'(I2.2)') jk 
     814            znam = 'sxe'//'_il'//zchar1   ;   z3d(:,:,:) = sxe (:,:,jk,:)   ;   CALL iom_rstput( iter, nitrst, numriw, znam , z3d ) 
     815            znam = 'sye'//'_il'//zchar1   ;   z3d(:,:,:) = sye (:,:,jk,:)   ;   CALL iom_rstput( iter, nitrst, numriw, znam , z3d ) 
     816            znam = 'sxxe'//'_il'//zchar1  ;   z3d(:,:,:) = sxxe(:,:,jk,:)   ;   CALL iom_rstput( iter, nitrst, numriw, znam , z3d ) 
     817            znam = 'syye'//'_il'//zchar1  ;   z3d(:,:,:) = syye(:,:,jk,:)   ;   CALL iom_rstput( iter, nitrst, numriw, znam , z3d ) 
     818            znam = 'sxye'//'_il'//zchar1  ;   z3d(:,:,:) = sxye(:,:,jk,:)   ;   CALL iom_rstput( iter, nitrst, numriw, znam , z3d ) 
     819         END DO 
     820         ! 
     821         IF( ln_pnd_H12 ) THEN                                       ! melt pond fraction 
     822            CALL iom_rstput( iter, nitrst, numriw, 'sxap' , sxap  ) 
     823            CALL iom_rstput( iter, nitrst, numriw, 'syap' , syap  ) 
     824            CALL iom_rstput( iter, nitrst, numriw, 'sxxap', sxxap ) 
     825            CALL iom_rstput( iter, nitrst, numriw, 'syyap', syyap ) 
     826            CALL iom_rstput( iter, nitrst, numriw, 'sxyap', sxyap ) 
     827            !                                                        ! melt pond volume 
     828            CALL iom_rstput( iter, nitrst, numriw, 'sxvp' , sxvp  ) 
     829            CALL iom_rstput( iter, nitrst, numriw, 'syvp' , syvp  ) 
     830            CALL iom_rstput( iter, nitrst, numriw, 'sxxvp', sxxvp ) 
     831            CALL iom_rstput( iter, nitrst, numriw, 'syyvp', syyvp ) 
     832            CALL iom_rstput( iter, nitrst, numriw, 'sxyvp', sxyvp ) 
    1026833         ENDIF 
    1027834         ! 
Note: See TracChangeset for help on using the changeset viewer.