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 508 for trunk/NEMO/LIM_SRC – NEMO

Changeset 508 for trunk/NEMO/LIM_SRC


Ignore:
Timestamp:
2006-10-03T17:58:55+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_071:RB: add iom for restart and reorganization of restart

Location:
trunk/NEMO/LIM_SRC
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC/dom_ice.F90

    r420 r508  
    44   !! LIM Sea Ice :   Domain  variables 
    55   !!====================================================================== 
    6    !! History : 
    7    !!   2.0  !  03-08  (C. Ethe)  Free form and module 
     6   !! History :   2.0  !  03-08  (C. Ethe)  Free form and module 
     7   !!---------------------------------------------------------------------- 
     8 
    89   !!---------------------------------------------------------------------- 
    910   !!   LIM 2.0, UCL-LOCEAN-IPSL (2005) 
    1011   !! $Header$ 
    11    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
     12   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    1213   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    1414   USE par_ice 
    1515 
     
    1717   PRIVATE 
    1818 
    19    !! * Share module variables 
    20    LOGICAL, PUBLIC ::       &  !: 
    21       l_jeq     = .TRUE. ,  &  !: Equator inside the domain flag 
    22       ln_limini = .FALSE.,  &  !: Ice initialization state 
    23       ln_limdmp = .FALSE.      !: Ice damping 
     19   LOGICAL, PUBLIC ::   l_jeq     = .TRUE.     !: Equator inside the domain flag 
     20   LOGICAL, PUBLIC ::   ln_limini = .FALSE.    !: Ice initialization state 
     21   LOGICAL, PUBLIC ::   ln_limdmp = .FALSE.    !: Ice damping 
    2422 
    25    INTEGER, PUBLIC ::   &  !: 
    26       njeq , njeqm1        !: j-index of the equator if it is inside the domain 
    27       !                    !  (otherwise = jpj+10 (SH) or -10 (SH) ) 
     23   INTEGER, PUBLIC ::   njeq , njeqm1          !: j-index of the equator if it is inside the domain 
     24      !                                        !  (otherwise = jpj+10 (SH) or -10 (SH) ) 
    2825 
    29    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  !: 
    30       fs2cor ,          &  !: coriolis factor 
    31       fcor   ,          &  !: coriolis coefficient 
    32       covrai ,          &  !: sine of geographic latitude 
    33       area   ,          &  !: surface of grid cell  
    34       tms    , tmu         !: temperature and velocity points masks 
    35  
    36    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2) ::   &  !: 
    37       wght   ,          &  !: weight of the 4 neighbours to compute averages 
    38       akappa ,          &  !: first group of metric coefficients 
    39       bkappa               !: third group of metric coefficients 
    40  
    41    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2,2,2) ::   &  !: 
    42       alambd               !: second group of metric coefficients 
     26   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)         ::   fs2cor , fcor,   &  !: coriolis factor and coeficient 
     27      &                                              covrai ,         &  !: sine of geographic latitude 
     28      &                                              area   ,         &  !: surface of grid cell  
     29      &                                              tms    , tmu        !: temperature and velocity points masks 
     30   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2)     ::   wght   ,         &  !: weight of the 4 neighbours to compute averages 
     31      &                                              akappa , bkappa     !: first and third group of metric coefficients 
     32   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2,2,2,2) ::   alambd   !: second group of metric coefficients 
    4333 
    4434   !!====================================================================== 
  • trunk/NEMO/LIM_SRC/iceini.F90

    r391 r508  
    44   !!   Sea-ice model : LIM Sea ice model Initialization 
    55   !!====================================================================== 
     6   !! History :   1.0  !  02-08  (G. Madec)  F90: Free form and modules 
     7   !!             2.0  !  03-08  (C. Ethe)  add ice_run 
     8   !!---------------------------------------------------------------------- 
    69#if defined key_ice_lim 
    710   !!---------------------------------------------------------------------- 
    811   !!   'key_ice_lim' :                                   LIM sea-ice model 
    912   !!---------------------------------------------------------------------- 
     13   !!---------------------------------------------------------------------- 
    1014   !!   ice_init       : sea-ice model initialization 
     15   !!   ice_run        : Definition some run parameter for ice model 
    1116   !!---------------------------------------------------------------------- 
    1217   USE dom_oce 
     
    1924   USE limmsh 
    2025   USE limistate 
    21    USE limrst 
     26   USE limrst    
    2227   USE ini1d           ! initialization of the 1D configuration 
    23  
     28       
    2429   IMPLICIT NONE 
    2530   PRIVATE 
    2631 
    27    !! * Routine accessibility 
    28    PUBLIC ice_init                 ! called by opa.F90 
     32   PUBLIC   ice_init                 ! called by opa.F90 
    2933 
    30    !! * Share Module variables 
    31    LOGICAL , PUBLIC  ::   & !!! ** init namelist (namicerun) ** 
    32       ln_limdyn   = .TRUE.   !: flag for ice dynamics (T) or not (F) 
    33    INTEGER , PUBLIC  ::   &  !: 
    34       nstart ,            &  !: iteration number of the begining of the run  
    35       nlast  ,            &  !: iteration number of the end of the run  
    36       nitrun ,            &  !: number of iteration 
    37       numit                  !: iteration number 
    38    REAL(wp), PUBLIC  ::   &  !: 
    39       hsndif = 0.e0 ,     &  !: computation of temp. in snow (0) or not (9999) 
    40       hicdif = 0.e0 ,     &  !: computation of temp. in ice (0) or not (9999) 
    41       tpstot                 !: time of the run in seconds 
    42    REAL(wp), PUBLIC, DIMENSION(2)  ::  &  !: 
    43       acrit  = (/ 1.e-06 , 1.e-06 /)    !: minimum fraction for leads in  
    44       !                                   !  north and south hemisphere 
     34   LOGICAL , PUBLIC               ::   ln_limdyn = .TRUE.   !: flag for ice dynamics (T) or not (F) 
     35   REAL(wp), PUBLIC               ::   hsndif = 0.e0        !: computation of temp. in snow (0) or not (9999) 
     36   REAL(wp), PUBLIC               ::   hicdif = 0.e0        !: computation of temp. in ice (0) or not (9999) 
     37   REAL(wp), PUBLIC, DIMENSION(2) ::   acrit  = (/ 1.e-06 , 1.e-06 /)    !: minimum fraction for leads in  
     38      !                                                                  !  north and south hemisphere 
    4539   !!---------------------------------------------------------------------- 
    4640   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)  
     
    5650      !! 
    5751      !! ** purpose :    
    58       !! 
    59       !! History : 
    60       !!   8.5  !  02-08  (G. Madec)  F90: Free form and modules 
    6152      !!---------------------------------------------------------------------- 
    62        CHARACTER(len=80) :: namelist_icename 
    63         
     53      CHARACTER(len=80) :: namelist_icename 
     54      !!---------------------------------------------------------------------- 
     55      ! 
    6456      ! Open the namelist file  
    6557      namelist_icename = 'namelist_ice' 
    66             
    6758      CALL ctlopn(numnam_ice,namelist_icename,'OLD', 'FORMATTED', 'SEQUENTIAL',   & 
    6859                     1,numout,.FALSE.,1)       
    69  
    7060      CALL ice_run                    !  read in namelist some run parameters 
    7161                  
     
    8373      ! Initial sea-ice state 
    8474      IF( .NOT.ln_rstart ) THEN 
    85          numit = 0 
    8675         CALL lim_istate              ! start from rest: sea-ice deduced from sst 
    8776      ELSE 
    88          CALL lim_rst_read( numit )   ! start from a restart file 
     77         CALL lim_rst_read            ! start from a restart file 
    8978      ENDIF 
    9079       
     
    9483      alb_ice(:,:) = albege(:,:)      ! sea-ice albedo 
    9584# endif 
    96        
    97       nstart = numit  + nfice       
    98       nitrun = nitend - nit000 + 1  
    99       nlast  = numit  + nitrun  
    100  
    101       IF( nstock == 0  )  nstock = nlast + 1 
    102  
     85      ! 
    10386   END SUBROUTINE ice_init 
    10487 
     
    11497      !! 
    11598      !! ** input   :   Namelist namicerun 
    116       !! 
    117       !! history : 
    118       !!   2.0  !  03-08 (C. Ethe)  Original code 
    11999      !!------------------------------------------------------------------- 
    120  
    121100      NAMELIST/namicerun/ ln_limdyn, acrit, hsndif, hicdif 
    122101      !!------------------------------------------------------------------- 
    123  
    124       !                                           ! Read Namelist namicerun  
    125       REWIND ( numnam_ice ) 
     102      !                     
     103      REWIND ( numnam_ice )                       ! Read Namelist namicerun  
    126104      READ   ( numnam_ice , namicerun ) 
    127105 
    128       IF( lk_cfg_1d  )  ln_limdyn = .FALSE.       ! No ice transport in 1D configuration 
     106      IF( lk_cfg_1d  )   ln_limdyn = .FALSE.      ! No ice transport in 1D configuration 
    129107 
    130108      IF(lwp) THEN 
     
    137115         WRITE(numout,*) '   computation of temp. in ice  (=0) or not (=9999) hicdif = ', hicdif 
    138116      ENDIF 
     117      ! 
    139118   END SUBROUTINE ice_run 
    140119 
  • trunk/NEMO/LIM_SRC/icestp.F90

    r420 r508  
    44   !!   Sea-Ice model : LIM Sea ice model time-stepping 
    55   !!====================================================================== 
     6   !! History :   1.0  !  99-11  (M. Imbard)  Original code 
     7   !!        !  01-03  (D. Ludicone, E. Durand, G. Madec) free surf. 
     8   !!   2.0  !  02-09  (G. Madec, C. Ethe)  F90: Free form and module 
     9   !!---------------------------------------------------------------------- 
    610#if defined key_ice_lim 
    711   !!---------------------------------------------------------------------- 
    812   !!   'key_ice_lim' :                                   Lim sea-ice model 
     13   !!---------------------------------------------------------------------- 
    914   !!---------------------------------------------------------------------- 
    1015   !!   ice_stp       : sea-ice model time-stepping 
     
    2126   USE taumod 
    2227   USE ice 
    23    USE iceini 
    2428   USE ocesbc 
    2529   USE lbclnk 
     
    3741   PRIVATE 
    3842 
    39    !! * Routine accessibility 
    40    PUBLIC ice_stp  ! called by step.F90 
     43   PUBLIC   ice_stp    ! called by step.F90 
    4144 
    4245   !! * Substitutions 
     
    4649   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)  
    4750   !! $Header$  
    48    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     51   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4952   !!----------------------------------------------------- 
    5053 
     
    6467      !!              - save the outputs  
    6568      !!              - save the outputs for restart when necessary 
    66       !! 
    67       !! History : 
    68       !!   1.0  !  99-11  (M. Imbard)  Original code 
    69       !!        !  01-03  (D. Ludicone, E. Durand, G. Madec) free surf. 
    70       !!   2.0  !  02-09  (G. Madec, C. Ethe)  F90: Free form and module 
    7169      !!---------------------------------------------------------------------- 
    72       !! * Arguments 
    73       INTEGER, INTENT( in ) ::   kt         ! ocean time-step index 
    74  
    75       !! * Local declarations 
    76       INTEGER   ::   ji, jj   ! dummy loop indices 
    77  
    78       REAL(wp) , DIMENSION(jpi,jpj)    :: & 
    79          zsss_io, zsss2_io, zsss3_io          ! tempory workspaces 
     70      INTEGER, INTENT(in)          ::   kt       ! ocean time-step index 
     71 
     72      INTEGER                      ::   ji, jj   ! dummy loop indices 
     73      REAL(wp), DIMENSION(jpi,jpj) ::   zsss_io, zsss2_io, zsss3_io          ! tempory workspaces 
    8074      !!---------------------------------------------------------------------- 
    8175 
     
    201195         ENDIF 
    202196 
    203          ! Ice model call 
    204          numit = numit + nfice  
     197         !                                                           !-----------------------! 
     198         CALL lim_rst_opn( kt )                                   ! Open Ice restart file ! 
     199         !                                                           !-----------------------! 
    205200 
    206201         !                                                           !--------------! 
    207          CALL lim_dyn                                                ! Ice dynamics !   ( rheology/dynamics ) 
     202         CALL lim_dyn( kt )                                          ! Ice dynamics !   ( rheology/dynamics ) 
    208203         !                                                           !--------------! 
    209204         IF(ln_ctl) THEN 
     
    214209 
    215210         !                                                           !---------------! 
    216          CALL lim_trp                                                ! Ice transport !  ( Advection/diffusion ) 
     211         CALL lim_trp( kt )                                          ! Ice transport !  ( Advection/diffusion ) 
    217212         !                                                           !---------------! 
    218213         IF(ln_ctl) THEN 
     
    222217 
    223218         !                                                           !-------------! 
    224          IF( ln_limdmp ) CALL lim_dmp(kt)                            ! Ice damping ! 
     219         IF( ln_limdmp ) CALL lim_dmp( kt )                          ! Ice damping ! 
    225220         !                                                           !-------------! 
    226221 
    227222         !                                                           !--------------------! 
    228          CALL lim_thd                                                ! Ice thermodynamics ! 
     223         CALL lim_thd( kt )                                          ! Ice thermodynamics ! 
    229224         !                                                           !--------------------! 
    230225         IF(ln_ctl) THEN 
     
    239234         !                                                           !------------------------------! 
    240235 
    241          IF( MOD( numit, ninfo ) == 0 .OR. ntmoy == 1 )  THEN        !-----------------! 
    242             CALL lim_dia                                             ! Ice Diagnostics ! 
     236         IF( MOD( kt + nfice -1, ninfo ) == 0 .OR. ntmoy == 1 )  THEN        !-----------------! 
     237            CALL lim_dia( kt )                                    ! Ice Diagnostics ! 
    243238         ENDIF                                                       !-----------------! 
    244239 
    245240         !                                                           !-------------! 
    246          CALL lim_wri                                                ! Ice outputs ! 
    247          !                                                           !-------------! 
    248  
    249          IF( MOD( numit, nstock ) == 0 .OR. numit == nlast ) THEN 
    250             !                                                        !------------------! 
    251             CALL lim_rst_write( numit )                              ! Ice restart file ! 
    252             !                                                        !------------------! 
    253          ENDIF 
     241         CALL lim_wri( kt )                                          ! Ice outputs ! 
     242         !                                                           !-------------! 
     243 
     244         !                                                           !------------------------! 
     245         IF( lrst_ice ) CALL lim_rst_write( kt )                  ! Write Ice restart file ! 
     246         !                                                           !------------------------! 
    254247 
    255248         ! Re-initialization of forcings 
     
    271264         dqla_ice(:,:) = 0.e0 
    272265#endif 
    273  
    274266      ENDIF 
    275  
     267      ! 
    276268   END SUBROUTINE ice_stp 
    277269 
  • trunk/NEMO/LIM_SRC/limdia.F90

    r247 r508  
    44   !!                      diagnostics of ice model  
    55   !!====================================================================== 
     6   !! History :   8.0  !  97-06  (Louvain-La-Neuve)  Original code 
     7   !!             8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module 
     8   !!             9.0  !  06-08  (S. Masson)  change frequency output control 
     9   !!------------------------------------------------------------------- 
    610#if defined key_ice_lim 
    711   !!---------------------------------------------------------------------- 
    812   !!   'key_ice_lim' :                                   LIM sea-ice model 
     13   !!---------------------------------------------------------------------- 
    914   !!---------------------------------------------------------------------- 
    1015   !!   lim_dia      : computation of the time evolution of keys var. 
    1116   !!   lim_dia_init : initialization and namelist read 
    1217   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    1418   USE phycst          !  
    1519   USE par_ice         ! ice parameters 
     
    1822   USE dom_ice         ! 
    1923   USE ice             ! 
    20    USE iceini          ! 
    2124   USE limistate       ! 
    2225   USE in_out_manager  ! I/O manager 
     
    2528   PRIVATE 
    2629 
    27    !! * Routine accessibility 
    28    PUBLIC lim_dia       ! called by ice_step 
    29  
    30    !! * Shared module variables 
    31    INTEGER, PUBLIC  ::  &  !: 
    32       ntmoy   = 1 ,     &  !: instantaneous values of ice evolution or averaging ntmoy 
    33       ninfo   = 1          !: frequency of ouputs on file ice_evolu in case of averaging 
    34  
    35    !! * Module variables 
     30   PUBLIC               lim_dia            ! called by ice_step 
     31   INTEGER, PUBLIC ::   ntmoy   = 1 ,   &  !: instantaneous values of ice evolution or averaging ntmoy 
     32      &                 ninfo   = 1        !: frequency of ouputs on file ice_evolu in case of averaging 
     33 
    3634   INTEGER, PARAMETER ::   &  ! Parameters for outputs to files "evolu" 
    3735      jpinfmx = 100         ,    &  ! maximum number of key variables 
     
    4644      naveg                ! number of step for accumulation before averaging 
    4745 
    48    CHARACTER(len=8) ::   & 
    49       fmtinf  = '1PE13.5 ' ! format of the output values   
    50    CHARACTER(len=30) ::   & 
    51       fmtw  ,           &  ! formats 
    52       fmtr  ,           &  ! ??? 
    53       fmtitr               ! ??? 
    54    CHARACTER(len=jpchsep), DIMENSION(jpinfmx) ::   & 
    55       titvar               ! title of key variables 
     46   CHARACTER(len= 8) ::   fmtinf  = '1PE13.5 ' ! format of the output values   
     47   CHARACTER(len=30) ::   fmtw  ,           &  ! formats 
     48      &                   fmtr  ,           &  ! ??? 
     49      &                   fmtitr               ! ??? 
     50   CHARACTER(len=jpchsep), DIMENSION(jpinfmx) ::   titvar               ! title of key variables 
    5651  
    57    REAL(wp) ::   & 
    58       epsi06 = 1.e-06      ! ??? 
    59    REAL(wp), DIMENSION(jpinfmx) ::  & 
    60       vinfom               ! temporary working space 
    61    REAL(wp), DIMENSION(jpi,jpj) ::   & 
    62       aire                 ! masked grid cell area 
     52   REAL(wp)                     ::   epsi06 = 1.e-06      ! ??? 
     53   REAL(wp), DIMENSION(jpinfmx) ::   vinfom               ! temporary working space 
     54   REAL(wp), DIMENSION(jpi,jpj) ::   aire                 ! masked grid cell area 
    6355 
    6456   !! * Substitutions 
     
    6759   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)  
    6860   !! $Header$  
    69    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     61   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    7062   !!---------------------------------------------------------------------- 
    7163 
    7264CONTAINS 
    7365 
    74    SUBROUTINE lim_dia 
     66   SUBROUTINE lim_dia( kt ) 
    7567      !!-------------------------------------------------------------------- 
    7668      !!                  ***  ROUTINE lim_dia  *** 
     
    7870      !! ** Purpose : Computation and outputs on file ice.evolu  
    7971      !!      the temporal evolution of some key variables 
     72      !!------------------------------------------------------------------- 
     73      INTEGER, INTENT(in) ::   kt     ! number of iteration 
    8074      !! 
    81       !! History : 
    82       !!   8.0  !  97-06  (Louvain-La-Neuve)  Original code 
    83       !!   8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module 
     75      INTEGER  ::   jv,ji, jj   ! dummy loop indices 
     76      INTEGER  ::   nv          ! indice of variable  
     77      REAL(wp) ::   zarea    , zldarea  ,    &  ! sea-ice and leads area 
     78         &          zextent15, zextent85,    &  ! sea-ice extent (15% and 85%) 
     79         &          zicevol  , zsnwvol  ,    &  ! sea-ice and snow volume volume 
     80         &          zicespd                     ! sea-ice velocity 
     81      REAL(wp), DIMENSION(jpinfmx) ::   vinfor  ! temporary working space  
    8482      !!------------------------------------------------------------------- 
    85       !! * Local variables 
    86        INTEGER  ::   jv,ji, jj   ! dummy loop indices 
    87        INTEGER  ::   nv          ! indice of variable  
    88        REAL(wp), DIMENSION(jpinfmx) ::  &  
    89           vinfor           ! temporary working space  
    90        REAL(wp) ::    & 
    91           zarea    ,    &  ! sea ice area 
    92           zldarea  ,    &  ! leads area 
    93           zextent15,    &  ! sea ice extent (15%) 
    94           zextent85,    &  ! sea ice extent (85%) 
    95           zicevol  ,    &  ! sea ice volume 
    96           zsnwvol  ,    &  ! snow volume over sea ice 
    97           zicespd          ! sea ice velocity 
    98        !!------------------------------------------------------------------- 
    99  
    100        IF( numit == nstart )   CALL lim_dia_init   ! initialisation of ice_evolu file       
    101  
    102        ! computation of key variables at each time step    
    103  
    104        nv = 1  
    105        vinfor(nv) = REAL( numit ) 
    106        nv = nv + 1 
    107        vinfor(nv) = nyear 
     83 
     84      IF( kt == nit000 )   CALL lim_dia_init   ! initialisation of ice_evolu file       
     85 
     86      ! computation of key variables at each time step    
     87 
     88      nv = 1  
     89      vinfor(nv) = REAL( kt + nfice - 1 ) 
     90      nv = nv + 1 
     91      vinfor(nv) = nyear 
    10892  
    109        DO jv = nbvt + 1, nvinfo 
    110           vinfor(jv) = 0.e0 
    111        END DO 
    112  
    113        zextent15 = 0.e0 
    114        zextent85 = 0.e0 
    115        ! variables in northern Hemis 
    116        DO jj = njeq, jpjm1 
    117           DO ji = fs_2, fs_jpim1   ! vector opt. 
    118              IF( tms(ji,jj) == 1 ) THEN 
    119                 zarea = ( 1.0 - frld(ji,jj) ) * aire(ji,jj) 
    120                 IF (frld(ji,jj) <= 0.15 ) zextent15 = aire(ji,jj)     
    121                 IF (frld(ji,jj) <= 0.85 ) zextent85 = aire(ji,jj)    
    122                 zldarea = zarea   / MAX( ( 1 - frld(ji,jj) ) , epsi06 ) 
    123                 zicevol = zarea   * hicif(ji,jj) 
    124                 zsnwvol = zarea   * hsnif(ji,jj) 
    125                 zicespd = zicevol * ( u_ice(ji,jj) * u_ice(ji,jj)   & 
    126                    &                + v_ice(ji,jj) * v_ice(ji,jj) ) 
    127                 vinfor(nv+ 1) = vinfor(nv+ 1) + zarea 
    128                 vinfor(nv+ 3) = vinfor(nv+ 3) + zextent15 
    129                 vinfor(nv+ 5) = vinfor(nv+ 5) + zextent85 
    130                 vinfor(nv+ 7) = vinfor(nv+ 7) + zldarea 
    131                 vinfor(nv+ 9) = vinfor(nv+ 9) + zicevol 
    132                 vinfor(nv+11) = vinfor(nv+11) + zsnwvol 
    133                 vinfor(nv+13) = vinfor(nv+13) + zicespd 
    134              ENDIF 
    135           END DO 
    136        END DO 
    137        vinfor(nv+13) = SQRT( vinfor(nv+13) / MAX( vinfor(nv+9) , epsi06 ) ) 
     93      DO jv = nbvt + 1, nvinfo 
     94         vinfor(jv) = 0.e0 
     95      END DO 
     96 
     97      zextent15 = 0.e0 
     98      zextent85 = 0.e0 
     99      ! variables in northern Hemis 
     100      DO jj = njeq, jpjm1 
     101         DO ji = fs_2, fs_jpim1   ! vector opt. 
     102            IF( tms(ji,jj) == 1 ) THEN 
     103               zarea = ( 1.0 - frld(ji,jj) ) * aire(ji,jj) 
     104               IF (frld(ji,jj) <= 0.15 ) zextent15 = aire(ji,jj)     
     105               IF (frld(ji,jj) <= 0.85 ) zextent85 = aire(ji,jj)    
     106               zldarea = zarea   / MAX( ( 1 - frld(ji,jj) ) , epsi06 ) 
     107               zicevol = zarea   * hicif(ji,jj) 
     108               zsnwvol = zarea   * hsnif(ji,jj) 
     109               zicespd = zicevol * ( u_ice(ji,jj) * u_ice(ji,jj)   & 
     110                  &                + v_ice(ji,jj) * v_ice(ji,jj) ) 
     111               vinfor(nv+ 1) = vinfor(nv+ 1) + zarea 
     112               vinfor(nv+ 3) = vinfor(nv+ 3) + zextent15 
     113               vinfor(nv+ 5) = vinfor(nv+ 5) + zextent85 
     114               vinfor(nv+ 7) = vinfor(nv+ 7) + zldarea 
     115               vinfor(nv+ 9) = vinfor(nv+ 9) + zicevol 
     116               vinfor(nv+11) = vinfor(nv+11) + zsnwvol 
     117               vinfor(nv+13) = vinfor(nv+13) + zicespd 
     118            ENDIF 
     119         END DO 
     120      END DO 
     121      vinfor(nv+13) = SQRT( vinfor(nv+13) / MAX( vinfor(nv+9) , epsi06 ) ) 
    138122 
    139123 
     
    170154     
    171155       ! oututs on file ice_evolu     
    172        IF( MOD( numit , ninfo ) == 0 ) THEN 
     156       IF( MOD( kt + nfice - 1, ninfo ) == 0 ) THEN 
    173157          WRITE(numevo_ice,fmtw) ( titvar(jv), vinfom(jv)/naveg, jv = 1, nvinfo ) 
    174158          naveg = 0 
     
    177161          END DO 
    178162       ENDIF 
    179    
     163       ! 
    180164    END SUBROUTINE lim_dia 
    181165  
     
    189173       !! 
    190174       !! ** input   : Namelist namicedia 
    191        !! 
    192        !! history : 
    193        !!  8.5  ! 03-08 (C. Ethe) original code 
    194175       !!------------------------------------------------------------------- 
     176       CHARACTER(len=jpchinf) ::   titinf 
     177       INTEGER  ::   jv            ! dummy loop indice 
     178       INTEGER  ::   ntot , ndeb , irecl 
     179       INTEGER  ::   nv            ! indice of variable  
     180       REAL(wp) ::   zxx0, zxx1    ! temporary scalars 
     181 
    195182       NAMELIST/namicedia/fmtinf, nfrinf, ninfo, ntmoy 
    196  
    197        INTEGER  ::   jv   ,     &  ! dummy loop indice 
    198           &          ntot ,     & 
    199           &          ndeb ,     & 
    200           &          irecl 
    201  
    202        INTEGER  ::   nv            ! indice of variable  
    203  
    204        REAL(wp) ::   zxx0, zxx1    ! temporary scalars 
    205  
    206        CHARACTER(len=jpchinf) ::   titinf 
    207183       !!------------------------------------------------------------------- 
    208184 
     
    210186       REWIND ( numnam_ice ) 
    211187       READ   ( numnam_ice  , namicedia ) 
     188        
    212189       IF(lwp) THEN 
    213190          WRITE(numout,*) 
     
    228205       nv = nv + 1 
    229206       titvar(nv) = 'T yr'  ! time step in years 
    230        nv = nv + 1 
    231  
     207        
    232208       nbvt = nv - 1 
    233209 
    234        titvar(nv) = 'AEFN' ! sea ice area in the northern Hemisp.(10^12 km2) 
    235        nv = nv + 1 
    236        titvar(nv) = 'AEFS' ! sea ice area in the southern Hemisp.(10^12 km2) 
    237        nv = nv + 1 
    238        titvar(nv) = 'A15N'  ! sea ice extent (15%) in the northern Hemisp.(10^12 km2) 
    239        nv = nv + 1 
    240        titvar(nv) = 'A15S'  ! sea ice extent (15%) in the southern Hemisp.(10^12 km2) 
    241        nv = nv + 1 
    242        titvar(nv) = 'A85N'  ! sea ice extent (85%) in the northern Hemisp.(10^12 km2) 
    243        nv = nv + 1 
    244        titvar(nv) = 'A85S'  ! sea ice extent (85%) in the southern Hemisp.(10^12 km2) 
    245        nv = nv + 1 
    246        titvar(nv) = 'ALEN'  ! leads area in the northern Hemisp.(10^12 km2) 
    247        nv = nv + 1 
    248        titvar(nv) = 'ALES'  ! leads area in the southern Hemisp.(10^12 km2) 
    249        nv = nv + 1 
    250        titvar(nv) = 'VOLN'  ! sea ice volume in the northern Hemisp.(10^3 km3) 
    251        nv = nv + 1 
    252        titvar(nv) = 'VOLS'  ! sea ice volume in the southern Hemisp.(10^3 km3) 
    253        nv = nv + 1 
    254        titvar(nv) = 'VONN'  ! snow volume over sea ice in the northern Hemisp.(10^3 km3) 
    255        nv = nv + 1 
    256        titvar(nv) = 'VONS'  ! snow volume over sea ice in the southern Hemisp.(10^3 km3) 
    257        nv = nv + 1 
    258        titvar(nv) = 'ECGN'  ! mean sea ice velocity in the northern Hemisp.(m/s) 
    259        nv = nv + 1 
    260        titvar(nv) = 'ECGS'  ! mean sea ice velocity in the southern Hemisp.(m/s) 
     210       nv = nv + 1   ;   titvar(nv) = 'AEFN' ! sea ice area in the northern Hemisp.(10^12 km2) 
     211       nv = nv + 1   ;   titvar(nv) = 'AEFS' ! sea ice area in the southern Hemisp.(10^12 km2) 
     212       nv = nv + 1   ;   titvar(nv) = 'A15N'  ! sea ice extent (15%) in the northern Hemisp.(10^12 km2) 
     213       nv = nv + 1   ;   titvar(nv) = 'A15S'  ! sea ice extent (15%) in the southern Hemisp.(10^12 km2) 
     214       nv = nv + 1   ;   titvar(nv) = 'A85N'  ! sea ice extent (85%) in the northern Hemisp.(10^12 km2) 
     215       nv = nv + 1   ;   titvar(nv) = 'A85S'  ! sea ice extent (85%) in the southern Hemisp.(10^12 km2) 
     216       nv = nv + 1   ;   titvar(nv) = 'ALEN'  ! leads area in the northern Hemisp.(10^12 km2) 
     217       nv = nv + 1   ;   titvar(nv) = 'ALES'  ! leads area in the southern Hemisp.(10^12 km2) 
     218       nv = nv + 1   ;   titvar(nv) = 'VOLN'  ! sea ice volume in the northern Hemisp.(10^3 km3) 
     219       nv = nv + 1   ;   titvar(nv) = 'VOLS'  ! sea ice volume in the southern Hemisp.(10^3 km3) 
     220       nv = nv + 1   ;   titvar(nv) = 'VONN'  ! snow volume over sea ice in the northern Hemisp.(10^3 km3) 
     221       nv = nv + 1   ;   titvar(nv) = 'VONS'  ! snow volume over sea ice in the southern Hemisp.(10^3 km3) 
     222       nv = nv + 1   ;   titvar(nv) = 'ECGN'  ! mean sea ice velocity in the northern Hemisp.(m/s) 
     223       nv = nv + 1   ;   titvar(nv) = 'ECGS'  ! mean sea ice velocity in the southern Hemisp.(m/s) 
    261224 
    262225       nvinfo = nv 
    263226 
    264227       ! Definition et Ecriture de l'entete : nombre d'enregistrements  
    265        ndeb   = ( nstart - 1 ) / ninfo 
    266        IF( nstart == 1 ) ndeb = -1 
    267  
    268        nferme = ( nstart - 1 + nitrun) / ninfo 
     228       ndeb   = ( nit000 - 1 + nfice - 1 ) / ninfo 
     229       IF( nit000 - 1 + nfice == 1 ) ndeb = -1 
     230 
     231       nferme = ( nitend + nfice - 1 ) / ninfo ! nit000 - 1 + nfice - 1 + nitend - nit000 + 1 
    269232       ntot   = nferme - ndeb 
    270233       ndeb   = ninfo * ( 1 + ndeb ) 
     
    288251 
    289252       !- ecriture de 2 lignes de titre : 
    290        WRITE(numevo_ice,'(A,I8,A,I8,A,I5)')                                      & 
     253       WRITE(numevo_ice,'(A,I8,A,I8,A,I5)')                 & 
    291254          'Evolution chronologique - Experience '//cexper   & 
    292255          //'   de', ndeb, ' a', nferme, ' pas', ninfo 
     
    3082711000   FORMAT( 3(A20),4(1x,I6) ) 
    3092721111   FORMAT( 3(F7.1,1X,F7.3,1X),I3,A )   
    310  
     273      ! 
    311274    END SUBROUTINE lim_dia_init 
    312275 
  • trunk/NEMO/LIM_SRC/limdmp.F90

    r477 r508  
    44   !!  Ice model : restoring Ice thickness and Fraction leads 
    55   !!====================================================================== 
    6 #if defined key_ice_lim && defined key_tradmp 
     6   !! History :   2.0  !  04-04 (S. Theetten) Original code 
    77   !!---------------------------------------------------------------------- 
    8    !!   'key_ice_lim' :                                   LIM sea-ice model 
     8#if defined key_ice_lim   &&   defined key_tradmp 
     9   !!---------------------------------------------------------------------- 
     10   !!   'key_ice_lim'  AND                                LIM sea-ice model 
     11   !!   'key_tradmp'                                                Damping 
     12   !!---------------------------------------------------------------------- 
    913   !!---------------------------------------------------------------------- 
    1014   !!   lim_dmp      : ice model damping 
    1115   !!---------------------------------------------------------------------- 
    12    !! * Modules used 
    1316   USE in_out_manager  ! I/O manager 
     17   USE phycst          ! physical constants 
    1418   USE ice 
    1519   USE ice_oce 
     
    1822   USE oce 
    1923   USE daymod          ! calendar 
     24   USE iom 
    2025    
    2126   IMPLICIT NONE 
    2227   PRIVATE 
    2328 
    24    !! * Routine accessibility 
    25    PUBLIC lim_dmp     ! called by ice_step 
     29   PUBLIC   lim_dmp     ! called by ice_step 
    2630    
    27    !! * Shared module variables 
    28    CHARACTER (len=38) ::   & 
    29       cl_icedata = 'ice_damping_ATL4.nc' 
    30    INTEGER ::   & 
    31         nice1      ,   &  ! first record used 
    32         nice2             ! second record used 
    33     
    34     REAL(wp), DIMENSION(jpi,jpj,2) ::   & 
    35          hicif_data ,   & ! ice thickness data at two consecutive times 
    36          frld_data        ! fraction lead data at two consecutive times 
    37  
    38     REAL(wp), DIMENSION(jpi,jpj) ::   & 
    39          hicif_dta ,   &  ! ice thickness at a given time 
    40          frld_dta         ! fraction lead at a given time 
     31   INTEGER                        ::   nice1, nice2,  &  ! first and second record used 
     32      &                                inumice_dmp       ! logical unit for ice variables (damping) 
     33   REAL(wp), DIMENSION(jpi,jpj)   ::   hicif_dta  ,   &  ! ice thickness at a given time 
     34      &                                frld_dta          ! fraction lead at a given time 
     35   REAL(wp), DIMENSION(jpi,jpj,2) ::   hicif_data ,   &  ! ice thickness data at two consecutive times 
     36      &                                frld_data         ! fraction lead data at two consecutive times 
    4137 
    4238   !! * Substitution 
    4339#  include "vectopt_loop_substitute.h90" 
    4440   !!---------------------------------------------------------------------- 
    45    !!   LIM 2.0 , UCL-LOCEAN-IPSL  (2005) 
     41   !!   LIM 2.0 , UCL-LOCEAN-IPSL  (2006) 
    4642   !! $Header$ 
    47    !! This software is governed by the CeCILL licence see !modipsl/doc/NEMO_CeCILL.txt 
     43   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4844   !!---------------------------------------------------------------------- 
    4945 
     
    5854      !! 
    5955      !! ** method  : the key_tradmp must be used to compute resto(:,:) coef. 
    60       !!      
    61       !! ** action : 
    62       !! 
    63       !! History : 
    64       !! 
    65       !!   2.0  !  04-04 (S. Theetten) Original 
    6656      !!--------------------------------------------------------------------- 
    67       !! * Arguments 
    68       INTEGER, INTENT( in ) ::   kt     ! ocean time-step 
    69  
    70       !! * Local Variables 
    71       INTEGER  ::   ji, jj         ! dummy loop indices 
     57      INTEGER, INTENT(in) ::   kt     ! ocean time-step 
     58      ! 
     59      INTEGER             ::   ji, jj         ! dummy loop indices 
    7260      !!--------------------------------------------------------------------- 
    73      
    74       CALL dta_lim(kt) 
     61      ! 
     62      CALL dta_lim( kt ) 
    7563 
    7664      DO jj = 2, jpjm1 
    7765         DO ji = fs_2, fs_jpim1   ! vector opt. 
    78  
    79             hicif(ji,jj) = hicif(ji,jj) - rdt_ice * resto(ji,jj,1) * ( hicif(ji,jj) -  hicif_dta(ji,jj)) 
    80             frld(ji,jj)  = frld(ji,jj)  - rdt_ice * resto(ji,jj,1) * ( frld(ji,jj)  - frld_dta(ji,jj))   
    81  
    82          ENDDO 
    83       ENDDO 
    84  
     66            hicif(ji,jj) = hicif(ji,jj) - rdt_ice * resto(ji,jj,1) * ( hicif(ji,jj) - hicif_dta(ji,jj) ) 
     67            frld(ji,jj)  = frld (ji,jj) - rdt_ice * resto(ji,jj,1) * ( frld(ji,jj)  - frld_dta (ji,jj) )   
     68         END DO 
     69      END DO 
     70      ! 
    8571   END SUBROUTINE lim_dmp 
    86  
    8772 
    8873 
     
    10186      !!      two monthly values. 
    10287      !!       
    103       !! 
    10488      !! ** Action  :   define hicif_dta and frld_dta arrays at time-step kt 
    105       !! 
    106       !! History : 
    107       !!   2.0   !   04-04 (S. Theetten) Original 
    10889      !!---------------------------------------------------------------------- 
    109       !! * Modules used 
    110       USE ioipsl 
    111  
    112       !! * Arguments 
    113       INTEGER, INTENT( in ) ::   kt     ! ocean time-step 
    114  
    115       !! * Local declarations 
    116       INTEGER, PARAMETER ::   jpmois = 12       ! number of month 
    117       
    118       INTEGER ::   & 
    119          imois, iman, itime ,    &  ! temporary integers 
    120          i15, ipi, ipj, ipk         !    "          " 
    121  
    122       INTEGER, DIMENSION(jpmois) ::   istep 
    123       REAL(wp) ::   zxy, zdate0, zdt 
    124       REAL(wp), DIMENSION(jpi,jpj) ::   zlon,zlat 
    125       REAL(wp), DIMENSION(jpk) ::   zlev 
     90      INTEGER, INTENT(in) ::   kt     ! ocean time-step 
     91      ! 
     92      INTEGER  ::   imois, iman, i15          ! temporary integers 
     93      REAL(wp) ::   zxy 
    12694      !!---------------------------------------------------------------------- 
    12795 
    12896      ! 0. Initialization 
    12997      ! ----------------- 
    130       iman  = jpmois 
     98      iman  = INT( raamo ) 
     99!!! better but change the results     i15 = INT( 2*FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) ) 
    131100      i15   = nday / 16 
    132101      imois = nmonth + i15 - 1 
    133       IF( imois == 0 )   imois = iman 
    134  
    135       itime = jpmois 
    136       ipi=jpiglo 
    137       ipj=jpjglo 
    138       ipk=1 
    139       zdt=rdt 
    140  
    141       ! 1. First call kt=nit000 
     102      IF( imois == 0 ) imois = iman 
     103       
     104      ! 1. First call kt=nit000: Initialization and Open 
    142105      ! ----------------------- 
    143  
    144106      IF( kt == nit000 ) THEN 
    145107         nice1 = 0 
     
    149111         IF(lwp) WRITE(numout,*) '             NetCDF FORMAT' 
    150112         IF(lwp) WRITE(numout,*) 
    151           
    152113         ! open file 
    153           
    154          CALL flinopen( TRIM(cl_icedata), mig(1), nlci , mjg(1),  nlcj, .FALSE.,  & 
    155             &           ipi, ipj, ipk, zlon, zlat, zlev, itime, istep, zdate0, zdt, numice_dmp ) 
    156  
    157           ! title, dimensions and tests 
    158          IF( itime /= jpmois ) THEN 
    159             IF(lwp) THEN 
    160                WRITE(numout,*) 
    161                WRITE(numout,*) 'problem with time coordinates' 
    162                WRITE(numout,*) ' itime ',itime,' jpmois ',jpmois 
    163             ENDIF 
    164             STOP 'dta_lim' 
    165          ENDIF 
    166          IF( ipi /= jpidta .OR. ipj /= jpjdta ) THEN 
    167             IF(lwp) THEN 
    168                WRITE(numout,*) 
    169                WRITE(numout,*) 'problem with dimensions' 
    170                WRITE(numout,*) ' ipi ',ipi,' jpidta ',jpidta 
    171                WRITE(numout,*) ' ipj ',ipj,' jpjdta ',jpjdta 
    172             ENDIF 
    173             STOP 'dta_lim' 
    174          ENDIF 
    175          IF(lwp) WRITE(numout,*) itime,istep,zdate0,zdt,numice_dmp 
    176  
     114         CALL iom_open( 'ice_damping_ATL4.nc', inumice_dmp ) 
    177115      ENDIF 
    178116 
    179117 
    180118      ! 2. Read monthly file 
    181       ! ------------------- 
    182  
     119      ! -------------------- 
    183120      IF( ( kt == nit000 ) .OR. imois /= nice1 ) THEN 
    184  
     121         ! 
    185122         ! Calendar computation 
    186           
    187123         nice1 = imois        ! first file record used  
    188124         nice2 = nice1 + 1    ! last  file record used 
    189125         nice1 = MOD( nice1, iman ) 
     126         nice2 = MOD( nice2, iman ) 
    190127         IF( nice1 == 0 )   nice1 = iman 
    191          nice2 = MOD( nice2, iman ) 
    192128         IF( nice2 == 0 )   nice2 = iman 
    193129         IF(lwp) WRITE(numout,*) 'first record file used nice1 ', nice1 
     
    195131          
    196132         ! Read monthly ice thickness Levitus  
     133         CALL iom_get( inumice_dmp, jpdom_data, 'iicethic', hicif_data(:,:,1), nice1 )  
     134         CALL iom_get( inumice_dmp, jpdom_data, 'iicethic', hicif_data(:,:,2), nice2 )  
    197135          
    198          CALL flinget( numice_dmp, 'iicethic', jpidta, jpjdta, jpk,  & 
    199             &          jpmois, nice1, nice1, mig(1), nlci, mjg(1), nlcj, hicif_data(1:nlci,1:nlcj,1) ) 
    200          CALL flinget( numice_dmp, 'iicethic', jpidta, jpjdta, jpk,  & 
    201             &          jpmois, nice2, nice2, mig(1), nlci, mjg(1), nlcj, hicif_data(1:nlci,1:nlcj,2) ) 
    202           
    203          IF(lwp) WRITE(numout,*) 
    204          IF(lwp) WRITE(numout,*) ' read ice thickness ok' 
    205          IF(lwp) WRITE(numout,*) 
    206  
    207136         ! Read monthly ice thickness Levitus  
    208           
    209          CALL flinget( numice_dmp, 'ileadfra', jpidta, jpjdta, jpk,  & 
    210             &          jpmois, nice1, nice1, mig(1), nlci, mjg(1), nlcj, frld_data(1:nlci,1:nlcj,1) ) 
    211          CALL flinget( numice_dmp, 'ileadfra', jpidta, jpjdta, jpk,  & 
    212             &          jpmois, nice2, nice2, mig(1), nlci, mjg(1), nlcj, frld_data(1:nlci,1:nlcj,2) ) 
     137         CALL iom_get( inumice_dmp, jpdom_data, 'ileadfra', frld_data(:,:,1), nice1 )  
     138         CALL iom_get( inumice_dmp, jpdom_data, 'ileadfra', frld_data(:,:,2), nice2 )  
    213139          
    214140         ! The fraction lead read in the file is in fact the  
     
    216142         frld_data = 1 - frld_data           
    217143          
    218          IF(lwp) WRITE(numout,*) 
    219          IF(lwp) WRITE(numout,*) ' read fraction lead ok' 
    220          IF(lwp) WRITE(numout,*) 
    221  
    222  
    223144         IF(lwp) THEN 
     145            WRITE(numout,*) 
    224146            WRITE(numout,*) ' Ice thickness month ', nice1,' and ', nice2 
    225147            WRITE(numout,*) 
     
    235157         ! 2. At every time step compute ice thickness and fraction lead data 
    236158         ! ------------------------------------------------------------------ 
    237           
    238159         zxy = FLOAT( nday + 15 - 30 * i15 ) / 30. 
    239160         hicif_dta(:,:) = (1.-zxy) * hicif_data(:,:,1) + zxy * hicif_data(:,:,2) 
     
    241162 
    242163      ENDIF 
    243  
    244  
     164       
     165      IF( kt == nitend )   CALL iom_close( inumice_dmp ) 
     166      ! 
    245167   END SUBROUTINE dta_lim 
    246168 
     
    250172   !!---------------------------------------------------------------------- 
    251173CONTAINS 
    252    SUBROUTINE lim_dmp(kt)        ! Dummy routine 
     174   SUBROUTINE lim_dmp( kt )        ! Dummy routine 
    253175      WRITE(*,*) 'lim_dmp: You should not see this print! error? ', kt 
    254176   END SUBROUTINE lim_dmp 
     
    256178 
    257179   !!====================================================================== 
    258  
    259180END MODULE limdmp 
  • trunk/NEMO/LIM_SRC/limdyn.F90

    r288 r508  
    4242CONTAINS 
    4343 
    44    SUBROUTINE lim_dyn 
     44   SUBROUTINE lim_dyn( kt ) 
    4545      !!------------------------------------------------------------------- 
    4646      !!               ***  ROUTINE lim_dyn  *** 
     
    5858      !!   2.0  !  02-08  (C. Ethe, G. Madec)  F90, mpp 
    5959      !!--------------------------------------------------------------------- 
    60       !! * Loal variables 
     60      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     61 
    6162      INTEGER ::   ji, jj             ! dummy loop indices 
    6263      INTEGER ::   i_j1, i_jpj        ! Starting/ending j-indices for rheology 
     
    7374      !!--------------------------------------------------------------------- 
    7475 
    75       IF( numit == nstart  )   CALL lim_dyn_init   ! Initialization (first time-step only) 
     76      IF( kt == nit000  )   CALL lim_dyn_init   ! Initialization (first time-step only) 
    7677       
    7778      IF ( ln_limdyn ) THEN 
  • trunk/NEMO/LIM_SRC/limistate.F90

    r474 r508  
    44   !!              Initialisation of diagnostics ice variables 
    55   !!====================================================================== 
     6   !! History :   2.0  !  01-04  (C. Ethe, G. Madec)  Original code 
     7   !!                  !  04-04  (S. Theetten) initialization from a file 
     8   !!                  !  06-07  (S. Masson)  IOM to read the restart 
     9   !!-------------------------------------------------------------------- 
    610#if defined key_ice_lim 
    711   !!---------------------------------------------------------------------- 
    812   !!   'key_ice_lim' :                                   LIM sea-ice model 
     13   !!---------------------------------------------------------------------- 
    914   !!---------------------------------------------------------------------- 
    1015   !!   lim_istate      :  Initialisation of diagnostics ice variables 
    1116   !!   lim_istate_init :  initialization of ice state and namelist read 
    1217   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    1418   USE phycst 
    1519   USE ocfzpt 
    16    USE oce             ! dynamics and tracers variables 
    17    USE dom_oce 
     20   USE oce             ! dynamics and tracers variables      !!gm used??? 
     21   USE dom_oce                                                     !!gm used??? 
    1822   USE par_ice         ! ice parameters 
    1923   USE ice_oce         ! ice variables 
     24   USE dom_ice 
     25   USE ice             ! ??? 
     26   USE lbclnk 
     27   USE ice 
     28   USE iom 
    2029   USE in_out_manager 
    21    USE dom_ice 
    22    USE ice 
    23    USE lbclnk 
    2430 
    2531   IMPLICIT NONE 
    2632   PRIVATE 
    2733 
    28    !! * Accessibility 
    2934   PUBLIC lim_istate      ! routine called by lim_init.F90 
    3035 
    31    !! * Module variables 
    32    REAL(wp) ::           & !!! ** init namelist (namiceini) ** 
     36   REAL(wp) ::           &  !!! ** init namelist (namiceini) ** 
    3337      ttest  = 2.0  ,    &  ! threshold water temperature for initial sea ice 
    3438      hninn  = 0.5  ,    &  ! initial snow thickness in the north 
     
    4347      zone    = 1.e0 
    4448   !!---------------------------------------------------------------------- 
    45    !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)  
     49   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2006)  
    4650   !! $Header$  
    47    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     51   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4852   !!---------------------------------------------------------------------- 
    4953 
     
    5862      !! ** Method  :   restart from a state defined in a binary file 
    5963      !!                or from arbitrary sea-ice conditions 
    60       !! 
    61       !! History : 
    62       !!   2.0  !  01-04  (C. Ethe, G. Madec)  Original code 
    63       !!        !  04-04  (S. Theetten) initialization from a file 
    6464      !!-------------------------------------------------------------------- 
    65       !! * Local variables 
    66       INTEGER  ::   ji, jj, jk   ! dummy loop indices 
    67       REAL(wp) ::   zidto,    &  ! temporary scalar 
    68          zs0, ztf, zbin 
    69       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    70          ztn 
     65      INTEGER  ::   ji, jj, jk                ! dummy loop indices 
     66      REAL(wp) ::   zidto, zs0, ztf, zbin     ! temporary scalar 
     67      REAL(wp), DIMENSION(jpi,jpj) ::   ztn   ! workspace 
    7168      !-------------------------------------------------------------------- 
    7269 
    73   
    74       CALL lim_istate_init     !  reading the initials parameters of the ice 
     70       CALL lim_istate_init     !  reading the initials parameters of the ice 
    7571 
    7672      !-- Initialisation of sst,sss,u,v do i=1,jpi 
     
    203199      CALL lbc_lnk( qstoif , 'T', 1. ) 
    204200      CALL lbc_lnk( sss_io , 'T', 1. ) 
    205  
     201      ! 
    206202   END SUBROUTINE lim_istate 
    207203 
     
    220216      !! 
    221217      !! ** input   :   Namelist namiceini 
    222       !! 
    223       !! history 
    224       !!  8.5  ! 03-08 (C. Ethe) original code 
    225       !!  9.0  ! 04-04 (S. Theetten) read a file 
    226       !!------------------------------------------------------------------- 
    227       !! * Modules used 
    228       USE ice 
    229       USE ioipsl 
     218      !!------------------------------------------------------------------- 
     219      INTEGER :: inum_ice 
    230220 
    231221      NAMELIST/namiceini/ ln_limini, ln_limdmp, ttest, hninn, hginn, alinn, & 
    232222         &                hnins, hgins, alins 
    233223      !!------------------------------------------------------------------- 
    234       !! local declaration 
    235       INTEGER, PARAMETER ::   jpmois=1 
    236        
    237       INTEGER ::                   & 
    238            itime, ipi, ipj, ipk  , & ! temporary integers 
    239            inum_ice 
    240        
    241       INTEGER ::  istep(jpmois) 
    242        
    243       REAL(wp) ::   zdate0, zdt 
    244       REAL(wp), DIMENSION(jpi,jpj) ::   zlon, zlat 
    245       REAL(wp), DIMENSION(3) ::   zlev 
    246        
    247       CHARACTER (len=32) :: cl_icedata 
    248        
    249       LOGICAL :: llbon 
    250       !!------------------------------------------------------------------- 
    251224       
    252225      ! Read Namelist namiceini  
    253  
    254226      REWIND ( numnam_ice ) 
    255227      READ   ( numnam_ice , namiceini ) 
     
    272244      IF( ln_limini ) THEN                      ! Ice initialization using input file 
    273245 
    274          cl_icedata = 'Ice_initialization.nc' 
    275          INQUIRE( FILE=cl_icedata, EXIST=llbon ) 
    276          IF( llbon ) THEN 
     246         CALL iom_open( 'Ice_initialization.nc', inum_ice ) 
     247 
     248         IF( inum_ice > 0 ) THEN 
    277249            IF(lwp) THEN 
    278250               WRITE(numout,*) ' ' 
    279                WRITE(numout,*) 'lim_istate_init : ice state initialization with : ',cl_icedata 
     251               WRITE(numout,*) 'lim_istate_init : ice state initialization with : Ice_initialization.nc' 
    280252               WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    281253               WRITE(numout,*) '         Ice state initialization using input file    ln_limini  = ', ln_limini 
     
    284256            ENDIF 
    285257             
    286             itime = 1 
    287             ipi=jpiglo 
    288             ipj=jpjglo 
    289             ipk=1 
    290             zdt=rdt 
     258            CALL iom_get( inum_ice, jpdom_data, 'sst'  , sst_ini(:,:) )         
     259            CALL iom_get( inum_ice, jpdom_data, 'sss'  , sss_ini(:,:) )        
     260            CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif  (:,:) )       
     261            CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif  (:,:) )       
     262            CALL iom_get( inum_ice, jpdom_data, 'frld' , frld   (:,:) )      
     263            CALL iom_get( inum_ice, jpdom_data, 'ts'   , sist   (:,:) ) 
     264            CALL iom_get( inum_ice, jpdom_unknown, 'tbif', tbif(:,:,:),   & 
     265                 &        kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,jplayersp1 /) ) 
     266 
     267            CALL iom_close( inum_ice) 
    291268             
    292             CALL flinopen( TRIM(cl_icedata), mig(1), nlci, mjg(1), nlcj, .FALSE., & 
    293                &           ipi, ipj, ipk, zlon, zlat, zlev, itime, istep, zdate0, zdt, inum_ice ) 
    294              
    295             CALL flinget( inum_ice, 'sst', jpidta, jpjdta, 1,  & 
    296                &          jpmois, 1, 0, mig(1), nlci, mjg(1), nlcj, sst_ini(1:nlci,1:nlcj) ) 
    297              
    298             CALL flinget( inum_ice, 'sss', jpidta, jpjdta, 1,  & 
    299                &          jpmois, 1, 0, mig(1), nlci, mjg(1), nlcj, sss_ini(1:nlci,1:nlcj) ) 
    300              
    301             CALL flinget( inum_ice, 'hicif', jpidta, jpjdta, 1,  & 
    302                &          jpmois, 1, 0, mig(1), nlci, mjg(1), nlcj, hicif(1:nlci,1:nlcj) ) 
    303              
    304             CALL flinget( inum_ice, 'hsnif', jpidta, jpjdta, 1,  & 
    305                &          jpmois, 1, 0, mig(1), nlci, mjg(1), nlcj, hsnif(1:nlci,1:nlcj) ) 
    306              
    307             CALL flinget( inum_ice, 'frld', jpidta, jpjdta, 1,  & 
    308                &          jpmois, 1, 0, mig(1), nlci, mjg(1), nlcj, frld(1:nlci,1:nlcj) ) 
    309              
    310             CALL flinget( inum_ice, 'ts', jpidta, jpjdta, 1,  & 
    311                &          jpmois, 1, 0, mig(1), nlci, mjg(1), nlcj, sist(1:nlci,1:nlcj) ) 
    312              
    313             CALL flinclo( inum_ice) 
    314              
    315             itime = 1 
    316             ipi=jpiglo 
    317             ipj=jpjglo 
    318             ipk=jplayersp1 
    319              
    320             CALL flinopen( TRIM(cl_icedata), mig(1), nlci, mjg(1), nlcj, .FALSE.,  & 
    321                &           ipi, ipj, ipk, zlon, zlat, zlev, itime, istep, zdate0, zdt, inum_ice ) 
    322              
    323             CALL flinget( inum_ice, 'tbif', jpidta, jpjdta, ipk,  & 
    324                &          jpmois, 1, 0, mig(1), nlci, mjg(1), nlcj, tbif(1:nlci,1:nlcj,1:ipk) ) 
    325              
    326             CALL flinclo( inum_ice) 
    327              
    328          ELSE 
    329             WRITE(ctmp1,*) '            ',cl_icedata, ' not found !' 
    330             CALL ctl_stop( ctmp1 ) 
    331269         ENDIF 
    332270      ENDIF 
    333  
     271      ! 
    334272   END SUBROUTINE lim_istate_init 
    335273 
  • trunk/NEMO/LIM_SRC/limrst.F90

    r473 r508  
    44   !! Ice restart :  write the ice restart file 
    55   !!====================================================================== 
     6   !! History :  2.0  !  01-04  (C. Ethe, G. Madec)  Original code 
     7   !!                 !  06-07  (S. Masson)  use IOM for restart read/write 
     8   !!---------------------------------------------------------------------- 
    69#if defined key_ice_lim 
    710   !!---------------------------------------------------------------------- 
    811   !!   'key_ice_lim' :                                   LIM sea-ice model 
    912   !!---------------------------------------------------------------------- 
    10    !!   lim_rst_write   : write of the restart file  
    11    !!   lim_rst_read    : read  the restart file  
    12    !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    14    USE in_out_manager 
     13   !!---------------------------------------------------------------------- 
     14   !!   lim_rst_opn   : open ice restart file 
     15   !!   lim_rst_write : write of the ice restart file  
     16   !!   lim_rst_read  : read  the ice restart file  
     17   !!---------------------------------------------------------------------- 
    1518   USE ice 
    16    USE ioipsl 
    1719   USE dom_oce 
    1820   USE ice_oce         ! ice variables 
    1921   USE daymod 
    2022 
     23   USE in_out_manager 
     24   USE iom 
     25   USE restart 
     26 
    2127   IMPLICIT NONE 
    2228   PRIVATE 
    2329 
    24    !! * Accessibility 
    25    PUBLIC lim_rst_write  ! routine called by lim_step.F90 
    26    PUBLIC lim_rst_read   ! routine called by lim_init.F90 
    27  
    28    !!---------------------------------------------------------------------- 
    29    !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)  
     30   PUBLIC   lim_rst_opn     ! routine called by ??? module 
     31   PUBLIC   lim_rst_write   ! routine called by ??? module 
     32   PUBLIC   lim_rst_read    ! routine called by ??? module 
     33 
     34   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the oce restart write  
     35   INTEGER, PUBLIC ::   numrir, numriw   !: logical unit for ice restart (read and write) 
     36 
     37   !!---------------------------------------------------------------------- 
     38   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2006)  
    3039   !! $Header$  
    31    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     40   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    3241   !!---------------------------------------------------------------------- 
    3342 
     
    3645# if ( defined key_mpp_mpi || defined key_mpp_shmem ) && defined key_dimgout 
    3746   !!---------------------------------------------------------------------- 
    38    !!   'key_mpp_mpi'     OR 
    39    !!   'key_mpp_shmem' 
    40    !!   'key_dimgout' :                           clipper type restart file 
    41    !!                 :                     can be used in mpp 
     47   !!   'key_mpp_mpi'     OR     'key_mpp_shmem'              MPP computing 
     48   !!   'key_dimgout' :                    Direct access file (DIMG format) 
    4249   !!---------------------------------------------------------------------- 
    4350#  include "limrst_dimg.h90" 
     
    4855   !!---------------------------------------------------------------------- 
    4956 
    50    SUBROUTINE lim_rst_write( niter ) 
     57   SUBROUTINE lim_rst_opn( kt ) 
     58      !!---------------------------------------------------------------------- 
     59      !!                    ***  lim_rst_opn  *** 
     60      !! 
     61      !! ** purpose  :   output of sea-ice variable in a netcdf file 
     62      !!---------------------------------------------------------------------- 
     63      INTEGER, INTENT(in) ::   kt       ! number of iteration 
     64      ! 
     65      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
     66      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
     67      !!---------------------------------------------------------------------- 
     68      ! 
     69      IF( kt == nit000 )   lrst_ice = .FALSE. 
     70       
     71      IF    ( kt == nitrst - 2*nfice + 1 .AND. lrst_ice ) THEN 
     72         CALL ctl_stop( 'lim_rst_opn: ice restart frequency must be larger than nfice' ) 
     73         numriw = 0 
     74      ELSEIF( kt == nitrst - 2*nfice + 1 .OR.  nitend - nit000 +1 < 2*nfice ) THEN 
     75         ! beware if model runs less than 2*nfice time step 
     76         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
     77         IF( nitrst > 1.0e9 ) THEN    
     78            WRITE(clkt,*) nitrst 
     79         ELSE 
     80            WRITE(clkt,'(i8.8)') nitrst 
     81         ENDIF 
     82         ! create the file 
     83         IF(lwp) WRITE(numout,*) 
     84         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_ice" 
     85         IF(lwp) WRITE(numout,*) '             open ice restart.output NetCDF file: '//clname 
     86         CALL iom_open( clname, numriw, ldwrt = .TRUE. ) 
     87         lrst_ice = .TRUE. 
     88      ENDIF 
     89      ! 
     90   END SUBROUTINE lim_rst_opn 
     91 
     92   SUBROUTINE lim_rst_write( kt ) 
    5193      !!---------------------------------------------------------------------- 
    5294      !!                    ***  lim_rst_write  *** 
    5395      !! 
    5496      !! ** purpose  :   output of sea-ice variable in a netcdf file 
    55       !! 
    56       !!---------------------------------------------------------------------- 
    57       ! Arguments 
    58       INTEGER  ::    niter        ! number of iteration 
    59  
    60       !- dummy variables : 
    61       LOGICAL :: & 
    62          llbon 
    63       INTEGER :: & 
    64          ji, jj 
    65       INTEGER :: & 
    66          inumwrs, it0, itime 
    67       REAL(wp), DIMENSION(1) :: & 
    68          zdept 
    69       REAL(wp), DIMENSION(2) :: & 
    70          zinfo 
    71       REAL(wp),DIMENSION(jpi,jpj,35) :: & 
    72          zmoment 
    73       REAL(wp) :: & 
    74          zsec, zdate0, zdt 
    75  
    76       CHARACTER(len=45)  ::  ccfile 
    77  
    78       ccfile = 'restart_ice_out.nc' 
    79  
    80 #if defined key_agrif 
    81       if ( .NOT. Agrif_Root() ) then 
    82          ccfile= TRIM(Agrif_CFixed())//'_'//TRIM(ccfile) 
    83       endif 
    84 #endif 
    85  
    86       inumwrs  = 61 
    87       INQUIRE ( FILE = ccfile, EXIST = llbon ) 
    88       IF( llbon ) THEN 
    89          OPEN ( UNIT = inumwrs , FILE = ccfile, STATUS = 'old' ) 
    90          CLOSE( inumwrs , STATUS = 'delete' ) 
    91       ENDIF 
    92  
    93  
    94       it0      = niter 
    95       zinfo(1) = FLOAT( nfice  )  ! coupling frequency OPA ICELLN  nfice 
    96       zinfo(2) = FLOAT( it0   )   ! iteration number 
    97  
    98       zsec     = 0.e0 
    99       itime    = 0 
    100       zdept(1) = 0.e0 
    101       zdt      = rdt_ice * nstock 
    102  
    103       ! Write in inumwrs 
    104  
    105       DO jj = 1, jpj              ! 3D array: 10 time faster than 35 restput 
    106          DO ji = 1, jpi 
    107             zmoment(ji,jj,1)  = sxice(ji,jj) 
    108             zmoment(ji,jj,2)  = syice(ji,jj) 
    109             zmoment(ji,jj,3)  = sxxice(ji,jj) 
    110             zmoment(ji,jj,4)  = syyice(ji,jj) 
    111             zmoment(ji,jj,5)  = sxyice(ji,jj) 
    112             zmoment(ji,jj,6)  = sxsn(ji,jj) 
    113             zmoment(ji,jj,7)  = sysn(ji,jj) 
    114             zmoment(ji,jj,8)  = sxxsn(ji,jj) 
    115             zmoment(ji,jj,9)  = syysn(ji,jj) 
    116             zmoment(ji,jj,10) = sxysn(ji,jj) 
    117             zmoment(ji,jj,11) = sxa(ji,jj) 
    118             zmoment(ji,jj,12) = sya(ji,jj) 
    119             zmoment(ji,jj,13) = sxxa(ji,jj) 
    120             zmoment(ji,jj,14) = syya(ji,jj) 
    121             zmoment(ji,jj,15) = sxya(ji,jj) 
    122             zmoment(ji,jj,16) = sxc0(ji,jj) 
    123             zmoment(ji,jj,17) = syc0(ji,jj) 
    124             zmoment(ji,jj,18) = sxxc0(ji,jj) 
    125             zmoment(ji,jj,19) = syyc0(ji,jj) 
    126             zmoment(ji,jj,20) = sxyc0(ji,jj) 
    127             zmoment(ji,jj,21) = sxc1(ji,jj) 
    128             zmoment(ji,jj,22) = syc1(ji,jj) 
    129             zmoment(ji,jj,23) = sxxc1(ji,jj) 
    130             zmoment(ji,jj,24) = syyc1(ji,jj) 
    131             zmoment(ji,jj,25) = sxyc1(ji,jj) 
    132             zmoment(ji,jj,26) = sxc2(ji,jj) 
    133             zmoment(ji,jj,27) = syc2(ji,jj) 
    134             zmoment(ji,jj,28) = sxxc2(ji,jj) 
    135             zmoment(ji,jj,29) = syyc2(ji,jj) 
    136             zmoment(ji,jj,30) = sxyc2(ji,jj) 
    137             zmoment(ji,jj,31) = sxst(ji,jj) 
    138             zmoment(ji,jj,32) = syst(ji,jj) 
    139             zmoment(ji,jj,33) = sxxst(ji,jj) 
    140             zmoment(ji,jj,34) = syyst(ji,jj) 
    141             zmoment(ji,jj,35) = sxyst(ji,jj) 
    142          END DO 
    143       END DO 
    144  
    145       CALL ymds2ju( nyear, nmonth, nday, zsec, zdate0 ) 
    146       CALL restini( 'NONE', jpi, jpj, glamt, gphit, 1 , zdept, ccfile, itime, zdate0, zdt, & 
    147          &         inumwrs, domain_id=nidom ) 
    148        
    149       CALL restput( inumwrs, 'info'   ,   1,   1, 2 , 0, zinfo   )  ! restart informations 
    150         
    151       CALL restput( inumwrs, 'hicif'  , jpi, jpj, 1 , 0, hicif   )  ! prognostic variables  
    152       CALL restput( inumwrs, 'hsnif'  , jpi, jpj, 1 , 0, hsnif   ) 
    153       CALL restput( inumwrs, 'frld'   , jpi, jpj, 1 , 0, frld    ) 
    154       CALL restput( inumwrs, 'sist'   , jpi, jpj, 1 , 0, sist    ) 
     97      !!---------------------------------------------------------------------- 
     98      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     99      !! 
     100      INTEGER ::   iter     ! kt + nfice -1 
     101      !!---------------------------------------------------------------------- 
     102 
     103      iter = kt + nfice -1 
     104 
     105      IF( iter == nitrst ) THEN 
     106         IF(lwp) WRITE(numout,*) 
     107         IF(lwp) WRITE(numout,*) 'lim_rst_write : write ice restart.output NetCDF file  kt =', kt 
     108         IF(lwp) WRITE(numout,*) '~~~~~~~'          
     109      ENDIF 
     110 
     111      ! Write in numriw (if iter == nitrst) 
     112      ! ------------------  
     113      !                                                                     ! calendar control 
     114      CALL iom_rstput( iter, nitrst, numriw, 'nfice' , REAL( nfice, wp) )      ! time-step  
     115      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice', REAL( iter, wp) )      ! date 
     116       
     117      CALL iom_rstput( iter, nitrst, numriw, 'hicif' , hicif (:,:)   )      ! prognostic variables  
     118      CALL iom_rstput( iter, nitrst, numriw, 'hsnif' , hsnif (:,:)   ) 
     119      CALL iom_rstput( iter, nitrst, numriw, 'frld'  , frld  (:,:)   ) 
     120      CALL iom_rstput( iter, nitrst, numriw, 'sist'  , sist  (:,:)   ) 
    155121# if defined key_coupled 
    156       CALL restput( inumwrs, 'albege' , jpi, jpj, 1 , 0, albege ) 
     122      CALL iom_rstput( iter, nitrst, numriw, 'albege', albege(:,:) ) 
    157123# endif 
    158       CALL restput( inumwrs, 'tbif'   , jpi, jpj, 3 , 0, tbif    ) 
    159       CALL restput( inumwrs, 'u_ice'  , jpi, jpj, 1 , 0, u_ice   ) 
    160       CALL restput( inumwrs, 'v_ice'  , jpi, jpj, 1 , 0, v_ice   ) 
    161       CALL restput( inumwrs, 'gtaux'  , jpi, jpj, 1 , 0, gtaux  ) 
    162       CALL restput( inumwrs, 'gtauy'  , jpi, jpj, 1 , 0, gtauy  ) 
    163       CALL restput( inumwrs, 'qstoif' , jpi, jpj, 1 , 0, qstoif  ) 
    164       CALL restput( inumwrs, 'fsbbq'  , jpi, jpj, 1 , 0, fsbbq   ) 
    165       CALL restput( inumwrs, 'moment' , jpi, jpj, 35, 0, zmoment ) 
    166  
    167        
    168       CALL restclo( inumwrs ) 
    169  
     124      CALL iom_rstput( iter, nitrst, numriw, 'tbif1' , tbif  (:,:,1) ) 
     125      CALL iom_rstput( iter, nitrst, numriw, 'tbif2' , tbif  (:,:,2) ) 
     126      CALL iom_rstput( iter, nitrst, numriw, 'tbif3' , tbif  (:,:,3) ) 
     127      CALL iom_rstput( iter, nitrst, numriw, 'u_ice' , u_ice (:,:)   ) 
     128      CALL iom_rstput( iter, nitrst, numriw, 'v_ice' , v_ice (:,:)   ) 
     129      CALL iom_rstput( iter, nitrst, numriw, 'gtaux' , gtaux (:,:)   ) 
     130      CALL iom_rstput( iter, nitrst, numriw, 'gtauy' , gtauy (:,:)   ) 
     131      CALL iom_rstput( iter, nitrst, numriw, 'qstoif', qstoif(:,:)   ) 
     132      CALL iom_rstput( iter, nitrst, numriw, 'fsbbq' , fsbbq (:,:)   ) 
     133      CALL iom_rstput( iter, nitrst, numriw, 'sxice' , sxice (:,:)   ) 
     134      CALL iom_rstput( iter, nitrst, numriw, 'syice' , syice (:,:)   ) 
     135      CALL iom_rstput( iter, nitrst, numriw, 'sxxice', sxxice(:,:)   ) 
     136      CALL iom_rstput( iter, nitrst, numriw, 'syyice', syyice(:,:)   ) 
     137      CALL iom_rstput( iter, nitrst, numriw, 'sxyice', sxyice(:,:)   ) 
     138      CALL iom_rstput( iter, nitrst, numriw, 'sxsn'  , sxsn  (:,:)   ) 
     139      CALL iom_rstput( iter, nitrst, numriw, 'sysn'  , sysn  (:,:)   ) 
     140      CALL iom_rstput( iter, nitrst, numriw, 'sxxsn' , sxxsn (:,:)   ) 
     141      CALL iom_rstput( iter, nitrst, numriw, 'syysn' , syysn (:,:)   ) 
     142      CALL iom_rstput( iter, nitrst, numriw, 'sxysn' , sxysn (:,:)   ) 
     143      CALL iom_rstput( iter, nitrst, numriw, 'sxa'   , sxa   (:,:)   ) 
     144      CALL iom_rstput( iter, nitrst, numriw, 'sya'   , sya   (:,:)   ) 
     145      CALL iom_rstput( iter, nitrst, numriw, 'sxxa'  , sxxa  (:,:)   ) 
     146      CALL iom_rstput( iter, nitrst, numriw, 'syya'  , syya  (:,:)   ) 
     147      CALL iom_rstput( iter, nitrst, numriw, 'sxya'  , sxya  (:,:)   ) 
     148      CALL iom_rstput( iter, nitrst, numriw, 'sxc0'  , sxc0  (:,:)   ) 
     149      CALL iom_rstput( iter, nitrst, numriw, 'syc0'  , syc0  (:,:)   ) 
     150      CALL iom_rstput( iter, nitrst, numriw, 'sxxc0' , sxxc0 (:,:)   ) 
     151      CALL iom_rstput( iter, nitrst, numriw, 'syyc0' , syyc0 (:,:)   ) 
     152      CALL iom_rstput( iter, nitrst, numriw, 'sxyc0' , sxyc0 (:,:)   ) 
     153      CALL iom_rstput( iter, nitrst, numriw, 'sxc1'  , sxc1  (:,:)   ) 
     154      CALL iom_rstput( iter, nitrst, numriw, 'syc1'  , syc1  (:,:)   ) 
     155      CALL iom_rstput( iter, nitrst, numriw, 'sxxc1' , sxxc1 (:,:)   ) 
     156      CALL iom_rstput( iter, nitrst, numriw, 'syyc1' , syyc1 (:,:)   ) 
     157      CALL iom_rstput( iter, nitrst, numriw, 'sxyc1' , sxyc1 (:,:)   ) 
     158      CALL iom_rstput( iter, nitrst, numriw, 'sxc2'  , sxc2  (:,:)   ) 
     159      CALL iom_rstput( iter, nitrst, numriw, 'syc2'  , syc2  (:,:)   ) 
     160      CALL iom_rstput( iter, nitrst, numriw, 'sxxc2' , sxxc2 (:,:)   ) 
     161      CALL iom_rstput( iter, nitrst, numriw, 'syyc2' , syyc2 (:,:)   ) 
     162      CALL iom_rstput( iter, nitrst, numriw, 'sxyc2' , sxyc2 (:,:)   ) 
     163      CALL iom_rstput( iter, nitrst, numriw, 'sxst'  , sxst  (:,:)   ) 
     164      CALL iom_rstput( iter, nitrst, numriw, 'syst'  , syst  (:,:)   ) 
     165      CALL iom_rstput( iter, nitrst, numriw, 'sxxst' , sxxst (:,:)   ) 
     166      CALL iom_rstput( iter, nitrst, numriw, 'syyst' , syyst (:,:)   ) 
     167      CALL iom_rstput( iter, nitrst, numriw, 'sxyst' , sxyst (:,:)   ) 
     168       
     169      IF( iter == nitrst ) THEN 
     170         CALL iom_close( numriw )                         ! close the restart file 
     171         lrst_ice = .FALSE. 
     172      ENDIF 
     173      ! 
    170174   END SUBROUTINE lim_rst_write 
    171175 
    172176 
    173    SUBROUTINE lim_rst_read( niter ) 
    174       !----------------------------------------------------------------------- 
    175       !  restart from a state defined in a binary file 
    176       !----------------------------------------------------------------------- 
    177       !! * Modules used 
    178       USE iom 
    179       ! Arguments 
    180       INTEGER  ::   niter        ! number of iteration 
    181  
    182       !- dummy variables : 
    183       INTEGER :: & 
    184          inum, it1, ifice 
    185       REAL(wp),DIMENSION(jpi,jpj,35) :: & 
    186          zmoment 
    187       REAL(wp),DIMENSION(1, 1, 2) :: & 
    188          zinfo 
    189  
    190       CALL iom_open ( 'restart_ice_in', inum ) 
    191  
    192       CALL iom_get (inum, jpdom_unknown, 'info', zinfo) 
    193       ifice   = INT( zinfo(1, 1, 1) ) ! not used ... 
    194       it1     = INT( zinfo(1, 1, 2) ) 
    195  
    196       IF(lwp) WRITE(numout,*) 'lim_rst_read : READ restart file at time step : ', it1 
     177   SUBROUTINE lim_rst_read 
     178      !!---------------------------------------------------------------------- 
     179      !!                    ***  lim_rst_read  *** 
     180      !! 
     181      !! ** purpose  :   read of sea-ice variable restart in a netcdf file 
     182      !!---------------------------------------------------------------------- 
     183      ! 
     184      REAL(wp) ::   zfice, ziter 
     185      !!---------------------------------------------------------------------- 
     186 
     187      IF(lwp) THEN 
     188         WRITE(numout,*) 
     189         WRITE(numout,*) 'lim_rst_read : read ice NetCDF restart file' 
     190         WRITE(numout,*) '~~~~~~~~' 
     191      ENDIF 
     192 
     193      CALL iom_open ( 'restart_ice_in', numrir ) 
     194 
     195      CALL iom_get( numrir, 'nfice' , zfice ) 
     196      CALL iom_get( numrir, 'kt_ice', ziter )     
     197      IF(lwp) WRITE(numout,*) '   read ice restart file at time step    : ', ziter 
     198      IF(lwp) WRITE(numout,*) '   in any case we force it to nit000 - 1 : ', nit000 - 1 
    197199 
    198200      !Control of date 
    199201       
    200       IF( ( nit000 - it1 ) /= 1 .AND. ABS( nrstdt ) == 1 ) & 
    201            CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 for the restart',  & 
    202       &                   '   verify the file or rerun with the value 0 for the',        & 
    203       &                   '   control of time parameter  nrstdt' ) 
    204  
    205       CALL iom_get( inum, jpdom_local, 'hicif' , hicif )     
    206       CALL iom_get( inum, jpdom_local, 'hsnif' , hsnif )     
    207       CALL iom_get( inum, jpdom_local, 'frld'  , frld )     
    208       CALL iom_get( inum, jpdom_local, 'sist'  , sist )     
     202      IF( ( nit000 - INT(ziter) ) /= 1 .AND. ABS( nrstdt ) == 1 )   & 
     203         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nit000 in ice restart',  & 
     204         &                   '   verify the file or rerun with the value 0 for the',        & 
     205         &                   '   control of time parameter  nrstdt' ) 
     206      IF( INT(zfice) /= nfice          .AND. ABS( nrstdt ) == 1 )   & 
     207         &     CALL ctl_stop( 'lim_rst_read ===>>>> : problem with nfice in ice restart',  & 
     208         &                   '   verify the file or rerun with the value 0 for the',        & 
     209         &                   '   control of time parameter  nrstdt' ) 
     210 
     211      CALL iom_get( numrir, jpdom_local, 'hicif' , hicif  )     
     212      CALL iom_get( numrir, jpdom_local, 'hsnif' , hsnif  )     
     213      CALL iom_get( numrir, jpdom_local, 'frld'  , frld   )     
     214      CALL iom_get( numrir, jpdom_local, 'sist'  , sist   )     
    209215# if defined key_coupled  
    210       CALL iom_get( inum, jpdom_local, 'albege', albege )     
     216      CALL iom_get( numrir, jpdom_local, 'albege', albege )     
    211217# endif 
    212       CALL iom_get( inum, jpdom_unknown, 'tbif', tbif )     
    213       CALL iom_get( inum, jpdom_local, 'u_ice' , u_ice )     
    214       CALL iom_get( inum, jpdom_local, 'v_ice' , v_ice )     
    215       CALL iom_get( inum, jpdom_local, 'gtaux' , gtaux )     
    216       CALL iom_get( inum, jpdom_local, 'gtauy' , gtauy )     
    217       CALL iom_get( inum, jpdom_local, 'qstoif', qstoif )     
    218       CALL iom_get( inum, jpdom_local, 'fsbbq' , fsbbq )     
    219       CALL iom_get( inum, jpdom_unknown, 'moment', zmoment )     
    220       sxice(:,:)  = zmoment(:,:,1) 
    221       syice(:,:)  = zmoment(:,:,2) 
    222       sxxice(:,:) = zmoment(:,:,3) 
    223       syyice(:,:) = zmoment(:,:,4) 
    224       sxyice(:,:) = zmoment(:,:,5) 
    225       sxsn(:,:)   = zmoment(:,:,6) 
    226       sysn(:,:)   = zmoment(:,:,7) 
    227       sxxsn(:,:)  = zmoment(:,:,8) 
    228       syysn(:,:)  = zmoment(:,:,9) 
    229       sxysn(:,:)  = zmoment(:,:,10) 
    230       sxa(:,:)    = zmoment(:,:,11) 
    231       sya(:,:)    = zmoment(:,:,12) 
    232       sxxa(:,:)   = zmoment(:,:,13) 
    233       syya(:,:)   = zmoment(:,:,14) 
    234       sxya(:,:)   = zmoment(:,:,15) 
    235       sxc0(:,:)   = zmoment(:,:,16) 
    236       syc0(:,:)   = zmoment(:,:,17) 
    237       sxxc0(:,:)  = zmoment(:,:,18) 
    238       syyc0(:,:)  = zmoment(:,:,19) 
    239       sxyc0(:,:)  = zmoment(:,:,20) 
    240       sxc1(:,:)   = zmoment(:,:,21) 
    241       syc1(:,:)   = zmoment(:,:,22) 
    242       sxxc1(:,:)  = zmoment(:,:,23) 
    243       syyc1(:,:)  = zmoment(:,:,24) 
    244       sxyc1(:,:)  = zmoment(:,:,25) 
    245       sxc2(:,:)   = zmoment(:,:,26) 
    246       syc2(:,:)   = zmoment(:,:,27) 
    247       sxxc2(:,:)  = zmoment(:,:,28) 
    248       syyc2(:,:)  = zmoment(:,:,29) 
    249       sxyc2(:,:)  = zmoment(:,:,30) 
    250       sxst(:,:)   = zmoment(:,:,31) 
    251       syst(:,:)   = zmoment(:,:,32) 
    252       sxxst(:,:)  = zmoment(:,:,33) 
    253       syyst(:,:)  = zmoment(:,:,34) 
    254       sxyst(:,:)  = zmoment(:,:,35) 
    255        
    256       CALL iom_close( inum ) 
    257        
    258       niter = it1 
    259  
     218      CALL iom_get( numrir, jpdom_local, 'tbif1' , tbif(:,:,1) )     
     219      CALL iom_get( numrir, jpdom_local, 'tbif2' , tbif(:,:,2) )     
     220      CALL iom_get( numrir, jpdom_local, 'tbif3' , tbif(:,:,3) )     
     221      CALL iom_get( numrir, jpdom_local, 'u_ice' , u_ice  )     
     222      CALL iom_get( numrir, jpdom_local, 'v_ice' , v_ice  )     
     223      CALL iom_get( numrir, jpdom_local, 'gtaux' , gtaux  )     
     224      CALL iom_get( numrir, jpdom_local, 'gtauy' , gtauy  )     
     225      CALL iom_get( numrir, jpdom_local, 'qstoif', qstoif )     
     226      CALL iom_get( numrir, jpdom_local, 'fsbbq' , fsbbq  )     
     227      CALL iom_get( numrir, jpdom_local, 'sxice' , sxice  ) 
     228      CALL iom_get( numrir, jpdom_local, 'syice' , syice  ) 
     229      CALL iom_get( numrir, jpdom_local, 'sxxice', sxxice ) 
     230      CALL iom_get( numrir, jpdom_local, 'syyice', syyice ) 
     231      CALL iom_get( numrir, jpdom_local, 'sxyice', sxyice ) 
     232      CALL iom_get( numrir, jpdom_local, 'sxsn'  , sxsn   ) 
     233      CALL iom_get( numrir, jpdom_local, 'sysn'  , sysn   ) 
     234      CALL iom_get( numrir, jpdom_local, 'sxxsn' , sxxsn  ) 
     235      CALL iom_get( numrir, jpdom_local, 'syysn' , syysn  ) 
     236      CALL iom_get( numrir, jpdom_local, 'sxysn' , sxysn  ) 
     237      CALL iom_get( numrir, jpdom_local, 'sxa'   , sxa    ) 
     238      CALL iom_get( numrir, jpdom_local, 'sya'   , sya    ) 
     239      CALL iom_get( numrir, jpdom_local, 'sxxa'  , sxxa   ) 
     240      CALL iom_get( numrir, jpdom_local, 'syya'  , syya   ) 
     241      CALL iom_get( numrir, jpdom_local, 'sxya'  , sxya   ) 
     242      CALL iom_get( numrir, jpdom_local, 'sxc0'  , sxc0   ) 
     243      CALL iom_get( numrir, jpdom_local, 'syc0'  , syc0   ) 
     244      CALL iom_get( numrir, jpdom_local, 'sxxc0' , sxxc0  ) 
     245      CALL iom_get( numrir, jpdom_local, 'syyc0' , syyc0  ) 
     246      CALL iom_get( numrir, jpdom_local, 'sxyc0' , sxyc0  ) 
     247      CALL iom_get( numrir, jpdom_local, 'sxc1'  , sxc1   ) 
     248      CALL iom_get( numrir, jpdom_local, 'syc1'  , syc1   ) 
     249      CALL iom_get( numrir, jpdom_local, 'sxxc1' , sxxc1  ) 
     250      CALL iom_get( numrir, jpdom_local, 'syyc1' , syyc1  ) 
     251      CALL iom_get( numrir, jpdom_local, 'sxyc1' , sxyc1  ) 
     252      CALL iom_get( numrir, jpdom_local, 'sxc2'  , sxc2   ) 
     253      CALL iom_get( numrir, jpdom_local, 'syc2'  , syc2   ) 
     254      CALL iom_get( numrir, jpdom_local, 'sxxc2' , sxxc2  ) 
     255      CALL iom_get( numrir, jpdom_local, 'syyc2' , syyc2  ) 
     256      CALL iom_get( numrir, jpdom_local, 'sxyc2' , sxyc2  ) 
     257      CALL iom_get( numrir, jpdom_local, 'sxst'  , sxst   ) 
     258      CALL iom_get( numrir, jpdom_local, 'syst'  , syst   ) 
     259      CALL iom_get( numrir, jpdom_local, 'sxxst' , sxxst  ) 
     260      CALL iom_get( numrir, jpdom_local, 'syyst' , syyst  ) 
     261      CALL iom_get( numrir, jpdom_local, 'sxyst' , sxyst  ) 
     262       
     263      CALL iom_close( numrir ) 
     264      ! 
    260265   END SUBROUTINE lim_rst_read 
    261266 
     
    266271   !!   Default option :       Empty module            NO LIM sea-ice model 
    267272   !!---------------------------------------------------------------------- 
    268 CONTAINS 
    269    SUBROUTINE lim_rst_read             ! Empty routine 
    270    END SUBROUTINE lim_rst_read 
    271    SUBROUTINE lim_rst_write            ! Empty routine 
    272    END SUBROUTINE lim_rst_write 
    273273#endif 
    274274 
    275275   !!====================================================================== 
    276276END MODULE limrst 
     277 
  • trunk/NEMO/LIM_SRC/limthd.F90

    r476 r508  
    5252CONTAINS 
    5353 
    54    SUBROUTINE lim_thd 
     54   SUBROUTINE lim_thd( kt ) 
    5555      !!------------------------------------------------------------------- 
    5656      !!                ***  ROUTINE lim_thd  ***        
     
    7575      !!   2.0  !  02-07 (C. Ethe, G. Madec) F90 
    7676      !!--------------------------------------------------------------------- 
    77       !! * Local variables 
     77      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     78 
    7879      INTEGER  ::   ji, jj,    &   ! dummy loop indices 
    7980         nbpb  ,               &   ! nb of icy pts for thermo. cal. 
     
    9899      !!------------------------------------------------------------------- 
    99100 
    100       IF( numit == nstart  )   CALL lim_thd_init  ! Initialization (first time-step only) 
     101      IF( kt == nit000  )   CALL lim_thd_init  ! Initialization (first time-step only) 
    101102    
    102103      !-------------------------------------------! 
  • trunk/NEMO/LIM_SRC/limtrp.F90

    r247 r508  
    5454CONTAINS 
    5555 
    56    SUBROUTINE lim_trp 
     56   SUBROUTINE lim_trp( kt ) 
    5757      !!------------------------------------------------------------------- 
    5858      !!                   ***  ROUTINE lim_trp *** 
     
    7171      !!   2.0  !  04-01 (G. Madec, C. Ethe)  F90, mpp 
    7272      !!--------------------------------------------------------------------- 
    73       !! * Local Variables 
     73      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     74 
    7475      INTEGER  ::   ji, jj, jk,   &  ! dummy loop indices 
    7576         &          initad           ! number of sub-timestep for the advection 
     
    9697      !--------------------------------------------------------------------- 
    9798 
    98       IF( numit == nstart  )   CALL lim_trp_init      ! Initialization (first time-step only) 
     99      IF( kt == nit000  )   CALL lim_trp_init      ! Initialization (first time-step only) 
    99100 
    100101      zsm(:,:) = area(:,:) 
  • trunk/NEMO/LIM_SRC/limwri.F90

    r352 r508  
    44   !!         Ice diagnostics :  write ice output files 
    55   !!====================================================================== 
    6    !!---------------------------------------------------------------------- 
    7    !!  LIM 2.0, UCL-LOCEAN-IPSL (2005) 
    8    !! $Header$ 
    9    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
    10    !!---------------------------------------------------------------------- 
     6   !! history :  2.0  ! 03-08  (C. Ethe) original code 
     7   !!            2.0  ! 04-10  (C. Ethe )  1D configuration 
     8   !!------------------------------------------------------------------- 
    119#if defined key_ice_lim 
    1210   !!---------------------------------------------------------------------- 
    1311   !!   'key_ice_lim'                                     LIM sea-ice model 
     12   !!---------------------------------------------------------------------- 
    1413   !!---------------------------------------------------------------------- 
    1514   !!   lim_wri      : write of the diagnostics variables in ouput file  
    1615   !!   lim_wri_init : initialization and namelist read 
    1716   !!---------------------------------------------------------------------- 
    18    !! * Modules used 
    1917   USE ioipsl 
    2018   USE dianam    ! build name of file (routine) 
     
    2725   USE dom_ice 
    2826   USE ice 
    29    USE iceini 
    3027   USE lbclnk 
    3128 
     
    3330   PRIVATE 
    3431 
    35    !! * Accessibility 
    36    PUBLIC lim_wri        ! routine called by lim_step.F90 
    37  
    38    !! * Module variables 
    39    INTEGER, PARAMETER ::   &  !: 
    40       jpnoumax = 40             !: maximum number of variable for ice output 
    41    INTEGER  ::                                & 
    42       noumef                                     ! number of fields 
    43    REAL(wp)           , DIMENSION(jpnoumax) ::  & 
    44       cmulti ,                                &  ! multiplicative constant 
    45       cadd                                       ! additive constant 
    46    CHARACTER(len = 35), DIMENSION(jpnoumax) ::  & 
    47       titn                                       ! title of the field 
    48    CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::  & 
    49       nam                                        ! name of the field 
    50    CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::  & 
    51       uni                                        ! unit of the field 
    52    INTEGER            , DIMENSION(jpnoumax) ::  & 
    53       nc                                         ! switch for saving field ( = 1 ) or not ( = 0 ) 
     32   PUBLIC   lim_wri        ! routine called by lim_step.F90 
     33 
     34   INTEGER, PARAMETER                       ::   jpnoumax = 40   ! maximum number of variable for ice output 
     35   INTEGER                                  ::   noumef          ! number of fields 
     36   REAL(wp)           , DIMENSION(jpnoumax) ::   cmulti ,     &  ! multiplicative constant 
     37      &                                          cadd            ! additive constant 
     38   CHARACTER(len = 35), DIMENSION(jpnoumax) ::   titn            ! title of the field 
     39   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::   nam             ! name of the field 
     40   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::   uni             ! unit of the field 
     41   INTEGER            , DIMENSION(jpnoumax) ::   nc              ! switch for saving field ( = 1 ) or not ( = 0 ) 
     42 
     43   INTEGER ::   nice, nhorid, ndim, niter, ndepid       ! ???? 
     44   INTEGER , DIMENSION( jpij ) ::   ndex51              ! ???? 
    5445 
    5546   REAL(wp)  ::            &  ! constant values 
     
    5748      zzero  = 0.e0     ,  & 
    5849      zone   = 1.e0 
    59    !!------------------------------------------------------------------- 
     50 
     51   !!---------------------------------------------------------------------- 
     52   !!  LIM 2.0, UCL-LOCEAN-IPSL (2005) 
     53   !! $Header$ 
     54   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     55   !!---------------------------------------------------------------------- 
    6056 
    6157CONTAINS 
     58 
    6259#if defined key_dimgout 
    63  
     60   !!---------------------------------------------------------------------- 
     61   !!   'key_dimgout'                                    Direct Access file 
     62   !!---------------------------------------------------------------------- 
    6463# include "limwri_dimg.h90" 
    65  
    6664#else 
    67  
    68    SUBROUTINE lim_wri 
    69       !!------------------------------------------------------------------- 
    70       !!  This routine computes the average of some variables and write it 
    71       !!  on the ouput files. 
    72       !!  ATTENTION cette routine n'est valable que si le pas de temps est 
    73       !!  egale a une fraction entiere de 1 jours. 
    74       !!  Diff 1-D 3-D : suppress common also included in etat 
    75       !!                 suppress cmoymo 11-18 
    76       !!  modif : 03/06/98 
    77       !!------------------------------------------------------------------- 
    78       !! * Local variables 
    79       REAL(wp),DIMENSION(1) ::   zdept 
    80        
    81       REAL(wp) :: & 
    82          zsto, zsec, zjulian,zout, & 
    83          zindh,zinda,zindb,  & 
    84          ztmu 
    85       REAL(wp), DIMENSION(jpi,jpj,jpnoumax) :: & 
    86          zcmo 
    87       REAL(wp), DIMENSION(jpi,jpj) ::  & 
    88          zfield 
    89       INTEGER ::  ji, jj, jf   ! dummy loop indices 
    90  
    91       CHARACTER(len = 40)  :: & 
    92          clhstnam, clop 
    93  
    94       INTEGER , SAVE ::      & 
    95          nice, nhorid, ndim, niter, ndepid 
    96       INTEGER , DIMENSION( jpij ) , SAVE ::  & 
    97          ndex51   
    98       !!------------------------------------------------------------------- 
    99        
    100       IF ( numit == nstart ) THEN  
    101  
     65   !!---------------------------------------------------------------------- 
     66   !!   Default option                                          NetCDF file 
     67   !!---------------------------------------------------------------------- 
     68 
     69   SUBROUTINE lim_wri( kt ) 
     70      !!------------------------------------------------------------------- 
     71      !!                    ***   ROUTINE lim_wri  *** 
     72      !!                 
     73      !! ** Purpose :   write the sea-ice output file in NetCDF 
     74      !! 
     75      !! ** Method  :   computes the average of some variables and write 
     76      !!      it in the NetCDF ouput files 
     77      !!      CAUTION: the sea-ice time-step must be an integer fraction 
     78      !!      of a day 
     79      !!------------------------------------------------------------------- 
     80      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     81 
     82      INTEGER  ::   ji, jj, jf                      ! dummy loop indices 
     83      CHARACTER(len = 40)  ::   clhstnam, clop 
     84      REAL(wp) ::   zsto, zsec, zjulian, zout,   &  ! temporary scalars 
     85         &          zindh, zinda, zindb, ztmu 
     86      REAL(wp), DIMENSION(1)                ::   zdept 
     87      REAL(wp), DIMENSION(jpi,jpj)          ::   zfield 
     88      REAL(wp), DIMENSION(jpi,jpj,jpnoumax) ::   zcmo 
     89      !!------------------------------------------------------------------- 
     90 
     91      !                                          !--------------------! 
     92      IF ( kt == nit000 ) THEN                !   Initialisation   ! 
     93         !                                       !--------------------! 
    10294         CALL lim_wri_init  
    103           
    104          !---5----|----5----|----5----|----5----|----5----|----5----|----5----|72 
    105          !  1) INITIALIZATIONS.                                                 | 
    106          !----------------------------------------------------------------------- 
    107           
    108          !-- essai NetCDF 
    109           
     95                            
    11096         zsto     = rdt_ice 
    11197!!Chris         clop     = "ave(only(x))"      !ibug  namelist parameter a ajouter 
     
    118104         CALL ymds2ju ( nyear, nmonth, nday, zsec, zjulian ) 
    119105         CALL dia_nam ( clhstnam, nwrite, 'icemod' ) 
    120          CALL histbeg ( clhstnam, jpi, glamt, jpj, gphit, 1, jpi, 1, jpj, 0, zjulian, rdt_ice, nhorid, nice , domain_id=nidom) 
     106         CALL histbeg ( clhstnam, jpi, glamt, jpj, gphit,    & 
     107            &           1, jpi, 1, jpj, 0, zjulian, rdt_ice, nhorid, nice , domain_id=nidom) 
    121108         CALL histvert( nice, "deptht", "Vertical T levels", "m", 1, zdept, ndepid) 
    122109         CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim) 
    123110          
    124111         DO jf = 1, noumef 
    125             IF ( nc(jf) == 1 ) THEN 
    126                CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj   & 
    127                   , nhorid, 1, 1, 1, -99, 32, clop, zsto, zout ) 
    128             ENDIF 
    129          END DO 
    130          CALL histend(nice) 
    131           
    132       ENDIF 
    133        
    134       !---5----|----5----|----5----|----5----|----5----|----5----|----5----|72 
    135       !--2. Computation of instantaneous values                                         | 
    136       !----------------------------------------------------------------------- 
    137  
     112            IF ( nc(jf) == 1 )   CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj   & 
     113                  &                                , nhorid, 1, 1, 1, -99, 32, clop, zsto, zout ) 
     114         END DO 
     115         CALL histend( nice ) 
     116          
     117      ENDIF 
     118      !                                          !--------------------! 
     119      !                                          !   Cumulate at kt   ! 
     120      !                                          !--------------------! 
     121 
     122!!gm  change the print below to have it only at output time step or when nitend =< 100 
    138123      IF(lwp) THEN 
    139124         WRITE(numout,*) 
    140          WRITE(numout,*) 'lim_wri : write ice outputs in NetCDF files at time : ', nyear, nmonth, nday, numit 
     125         WRITE(numout,*) 'lim_wri : write ice outputs in NetCDF files at time : ', nyear, nmonth, nday, kt + nfice - 1 
    141126         WRITE(numout,*) '~~~~~~~ ' 
    142127      ENDIF 
     
    179164         END DO 
    180165      END DO 
    181                  
    182166      ! 
    183       ! ecriture d'un fichier netcdf 
     167      ! Write the netcdf file 
    184168      ! 
    185169      niter = niter + 1 
     
    205189         CALL histclo( nice )  
    206190      ENDIF 
    207        
     191      ! 
    208192   END SUBROUTINE lim_wri 
     193    
    209194#endif 
    210195    
     
    213198      !!                    ***   ROUTINE lim_wri_init  *** 
    214199      !!                 
    215       !! ** Purpose :   ??? 
     200      !! ** Purpose :   intialisation of LIM sea-ice output 
    216201      !! 
    217202      !! ** Method  : Read the namicewri namelist and check the parameter  
     
    219204      !! 
    220205      !! ** input   :   Namelist namicewri 
    221       !! 
    222       !! history : 
    223       !!  8.5  ! 03-08 (C. Ethe) original code 
    224       !!------------------------------------------------------------------- 
    225       !! * Local declarations 
     206      !!------------------------------------------------------------------- 
    226207      INTEGER ::   nf      ! ??? 
    227  
    228208      TYPE FIELD  
    229209         CHARACTER(len = 35) :: ztitle  
     
    234214         REAL                :: zcadd         
    235215      END TYPE FIELD 
    236  
    237216      TYPE(FIELD) ::  & 
    238217         field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,   & 
     
    240219         field_13, field_14, field_15, field_16, field_17, field_18,   & 
    241220         field_19 
    242  
    243221      TYPE(FIELD) , DIMENSION(jpnoumax) :: zfield 
    244222 
     
    248226         field_13, field_14, field_15, field_16, field_17, field_18,   & 
    249227         field_19 
    250       !!------------------------------------------------------------------- 
    251  
     228!!gm      NAMELIST/namiceout/ noumef, & 
     229!!           zfield( 1), zfield( 2), zfield( 3), zfield( 4), zfield( 5),   & 
     230!!           zfield( 6), zfield( 7), zfield( 8), zfield( 9), zfield(10),   & 
     231!!           zfield(11), zfield(12), zfield(13), zfield(14), zfield(15),   & 
     232!!gm         zfield(16), zfield(17), zfield(18), zfield(19) 
     233      !!------------------------------------------------------------------- 
    252234 
    253235      ! Read Namelist namicewri 
    254236      REWIND ( numnam_ice ) 
    255237      READ   ( numnam_ice  , namiceout ) 
     238       
    256239      zfield(1)  = field_1 
    257240      zfield(2)  = field_2 
     
    295278         END DO 
    296279      ENDIF 
    297              
     280      !     
    298281   END SUBROUTINE lim_wri_init 
    299282 
  • trunk/NEMO/LIM_SRC/limwri_dimg.h90

    r284 r508  
    1     SUBROUTINE lim_wri 
     1    SUBROUTINE lim_wri(kt) 
    22   !!---------------------------------------------------------------------- 
    33   !!  LIM 2.0, UCL-LOCEAN-IPSL (2005) 
     
    1414    !!  modif : 03/06/98 
    1515    !!------------------------------------------------------------------- 
    16     !! * Local variables 
    1716    USE  diadimg                ! use of dia_wri_dimg 
     17 
     18    INTEGER, INTENT(in) ::   kt     ! number of iteration 
     19 
    1820    REAL(wp),DIMENSION(1) ::   zdept 
    1921 
     
    4850         ndex51   
    4951    !!------------------------------------------------------------------- 
    50     IF ( numit == nstart ) THEN  
     52    IF ( kt == nit000 ) THEN  
    5153 
    5254       CALL lim_wri_init  
     
    130132    nmoyice = nmoyice + 1  
    131133    ! compute mean value if it is time to write on file 
    132     IF ( MOD(numit-nit000+1,nwrite) == 0 ) THEN 
     134    IF ( MOD(kt+nfice-1-nit000+1,nwrite) == 0 ) THEN 
    133135       rcmoy(:,:,:) = rcmoy(:,:,:) / FLOAT(nmoyice) 
    134136#else   
    135        IF ( MOD(numit-nit000+1,nwrite) == 0 ) THEN  
     137       IF ( MOD(kt-nfice-1-nit000+1,nwrite) == 0 ) THEN  
    136138          !  case of instantaneaous output rcmoy(:,:, 1:jpnoumax ) = 0.e0 
    137139          DO jj = 2 , jpjm1 
     
    200202          rcmoy(:,:,:) = 0.0 
    201203          nmoyice = 0  
    202        END IF     !  MOD(numit, nwrite == 0 ) ! 
     204       END IF     !  MOD(kt+nfice-1-nit000+1, nwrite == 0 ) ! 
    203205 
    204206     END SUBROUTINE lim_wri 
Note: See TracChangeset for help on using the changeset viewer.