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 6989 for branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90 – NEMO

Ignore:
Timestamp:
2016-10-05T09:43:42+02:00 (8 years ago)
Author:
clem
Message:

use a namelist parameter to choose between the different advection schemes

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90

    r5341 r6989  
    5353      INTEGER, INTENT(in) ::   kt       ! number of iteration 
    5454      ! 
    55       CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character 
    56       CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
     55      CHARACTER(len=20)   ::   clkt     ! ocean time-step define as a character 
     56      CHARACTER(len=50)   ::   clname   ! ice output restart file name 
    5757      CHARACTER(len=256)  ::   clpath   ! full path to ice output restart file  
    5858      !!---------------------------------------------------------------------- 
     
    107107      INTEGER ::   ji, jj, jk ,jl   ! dummy loop indices 
    108108      INTEGER ::   iter 
    109       CHARACTER(len=15) ::   znam 
    110       CHARACTER(len=1)  ::   zchar, zchar1 
     109      CHARACTER(len=25) ::   znam 
     110      CHARACTER(len=2)  ::   zchar, zchar1 
    111111      REAL(wp), POINTER, DIMENSION(:,:) :: z2d 
    112112      !!---------------------------------------------------------------------- 
     
    130130      ! Prognostic variables  
    131131      DO jl = 1, jpl  
    132          WRITE(zchar,'(I1)') jl 
     132         WRITE(zchar,'(I2.2)') jl 
    133133         znam = 'v_i'//'_htc'//zchar 
    134134         z2d(:,:) = v_i(:,:,jl) 
     
    152152 
    153153      DO jl = 1, jpl  
    154          WRITE(zchar,'(I1)') jl 
     154         WRITE(zchar,'(I2.2)') jl 
    155155         znam = 'tempt_sl1'//'_htc'//zchar 
    156156         z2d(:,:) = e_s(:,:,1,jl) 
     
    159159 
    160160      DO jl = 1, jpl  
    161          WRITE(zchar,'(I1)') jl 
     161         WRITE(zchar,'(I2.2)') jl 
    162162         DO jk = 1, nlay_i  
    163             WRITE(zchar1,'(I1)') jk 
     163            WRITE(zchar1,'(I2.2)') jk 
    164164            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar 
    165165            z2d(:,:) = e_i(:,:,jk,jl) 
     
    176176      CALL iom_rstput( iter, nitrst, numriw, 'snwice_mass_b', snwice_mass_b ) 
    177177 
    178       DO jl = 1, jpl  
    179          WRITE(zchar,'(I1)') jl 
    180          znam = 'sxice'//'_htc'//zchar 
    181          z2d(:,:) = sxice(:,:,jl) 
    182          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    183          znam = 'syice'//'_htc'//zchar 
    184          z2d(:,:) = syice(:,:,jl) 
    185          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    186          znam = 'sxxice'//'_htc'//zchar 
    187          z2d(:,:) = sxxice(:,:,jl) 
    188          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    189          znam = 'syyice'//'_htc'//zchar 
    190          z2d(:,:) = syyice(:,:,jl) 
    191          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    192          znam = 'sxyice'//'_htc'//zchar 
    193          z2d(:,:) = sxyice(:,:,jl) 
    194          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    195          znam = 'sxsn'//'_htc'//zchar 
    196          z2d(:,:) = sxsn(:,:,jl) 
    197          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    198          znam = 'sysn'//'_htc'//zchar 
    199          z2d(:,:) = sysn(:,:,jl) 
    200          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    201          znam = 'sxxsn'//'_htc'//zchar 
    202          z2d(:,:) = sxxsn(:,:,jl) 
    203          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    204          znam = 'syysn'//'_htc'//zchar 
    205          z2d(:,:) = syysn(:,:,jl) 
    206          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    207          znam = 'sxysn'//'_htc'//zchar 
    208          z2d(:,:) = sxysn(:,:,jl) 
    209          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    210          znam = 'sxa'//'_htc'//zchar 
    211          z2d(:,:) = sxa(:,:,jl) 
    212          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    213          znam = 'sya'//'_htc'//zchar 
    214          z2d(:,:) = sya(:,:,jl) 
    215          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    216          znam = 'sxxa'//'_htc'//zchar 
    217          z2d(:,:) = sxxa(:,:,jl) 
    218          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    219          znam = 'syya'//'_htc'//zchar 
    220          z2d(:,:) = syya(:,:,jl) 
    221          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    222          znam = 'sxya'//'_htc'//zchar 
    223          z2d(:,:) = sxya(:,:,jl) 
    224          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    225          znam = 'sxc0'//'_htc'//zchar 
    226          z2d(:,:) = sxc0(:,:,jl) 
    227          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    228          znam = 'syc0'//'_htc'//zchar 
    229          z2d(:,:) = syc0(:,:,jl) 
    230          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    231          znam = 'sxxc0'//'_htc'//zchar 
    232          z2d(:,:) = sxxc0(:,:,jl) 
    233          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    234          znam = 'syyc0'//'_htc'//zchar 
    235          z2d(:,:) = syyc0(:,:,jl) 
    236          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    237          znam = 'sxyc0'//'_htc'//zchar 
    238          z2d(:,:) = sxyc0(:,:,jl) 
    239          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    240          znam = 'sxsal'//'_htc'//zchar 
    241          z2d(:,:) = sxsal(:,:,jl) 
    242          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    243          znam = 'sysal'//'_htc'//zchar 
    244          z2d(:,:) = sysal(:,:,jl) 
    245          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    246          znam = 'sxxsal'//'_htc'//zchar 
    247          z2d(:,:) = sxxsal(:,:,jl) 
    248          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    249          znam = 'syysal'//'_htc'//zchar 
    250          z2d(:,:) = syysal(:,:,jl) 
    251          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    252          znam = 'sxysal'//'_htc'//zchar 
    253          z2d(:,:) = sxysal(:,:,jl) 
    254          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    255          znam = 'sxage'//'_htc'//zchar 
    256          z2d(:,:) = sxage(:,:,jl) 
    257          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    258          znam = 'syage'//'_htc'//zchar 
    259          z2d(:,:) = syage(:,:,jl) 
    260          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    261          znam = 'sxxage'//'_htc'//zchar 
    262          z2d(:,:) = sxxage(:,:,jl) 
    263          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    264          znam = 'syyage'//'_htc'//zchar 
    265          z2d(:,:) = syyage(:,:,jl) 
    266          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    267          znam = 'sxyage'//'_htc'//zchar 
    268          z2d(:,:) = sxyage(:,:,jl) 
    269          CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    270       END DO 
    271  
    272       CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  ) 
    273       CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  ) 
    274       CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw ) 
    275       CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw ) 
    276       CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw ) 
    277  
    278       DO jl = 1, jpl  
    279          WRITE(zchar,'(I1)') jl 
    280          DO jk = 1, nlay_i  
    281             WRITE(zchar1,'(I1)') jk 
    282             znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
    283             z2d(:,:) = sxe(:,:,jk,jl) 
    284             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    285             znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
    286             z2d(:,:) = sye(:,:,jk,jl) 
    287             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    288             znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
    289             z2d(:,:) = sxxe(:,:,jk,jl) 
    290             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    291             znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
    292             z2d(:,:) = syye(:,:,jk,jl) 
    293             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    294             znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
    295             z2d(:,:) = sxye(:,:,jk,jl) 
    296             CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
    297          END DO 
    298       END DO 
    299  
     178      ! In case Prather scheme is used for advection, write second order moments 
     179      ! ------------------------------------------------------------------------ 
     180      IF( nn_limadv == -1 ) THEN 
     181          
     182         DO jl = 1, jpl  
     183            WRITE(zchar,'(I2.2)') jl 
     184            znam = 'sxice'//'_htc'//zchar 
     185            z2d(:,:) = sxice(:,:,jl) 
     186            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     187            znam = 'syice'//'_htc'//zchar 
     188            z2d(:,:) = syice(:,:,jl) 
     189            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     190            znam = 'sxxice'//'_htc'//zchar 
     191            z2d(:,:) = sxxice(:,:,jl) 
     192            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     193            znam = 'syyice'//'_htc'//zchar 
     194            z2d(:,:) = syyice(:,:,jl) 
     195            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     196            znam = 'sxyice'//'_htc'//zchar 
     197            z2d(:,:) = sxyice(:,:,jl) 
     198            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     199            znam = 'sxsn'//'_htc'//zchar 
     200            z2d(:,:) = sxsn(:,:,jl) 
     201            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     202            znam = 'sysn'//'_htc'//zchar 
     203            z2d(:,:) = sysn(:,:,jl) 
     204            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     205            znam = 'sxxsn'//'_htc'//zchar 
     206            z2d(:,:) = sxxsn(:,:,jl) 
     207            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     208            znam = 'syysn'//'_htc'//zchar 
     209            z2d(:,:) = syysn(:,:,jl) 
     210            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     211            znam = 'sxysn'//'_htc'//zchar 
     212            z2d(:,:) = sxysn(:,:,jl) 
     213            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     214            znam = 'sxa'//'_htc'//zchar 
     215            z2d(:,:) = sxa(:,:,jl) 
     216            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     217            znam = 'sya'//'_htc'//zchar 
     218            z2d(:,:) = sya(:,:,jl) 
     219            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     220            znam = 'sxxa'//'_htc'//zchar 
     221            z2d(:,:) = sxxa(:,:,jl) 
     222            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     223            znam = 'syya'//'_htc'//zchar 
     224            z2d(:,:) = syya(:,:,jl) 
     225            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     226            znam = 'sxya'//'_htc'//zchar 
     227            z2d(:,:) = sxya(:,:,jl) 
     228            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     229            znam = 'sxc0'//'_htc'//zchar 
     230            z2d(:,:) = sxc0(:,:,jl) 
     231            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     232            znam = 'syc0'//'_htc'//zchar 
     233            z2d(:,:) = syc0(:,:,jl) 
     234            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     235            znam = 'sxxc0'//'_htc'//zchar 
     236            z2d(:,:) = sxxc0(:,:,jl) 
     237            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     238            znam = 'syyc0'//'_htc'//zchar 
     239            z2d(:,:) = syyc0(:,:,jl) 
     240            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     241            znam = 'sxyc0'//'_htc'//zchar 
     242            z2d(:,:) = sxyc0(:,:,jl) 
     243            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     244            znam = 'sxsal'//'_htc'//zchar 
     245            z2d(:,:) = sxsal(:,:,jl) 
     246            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     247            znam = 'sysal'//'_htc'//zchar 
     248            z2d(:,:) = sysal(:,:,jl) 
     249            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     250            znam = 'sxxsal'//'_htc'//zchar 
     251            z2d(:,:) = sxxsal(:,:,jl) 
     252            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     253            znam = 'syysal'//'_htc'//zchar 
     254            z2d(:,:) = syysal(:,:,jl) 
     255            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     256            znam = 'sxysal'//'_htc'//zchar 
     257            z2d(:,:) = sxysal(:,:,jl) 
     258            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     259            znam = 'sxage'//'_htc'//zchar 
     260            z2d(:,:) = sxage(:,:,jl) 
     261            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     262            znam = 'syage'//'_htc'//zchar 
     263            z2d(:,:) = syage(:,:,jl) 
     264            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     265            znam = 'sxxage'//'_htc'//zchar 
     266            z2d(:,:) = sxxage(:,:,jl) 
     267            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     268            znam = 'syyage'//'_htc'//zchar 
     269            z2d(:,:) = syyage(:,:,jl) 
     270            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     271            znam = 'sxyage'//'_htc'//zchar 
     272            z2d(:,:) = sxyage(:,:,jl) 
     273            CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     274         END DO 
     275 
     276         CALL iom_rstput( iter, nitrst, numriw, 'sxopw ' ,  sxopw  ) 
     277         CALL iom_rstput( iter, nitrst, numriw, 'syopw ' ,  syopw  ) 
     278         CALL iom_rstput( iter, nitrst, numriw, 'sxxopw' ,  sxxopw ) 
     279         CALL iom_rstput( iter, nitrst, numriw, 'syyopw' ,  syyopw ) 
     280         CALL iom_rstput( iter, nitrst, numriw, 'sxyopw' ,  sxyopw ) 
     281          
     282         DO jl = 1, jpl  
     283            WRITE(zchar,'(I2.2)') jl 
     284            DO jk = 1, nlay_i  
     285               WRITE(zchar1,'(I2.2)') jk 
     286               znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
     287               z2d(:,:) = sxe(:,:,jk,jl) 
     288               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     289               znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
     290               z2d(:,:) = sye(:,:,jk,jl) 
     291               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     292               znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
     293               z2d(:,:) = sxxe(:,:,jk,jl) 
     294               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     295               znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
     296               z2d(:,:) = syye(:,:,jk,jl) 
     297               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     298               znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
     299               z2d(:,:) = sxye(:,:,jk,jl) 
     300               CALL iom_rstput( iter, nitrst, numriw, znam , z2d ) 
     301            END DO 
     302         END DO 
     303 
     304      ENDIF 
     305       
     306      ! close restart file 
     307      ! ------------------ 
    300308      IF( iter == nitrst ) THEN 
    301          CALL iom_close( numriw )                         ! close the restart file 
     309         CALL iom_close( numriw ) 
    302310         lrst_ice = .FALSE. 
    303311      ENDIF 
     
    317325      REAL(wp) ::   zfice, ziter 
    318326      REAL(wp), POINTER, DIMENSION(:,:) ::   z2d 
    319       CHARACTER(len=15) ::   znam 
    320       CHARACTER(len=1)  ::   zchar, zchar1 
     327      CHARACTER(len=25) ::   znam 
     328      CHARACTER(len=2)  ::   zchar, zchar1 
    321329      INTEGER           ::   jlibalt = jprstlib 
    322330      LOGICAL           ::   llok 
     
    356364         &                   '   control of time parameter  nrstdt' ) 
    357365 
     366      ! Prognostic variables  
    358367      DO jl = 1, jpl  
    359          WRITE(zchar,'(I1)') jl 
     368         WRITE(zchar,'(I2.2)') jl 
    360369         znam = 'v_i'//'_htc'//zchar 
    361370         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     
    379388 
    380389      DO jl = 1, jpl  
    381          WRITE(zchar,'(I1)') jl 
     390         WRITE(zchar,'(I2.2)') jl 
    382391         znam = 'tempt_sl1'//'_htc'//zchar 
    383392         CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     
    386395 
    387396      DO jl = 1, jpl  
    388          WRITE(zchar,'(I1)') jl 
     397         WRITE(zchar,'(I2.2)') jl 
    389398         DO jk = 1, nlay_i  
    390             WRITE(zchar1,'(I1)') jk 
     399            WRITE(zchar1,'(I2.2)') jk 
    391400            znam = 'tempt'//'_il'//zchar1//'_htc'//zchar 
    392401            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     
    403412      CALL iom_get( numrir, jpdom_autoglo, 'snwice_mass_b', snwice_mass_b ) 
    404413 
    405       DO jl = 1, jpl  
    406          WRITE(zchar,'(I1)') jl 
    407          znam = 'sxice'//'_htc'//zchar 
    408          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    409          sxice(:,:,jl) = z2d(:,:) 
    410          znam = 'syice'//'_htc'//zchar 
    411          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    412          syice(:,:,jl) = z2d(:,:) 
    413          znam = 'sxxice'//'_htc'//zchar 
    414          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    415          sxxice(:,:,jl) = z2d(:,:) 
    416          znam = 'syyice'//'_htc'//zchar 
    417          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    418          syyice(:,:,jl) = z2d(:,:) 
    419          znam = 'sxyice'//'_htc'//zchar 
    420          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    421          sxyice(:,:,jl) = z2d(:,:) 
    422          znam = 'sxsn'//'_htc'//zchar 
    423          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    424          sxsn(:,:,jl) = z2d(:,:) 
    425          znam = 'sysn'//'_htc'//zchar 
    426          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    427          sysn(:,:,jl) = z2d(:,:) 
    428          znam = 'sxxsn'//'_htc'//zchar 
    429          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    430          sxxsn(:,:,jl) = z2d(:,:) 
    431          znam = 'syysn'//'_htc'//zchar 
    432          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    433          syysn(:,:,jl) = z2d(:,:) 
    434          znam = 'sxysn'//'_htc'//zchar 
    435          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    436          sxysn(:,:,jl) = z2d(:,:) 
    437          znam = 'sxa'//'_htc'//zchar 
    438          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    439          sxa(:,:,jl) = z2d(:,:) 
    440          znam = 'sya'//'_htc'//zchar 
    441          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    442          sya(:,:,jl) = z2d(:,:) 
    443          znam = 'sxxa'//'_htc'//zchar 
    444          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    445          sxxa(:,:,jl) = z2d(:,:) 
    446          znam = 'syya'//'_htc'//zchar 
    447          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    448          syya(:,:,jl) = z2d(:,:) 
    449          znam = 'sxya'//'_htc'//zchar 
    450          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    451          sxya(:,:,jl) = z2d(:,:) 
    452          znam = 'sxc0'//'_htc'//zchar 
    453          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    454          sxc0(:,:,jl) = z2d(:,:) 
    455          znam = 'syc0'//'_htc'//zchar 
    456          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    457          syc0(:,:,jl) = z2d(:,:) 
    458          znam = 'sxxc0'//'_htc'//zchar 
    459          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    460          sxxc0(:,:,jl) = z2d(:,:) 
    461          znam = 'syyc0'//'_htc'//zchar 
    462          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    463          syyc0(:,:,jl) = z2d(:,:) 
    464          znam = 'sxyc0'//'_htc'//zchar 
    465          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    466          sxyc0(:,:,jl) = z2d(:,:) 
    467          znam = 'sxsal'//'_htc'//zchar 
    468          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    469          sxsal(:,:,jl) = z2d(:,:) 
    470          znam = 'sysal'//'_htc'//zchar 
    471          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    472          sysal(:,:,jl) = z2d(:,:) 
    473          znam = 'sxxsal'//'_htc'//zchar 
    474          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    475          sxxsal(:,:,jl) = z2d(:,:) 
    476          znam = 'syysal'//'_htc'//zchar 
    477          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    478          syysal(:,:,jl) = z2d(:,:) 
    479          znam = 'sxysal'//'_htc'//zchar 
    480          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    481          sxysal(:,:,jl) = z2d(:,:) 
    482          znam = 'sxage'//'_htc'//zchar 
    483          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    484          sxage(:,:,jl) = z2d(:,:) 
    485          znam = 'syage'//'_htc'//zchar 
    486          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    487          syage(:,:,jl) = z2d(:,:) 
    488          znam = 'sxxage'//'_htc'//zchar 
    489          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    490          sxxage(:,:,jl) = z2d(:,:) 
    491          znam = 'syyage'//'_htc'//zchar 
    492          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    493          syyage(:,:,jl) = z2d(:,:) 
    494          znam = 'sxyage'//'_htc'//zchar 
    495          CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    496          sxyage(:,:,jl)= z2d(:,:) 
    497       END DO 
    498  
    499       CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  ) 
    500       CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  ) 
    501       CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw ) 
    502       CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw ) 
    503       CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw ) 
    504  
    505       DO jl = 1, jpl  
    506          WRITE(zchar,'(I1)') jl 
    507          DO jk = 1, nlay_i  
    508             WRITE(zchar1,'(I1)') jk 
    509             znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
    510             CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    511             sxe(:,:,jk,jl) = z2d(:,:) 
    512             znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
    513             CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    514             sye(:,:,jk,jl) = z2d(:,:) 
    515             znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
    516             CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    517             sxxe(:,:,jk,jl) = z2d(:,:) 
    518             znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
    519             CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    520             syye(:,:,jk,jl) = z2d(:,:) 
    521             znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
    522             CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
    523             sxye(:,:,jk,jl) = z2d(:,:) 
    524          END DO 
    525       END DO 
    526       ! 
     414      ! In case Prather scheme is used for advection, read second order moments 
     415      ! ------------------------------------------------------------------------ 
     416      IF( nn_limadv == -1 ) THEN 
     417 
     418         DO jl = 1, jpl  
     419            WRITE(zchar,'(I2.2)') jl 
     420            znam = 'sxice'//'_htc'//zchar 
     421            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     422            sxice(:,:,jl) = z2d(:,:) 
     423            znam = 'syice'//'_htc'//zchar 
     424            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     425            syice(:,:,jl) = z2d(:,:) 
     426            znam = 'sxxice'//'_htc'//zchar 
     427            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     428            sxxice(:,:,jl) = z2d(:,:) 
     429            znam = 'syyice'//'_htc'//zchar 
     430            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     431            syyice(:,:,jl) = z2d(:,:) 
     432            znam = 'sxyice'//'_htc'//zchar 
     433            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     434            sxyice(:,:,jl) = z2d(:,:) 
     435            znam = 'sxsn'//'_htc'//zchar 
     436            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     437            sxsn(:,:,jl) = z2d(:,:) 
     438            znam = 'sysn'//'_htc'//zchar 
     439            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     440            sysn(:,:,jl) = z2d(:,:) 
     441            znam = 'sxxsn'//'_htc'//zchar 
     442            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     443            sxxsn(:,:,jl) = z2d(:,:) 
     444            znam = 'syysn'//'_htc'//zchar 
     445            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     446            syysn(:,:,jl) = z2d(:,:) 
     447            znam = 'sxysn'//'_htc'//zchar 
     448            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     449            sxysn(:,:,jl) = z2d(:,:) 
     450            znam = 'sxa'//'_htc'//zchar 
     451            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     452            sxa(:,:,jl) = z2d(:,:) 
     453            znam = 'sya'//'_htc'//zchar 
     454            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     455            sya(:,:,jl) = z2d(:,:) 
     456            znam = 'sxxa'//'_htc'//zchar 
     457            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     458            sxxa(:,:,jl) = z2d(:,:) 
     459            znam = 'syya'//'_htc'//zchar 
     460            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     461            syya(:,:,jl) = z2d(:,:) 
     462            znam = 'sxya'//'_htc'//zchar 
     463            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     464            sxya(:,:,jl) = z2d(:,:) 
     465            znam = 'sxc0'//'_htc'//zchar 
     466            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     467            sxc0(:,:,jl) = z2d(:,:) 
     468            znam = 'syc0'//'_htc'//zchar 
     469            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     470            syc0(:,:,jl) = z2d(:,:) 
     471            znam = 'sxxc0'//'_htc'//zchar 
     472            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     473            sxxc0(:,:,jl) = z2d(:,:) 
     474            znam = 'syyc0'//'_htc'//zchar 
     475            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     476            syyc0(:,:,jl) = z2d(:,:) 
     477            znam = 'sxyc0'//'_htc'//zchar 
     478            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     479            sxyc0(:,:,jl) = z2d(:,:) 
     480            znam = 'sxsal'//'_htc'//zchar 
     481            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     482            sxsal(:,:,jl) = z2d(:,:) 
     483            znam = 'sysal'//'_htc'//zchar 
     484            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     485            sysal(:,:,jl) = z2d(:,:) 
     486            znam = 'sxxsal'//'_htc'//zchar 
     487            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     488            sxxsal(:,:,jl) = z2d(:,:) 
     489            znam = 'syysal'//'_htc'//zchar 
     490            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     491            syysal(:,:,jl) = z2d(:,:) 
     492            znam = 'sxysal'//'_htc'//zchar 
     493            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     494            sxysal(:,:,jl) = z2d(:,:) 
     495            znam = 'sxage'//'_htc'//zchar 
     496            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     497            sxage(:,:,jl) = z2d(:,:) 
     498            znam = 'syage'//'_htc'//zchar 
     499            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     500            syage(:,:,jl) = z2d(:,:) 
     501            znam = 'sxxage'//'_htc'//zchar 
     502            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     503            sxxage(:,:,jl) = z2d(:,:) 
     504            znam = 'syyage'//'_htc'//zchar 
     505            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     506            syyage(:,:,jl) = z2d(:,:) 
     507            znam = 'sxyage'//'_htc'//zchar 
     508            CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     509            sxyage(:,:,jl)= z2d(:,:) 
     510         END DO 
     511 
     512         CALL iom_get( numrir, jpdom_autoglo, 'sxopw ' ,  sxopw  ) 
     513         CALL iom_get( numrir, jpdom_autoglo, 'syopw ' ,  syopw  ) 
     514         CALL iom_get( numrir, jpdom_autoglo, 'sxxopw' ,  sxxopw ) 
     515         CALL iom_get( numrir, jpdom_autoglo, 'syyopw' ,  syyopw ) 
     516         CALL iom_get( numrir, jpdom_autoglo, 'sxyopw' ,  sxyopw ) 
     517 
     518         DO jl = 1, jpl  
     519            WRITE(zchar,'(I2.2)') jl 
     520            DO jk = 1, nlay_i  
     521               WRITE(zchar1,'(I2.2)') jk 
     522               znam = 'sxe'//'_il'//zchar1//'_htc'//zchar 
     523               CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     524               sxe(:,:,jk,jl) = z2d(:,:) 
     525               znam = 'sye'//'_il'//zchar1//'_htc'//zchar 
     526               CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     527               sye(:,:,jk,jl) = z2d(:,:) 
     528               znam = 'sxxe'//'_il'//zchar1//'_htc'//zchar 
     529               CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     530               sxxe(:,:,jk,jl) = z2d(:,:) 
     531               znam = 'syye'//'_il'//zchar1//'_htc'//zchar 
     532               CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     533               syye(:,:,jk,jl) = z2d(:,:) 
     534               znam = 'sxye'//'_il'//zchar1//'_htc'//zchar 
     535               CALL iom_get( numrir, jpdom_autoglo, znam , z2d ) 
     536               sxye(:,:,jk,jl) = z2d(:,:) 
     537            END DO 
     538         END DO 
     539         ! 
     540      END IF 
     541       
    527542      ! clem: I do not understand why the following IF is needed 
    528543      !       I suspect something inconsistent in the main code with option nn_icesal=1 
Note: See TracChangeset for help on using the changeset viewer.