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 8518 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv_prather.F90 – NEMO

Ignore:
Timestamp:
2017-09-13T18:46:56+02:00 (7 years ago)
Author:
clem
Message:

changes in style - part6 - commits of the day

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv_prather.F90

    r8512 r8518  
    2020   USE lbclnk         ! lateral boundary condition - MPP exchanges 
    2121   USE in_out_manager ! I/O manager 
     22   USE iom            ! I/O library 
    2223   USE prtctl         ! Print control 
    2324   USE lib_mpp        ! MPP library 
     
    2829 
    2930   PUBLIC   ice_adv_prather   ! called by iceadv 
     31   PUBLIC   adv_pra_rst       ! called by iceadv 
    3032 
    3133   !! * Substitutions 
     
    592594   END SUBROUTINE adv_y 
    593595 
     596   SUBROUTINE adv_pra_rst( cdrw, kt ) 
     597      !!--------------------------------------------------------------------- 
     598      !!                   ***  ROUTINE adv_pra_rst  *** 
     599      !!                      
     600      !! ** Purpose :   Read or write RHG file in restart file 
     601      !! 
     602      !! ** Method  :   use of IOM library 
     603      !!---------------------------------------------------------------------- 
     604      CHARACTER(len=*) , INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag 
     605      INTEGER, OPTIONAL, INTENT(in) ::   kt     ! ice time-step 
     606      ! 
     607      INTEGER ::   jk, jl   ! dummy loop indices 
     608      INTEGER ::   iter     ! local integer 
     609      INTEGER ::   id1      ! local integer 
     610      CHARACTER(len=25) ::   znam 
     611      CHARACTER(len=2)  ::   zchar, zchar1 
     612      REAL(wp), DIMENSION(jpi,jpj) :: z2d 
     613      !!---------------------------------------------------------------------- 
     614      ! 
     615      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialize 
     616         !                                   ! --------------- 
     617         IF( ln_rstart ) THEN                   !* Read the restart file 
     618            ! 
     619            id1 = iom_varid( numrir, 'sxopw' , ldstop = .FALSE. ) 
     620            ! 
     621            IF( id1 > 0 ) THEN      ! fields exist 
     622               DO jl = 1, jpl  
     623                  WRITE(zchar,'(I2.2)') jl 
     624                  znam = 'sxice'//'_htc'//zchar 
     625                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     626                  sxice(:,:,jl) = z2d(:,:) 
     627                  znam = 'syice'//'_htc'//zchar 
     628                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     629                  syice(:,:,jl) = z2d(:,:) 
     630                  znam = 'sxxice'//'_htc'//zchar 
     631                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     632                  sxxice(:,:,jl) = z2d(:,:) 
     633                  znam = 'syyice'//'_htc'//zchar 
     634                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     635                  syyice(:,:,jl) = z2d(:,:) 
     636                  znam = 'sxyice'//'_htc'//zchar 
     637                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     638                  sxyice(:,:,jl) = z2d(:,:) 
     639                  znam = 'sxsn'//'_htc'//zchar 
     640                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     641                  sxsn(:,:,jl) = z2d(:,:) 
     642                  znam = 'sysn'//'_htc'//zchar 
     643                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     644                  sysn(:,:,jl) = z2d(:,:) 
     645                  znam = 'sxxsn'//'_htc'//zchar 
     646                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     647                  sxxsn(:,:,jl) = z2d(:,:) 
     648                  znam = 'syysn'//'_htc'//zchar 
     649                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     650                  syysn(:,:,jl) = z2d(:,:) 
     651                  znam = 'sxysn'//'_htc'//zchar 
     652                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     653                  sxysn(:,:,jl) = z2d(:,:) 
     654                  znam = 'sxa'//'_htc'//zchar 
     655                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     656                  sxa(:,:,jl) = z2d(:,:) 
     657                  znam = 'sya'//'_htc'//zchar 
     658                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     659                  sya(:,:,jl) = z2d(:,:) 
     660                  znam = 'sxxa'//'_htc'//zchar 
     661                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     662                  sxxa(:,:,jl) = z2d(:,:) 
     663                  znam = 'syya'//'_htc'//zchar 
     664                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     665                  syya(:,:,jl) = z2d(:,:) 
     666                  znam = 'sxya'//'_htc'//zchar 
     667                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     668                  sxya(:,:,jl) = z2d(:,:) 
     669                  znam = 'sxc0'//'_htc'//zchar 
     670                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     671                  sxc0(:,:,jl) = z2d(:,:) 
     672                  znam = 'syc0'//'_htc'//zchar 
     673                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     674                  syc0(:,:,jl) = z2d(:,:) 
     675                  znam = 'sxxc0'//'_htc'//zchar 
     676                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     677                  sxxc0(:,:,jl) = z2d(:,:) 
     678                  znam = 'syyc0'//'_htc'//zchar 
     679                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     680                  syyc0(:,:,jl) = z2d(:,:) 
     681                  znam = 'sxyc0'//'_htc'//zchar 
     682                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     683                  sxyc0(:,:,jl) = z2d(:,:) 
     684                  znam = 'sxsal'//'_htc'//zchar 
     685                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     686                  sxsal(:,:,jl) = z2d(:,:) 
     687                  znam = 'sysal'//'_htc'//zchar 
     688                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     689                  sysal(:,:,jl) = z2d(:,:) 
     690                  znam = 'sxxsal'//'_htc'//zchar 
     691                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     692                  sxxsal(:,:,jl) = z2d(:,:) 
     693                  znam = 'syysal'//'_htc'//zchar 
     694                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     695                  syysal(:,:,jl) = z2d(:,:) 
     696                  znam = 'sxysal'//'_htc'//zchar 
     697                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     698                  sxysal(:,:,jl) = z2d(:,:) 
     699                  znam = 'sxage'//'_htc'//zchar 
     700                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     701                  sxage(:,:,jl) = z2d(:,:) 
     702                  znam = 'syage'//'_htc'//zchar 
     703                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     704                  syage(:,:,jl) = z2d(:,:) 
     705                  znam = 'sxxage'//'_htc'//zchar 
     706                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     707                  sxxage(:,:,jl) = z2d(:,:) 
     708                  znam = 'syyage'//'_htc'//zchar 
     709                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     710                  syyage(:,:,jl) = z2d(:,:) 
     711                  znam = 'sxyage'//'_htc'//zchar 
     712                  CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     713                  sxyage(:,:,jl)= z2d(:,:) 
     714               END DO 
     715               ! MV MP 2016 
     716               IF ( nn_pnd_scheme > 0 ) THEN 
     717                  DO jl = 1, jpl  
     718                     WRITE(zchar,'(I2.2)') jl 
     719                     znam = 'sxap'//'_htc'//zchar 
     720                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     721                     sxap(:,:,jl) = z2d(:,:) 
     722                     znam = 'syap'//'_htc'//zchar 
     723                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     724                     syap(:,:,jl) = z2d(:,:) 
     725                     znam = 'sxxap'//'_htc'//zchar 
     726                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     727                     sxxap(:,:,jl) = z2d(:,:) 
     728                     znam = 'syyap'//'_htc'//zchar 
     729                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     730                     syyap(:,:,jl) = z2d(:,:) 
     731                     znam = 'sxyap'//'_htc'//zchar 
     732                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     733                     sxyap(:,:,jl) = z2d(:,:) 
     734 
     735                     znam = 'sxvp'//'_htc'//zchar 
     736                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     737                     sxvp(:,:,jl) = z2d(:,:) 
     738                     znam = 'syvp'//'_htc'//zchar 
     739                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     740                     syvp(:,:,jl) = z2d(:,:) 
     741                     znam = 'sxxvp'//'_htc'//zchar 
     742                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     743                     sxxvp(:,:,jl) = z2d(:,:) 
     744                     znam = 'syyvp'//'_htc'//zchar 
     745                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     746                     syyvp(:,:,jl) = z2d(:,:) 
     747                     znam = 'sxyvp'//'_htc'//zchar 
     748                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     749                     sxyvp(:,:,jl) = z2d(:,:) 
     750                  END DO 
     751               ENDIF 
     752               ! END MV MP 2016 
     753 
     754               CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  ) 
     755               CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  ) 
     756               CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw ) 
     757               CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw ) 
     758               CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw ) 
     759 
     760               DO jl = 1, jpl  
     761                  WRITE(zchar,'(I2.2)') jl 
     762                  DO jk = 1, nlay_i  
     763                     WRITE(zchar1,'(I2.2)') jk 
     764                     znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
     765                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     766                     sxe(:,:,jk,jl) = z2d(:,:) 
     767                     znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
     768                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     769                     sye(:,:,jk,jl) = z2d(:,:) 
     770                     znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
     771                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     772                     sxxe(:,:,jk,jl) = z2d(:,:) 
     773                     znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
     774                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     775                     syye(:,:,jk,jl) = z2d(:,:) 
     776                     znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
     777                     CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     778                     sxye(:,:,jk,jl) = z2d(:,:) 
     779                  END DO 
     780               END DO 
     781               ! 
     782            ELSE                                     ! start rheology from rest 
     783               IF(lwp) WRITE(numout,*) '   ==>>   previous run without Prather, set moments to 0' 
     784               sxopw (:,:) = 0._wp   ;   sxice (:,:,:) = 0._wp   ;   sxsn (:,:,:)  = 0._wp   ;   sxa  (:,:,:) = 0._wp 
     785               syopw (:,:) = 0._wp   ;   syice (:,:,:) = 0._wp   ;   sysn (:,:,:)  = 0._wp   ;   sya  (:,:,:) = 0._wp 
     786               sxxopw(:,:) = 0._wp   ;   sxxice(:,:,:) = 0._wp   ;   sxxsn(:,:,:)  = 0._wp   ;   sxxa (:,:,:) = 0._wp 
     787               syyopw(:,:) = 0._wp   ;   syyice(:,:,:) = 0._wp   ;   syysn(:,:,:)  = 0._wp   ;   syya (:,:,:) = 0._wp 
     788               sxyopw(:,:) = 0._wp   ;   sxyice(:,:,:) = 0._wp   ;   sxysn(:,:,:)  = 0._wp   ;   sxya (:,:,:) = 0._wp 
     789               ! 
     790               sxc0  (:,:,:) = 0._wp   ;   sxe  (:,:,:,:) = 0._wp   ;   sxsal  (:,:,:) = 0._wp   ;   sxage  (:,:,:) = 0._wp 
     791               syc0  (:,:,:) = 0._wp   ;   sye  (:,:,:,:) = 0._wp   ;   sysal  (:,:,:) = 0._wp   ;   syage  (:,:,:) = 0._wp 
     792               sxxc0 (:,:,:) = 0._wp   ;   sxxe (:,:,:,:) = 0._wp   ;   sxxsal (:,:,:) = 0._wp   ;   sxxage (:,:,:) = 0._wp 
     793               syyc0 (:,:,:) = 0._wp   ;   syye (:,:,:,:) = 0._wp   ;   syysal (:,:,:) = 0._wp   ;   syyage (:,:,:) = 0._wp 
     794               sxyc0 (:,:,:) = 0._wp   ;   sxye (:,:,:,:) = 0._wp   ;   sxysal (:,:,:) = 0._wp   ;   sxyage (:,:,:) = 0._wp 
     795               ! MV MP 2016 
     796               IF ( nn_pnd_scheme > 0 ) THEN 
     797                  sxap  (:,:,:) = 0._wp    ; sxvp  (:,:,:) = 0._wp  
     798                  syap  (:,:,:) = 0._wp    ; syvp  (:,:,:) = 0._wp  
     799                  sxxap (:,:,:) = 0._wp    ; sxxvp (:,:,:) = 0._wp  
     800                  syyap (:,:,:) = 0._wp    ; syyvp (:,:,:) = 0._wp  
     801                  sxyap (:,:,:) = 0._wp    ; sxyvp (:,:,:) = 0._wp 
     802               ENDIF 
     803               ! END MV MP 2016 
     804            ENDIF 
     805         ELSE                                   !* Start from rest 
     806            IF(lwp) WRITE(numout,*) '   ==>>   start from rest: set moments to 0' 
     807            sxopw (:,:) = 0._wp   ;   sxice (:,:,:) = 0._wp   ;   sxsn (:,:,:)  = 0._wp   ;   sxa  (:,:,:) = 0._wp 
     808            syopw (:,:) = 0._wp   ;   syice (:,:,:) = 0._wp   ;   sysn (:,:,:)  = 0._wp   ;   sya  (:,:,:) = 0._wp 
     809            sxxopw(:,:) = 0._wp   ;   sxxice(:,:,:) = 0._wp   ;   sxxsn(:,:,:)  = 0._wp   ;   sxxa (:,:,:) = 0._wp 
     810            syyopw(:,:) = 0._wp   ;   syyice(:,:,:) = 0._wp   ;   syysn(:,:,:)  = 0._wp   ;   syya (:,:,:) = 0._wp 
     811            sxyopw(:,:) = 0._wp   ;   sxyice(:,:,:) = 0._wp   ;   sxysn(:,:,:)  = 0._wp   ;   sxya (:,:,:) = 0._wp 
     812            ! 
     813            sxc0  (:,:,:) = 0._wp   ;   sxe  (:,:,:,:) = 0._wp   ;   sxsal  (:,:,:) = 0._wp   ;   sxage  (:,:,:) = 0._wp 
     814            syc0  (:,:,:) = 0._wp   ;   sye  (:,:,:,:) = 0._wp   ;   sysal  (:,:,:) = 0._wp   ;   syage  (:,:,:) = 0._wp 
     815            sxxc0 (:,:,:) = 0._wp   ;   sxxe (:,:,:,:) = 0._wp   ;   sxxsal (:,:,:) = 0._wp   ;   sxxage (:,:,:) = 0._wp 
     816            syyc0 (:,:,:) = 0._wp   ;   syye (:,:,:,:) = 0._wp   ;   syysal (:,:,:) = 0._wp   ;   syyage (:,:,:) = 0._wp 
     817            sxyc0 (:,:,:) = 0._wp   ;   sxye (:,:,:,:) = 0._wp   ;   sxysal (:,:,:) = 0._wp   ;   sxyage (:,:,:) = 0._wp 
     818            ! MV MP 2016 
     819            IF ( nn_pnd_scheme > 0 ) THEN 
     820               sxap  (:,:,:) = 0._wp    ; sxvp  (:,:,:) = 0._wp  
     821               syap  (:,:,:) = 0._wp    ; syvp  (:,:,:) = 0._wp  
     822               sxxap (:,:,:) = 0._wp    ; sxxvp (:,:,:) = 0._wp  
     823               syyap (:,:,:) = 0._wp    ; syyvp (:,:,:) = 0._wp  
     824               sxyap (:,:,:) = 0._wp    ; sxyvp (:,:,:) = 0._wp 
     825            ENDIF 
     826            ! END MV MP 2016 
     827         ENDIF 
     828         ! 
     829      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
     830         !                                   ! ------------------- 
     831         IF(lwp) WRITE(numout,*) '---- adv-rst ----' 
     832         iter = kt + nn_fsbc - 1             ! ice restarts are written at kt == nitrst - nn_fsbc + 1 
     833         ! 
     834         DO jl = 1, jpl  
     835            WRITE(zchar,'(I2.2)') jl 
     836            znam = 'sxice'//'_htc'//zchar 
     837            z2d(:,:) = sxice(:,:,jl) 
     838            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     839            znam = 'syice'//'_htc'//zchar 
     840            z2d(:,:) = syice(:,:,jl) 
     841            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     842            znam = 'sxxice'//'_htc'//zchar 
     843            z2d(:,:) = sxxice(:,:,jl) 
     844            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     845            znam = 'syyice'//'_htc'//zchar 
     846            z2d(:,:) = syyice(:,:,jl) 
     847            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     848            znam = 'sxyice'//'_htc'//zchar 
     849            z2d(:,:) = sxyice(:,:,jl) 
     850            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     851            znam = 'sxsn'//'_htc'//zchar 
     852            z2d(:,:) = sxsn(:,:,jl) 
     853            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     854            znam = 'sysn'//'_htc'//zchar 
     855            z2d(:,:) = sysn(:,:,jl) 
     856            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     857            znam = 'sxxsn'//'_htc'//zchar 
     858            z2d(:,:) = sxxsn(:,:,jl) 
     859            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     860            znam = 'syysn'//'_htc'//zchar 
     861            z2d(:,:) = syysn(:,:,jl) 
     862            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     863            znam = 'sxysn'//'_htc'//zchar 
     864            z2d(:,:) = sxysn(:,:,jl) 
     865            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     866            znam = 'sxa'//'_htc'//zchar 
     867            z2d(:,:) = sxa(:,:,jl) 
     868            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     869            znam = 'sya'//'_htc'//zchar 
     870            z2d(:,:) = sya(:,:,jl) 
     871            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     872            znam = 'sxxa'//'_htc'//zchar 
     873            z2d(:,:) = sxxa(:,:,jl) 
     874            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     875            znam = 'syya'//'_htc'//zchar 
     876            z2d(:,:) = syya(:,:,jl) 
     877            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     878            znam = 'sxya'//'_htc'//zchar 
     879            z2d(:,:) = sxya(:,:,jl) 
     880            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     881            znam = 'sxc0'//'_htc'//zchar 
     882            z2d(:,:) = sxc0(:,:,jl) 
     883            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     884            znam = 'syc0'//'_htc'//zchar 
     885            z2d(:,:) = syc0(:,:,jl) 
     886            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     887            znam = 'sxxc0'//'_htc'//zchar 
     888            z2d(:,:) = sxxc0(:,:,jl) 
     889            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     890            znam = 'syyc0'//'_htc'//zchar 
     891            z2d(:,:) = syyc0(:,:,jl) 
     892            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     893            znam = 'sxyc0'//'_htc'//zchar 
     894            z2d(:,:) = sxyc0(:,:,jl) 
     895            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     896            znam = 'sxsal'//'_htc'//zchar 
     897            z2d(:,:) = sxsal(:,:,jl) 
     898            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     899            znam = 'sysal'//'_htc'//zchar 
     900            z2d(:,:) = sysal(:,:,jl) 
     901            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     902            znam = 'sxxsal'//'_htc'//zchar 
     903            z2d(:,:) = sxxsal(:,:,jl) 
     904            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     905            znam = 'syysal'//'_htc'//zchar 
     906            z2d(:,:) = syysal(:,:,jl) 
     907            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     908            znam = 'sxysal'//'_htc'//zchar 
     909            z2d(:,:) = sxysal(:,:,jl) 
     910            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     911            znam = 'sxage'//'_htc'//zchar 
     912            z2d(:,:) = sxage(:,:,jl) 
     913            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     914            znam = 'syage'//'_htc'//zchar 
     915            z2d(:,:) = syage(:,:,jl) 
     916            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     917            znam = 'sxxage'//'_htc'//zchar 
     918            z2d(:,:) = sxxage(:,:,jl) 
     919            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     920            znam = 'syyage'//'_htc'//zchar 
     921            z2d(:,:) = syyage(:,:,jl) 
     922            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     923            znam = 'sxyage'//'_htc'//zchar 
     924            z2d(:,:) = sxyage(:,:,jl) 
     925            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     926         END DO 
     927 
     928         CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  ) 
     929         CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  ) 
     930         CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw ) 
     931         CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw ) 
     932         CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw ) 
     933          
     934         DO jl = 1, jpl  
     935            WRITE(zchar,'(I2.2)') jl 
     936            DO jk = 1, nlay_i  
     937               WRITE(zchar1,'(I2.2)') jk 
     938               znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
     939               z2d(:,:) = sxe(:,:,jk,jl) 
     940               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     941               znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
     942               z2d(:,:) = sye(:,:,jk,jl) 
     943               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     944               znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
     945               z2d(:,:) = sxxe(:,:,jk,jl) 
     946               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     947               znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
     948               z2d(:,:) = syye(:,:,jk,jl) 
     949               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     950               znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
     951               z2d(:,:) = sxye(:,:,jk,jl) 
     952               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     953            END DO 
     954         END DO 
     955         ! MV MP 2016 
     956         IF ( nn_pnd_scheme > 0 ) THEN 
     957            DO jl = 1, jpl  
     958               WRITE(zchar,'(I2.2)') jl 
     959               znam = 'sxap'//'_htc'//zchar 
     960               z2d(:,:) = sxap(:,:,jl) 
     961               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     962               znam = 'syap'//'_htc'//zchar 
     963               z2d(:,:) = syap(:,:,jl) 
     964               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     965               znam = 'sxxap'//'_htc'//zchar 
     966               z2d(:,:) = sxxap(:,:,jl) 
     967               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     968               znam = 'syyap'//'_htc'//zchar 
     969               z2d(:,:) = syyap(:,:,jl) 
     970               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     971               znam = 'sxyap'//'_htc'//zchar 
     972               z2d(:,:) = sxyap(:,:,jl) 
     973               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     974    
     975               znam = 'sxvp'//'_htc'//zchar 
     976               z2d(:,:) = sxvp(:,:,jl) 
     977               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     978               znam = 'syvp'//'_htc'//zchar 
     979               z2d(:,:) = syvp(:,:,jl) 
     980               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     981               znam = 'sxxvp'//'_htc'//zchar 
     982               z2d(:,:) = sxxvp(:,:,jl) 
     983               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     984               znam = 'syyvp'//'_htc'//zchar 
     985               z2d(:,:) = syyvp(:,:,jl) 
     986               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     987               znam = 'sxyvp'//'_htc'//zchar 
     988               z2d(:,:) = sxyvp(:,:,jl) 
     989               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     990            END DO 
     991         ENDIF 
     992         ! 
     993      ENDIF 
     994      ! 
     995   END SUBROUTINE adv_pra_rst 
     996 
    594997#else 
    595998   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.