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 557 – NEMO

Changeset 557


Ignore:
Timestamp:
2006-10-27T17:15:13+02:00 (17 years ago)
Author:
opalod
Message:

nemo_v1_bugfix_069: SM+CT+CE: bugfix of mld restart + OFF line compatibiblity

Location:
trunk/NEMO
Files:
5 edited

Legend:

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

    r547 r557  
    2323   USE in_out_manager 
    2424   USE iom 
    25    USE restart 
    2625 
    2726   IMPLICIT NONE 
  • trunk/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r556 r557  
    3232   INTEGER            ::   nleapy     = 0         !: Leap year calendar flag (0/1 or 30) 
    3333   INTEGER            ::   ninist     = 0         !: initial state output flag (0/1) 
     34   !!---------------------------------------------------------------------- 
     35   !! was in restart but moved here because of the OFF line... better solution should be found... 
     36   !!---------------------------------------------------------------------- 
     37   INTEGER            ::   nitrst                 !: time step at which restart file should be written 
    3438   !!---------------------------------------------------------------------- 
    3539   !!                    output monitoring 
  • trunk/NEMO/OPA_SRC/TRD/trdmld.F90

    r521 r557  
    3737   USE trdmld_rst      ! restart for diagnosing the ML trends 
    3838   USE prtctl          ! Print control 
     39   USE restart         ! for lrst_oce 
    3940 
    4041   IMPLICIT NONE 
     
    4950   INTEGER ::   nidtrd, ndextrd1(jpi*jpj) 
    5051   INTEGER ::   ndimtrd1                         
    51    INTEGER, SAVE ::  ionce, icount                    
     52   INTEGER ::   ionce, icount                    
    5253 
    5354   !! * Substitutions 
     
    246247#endif 
    247248      !!---------------------------------------------------------------------- 
     249       
     250      ! ====================================================================== 
     251      ! 0. open restart trend when needed (at kt ==  nitrst-1) 
     252      ! ====================================================================== 
     253      IF( kt == nitrst-1 ) THEN 
     254         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_mld" 
     255         IF(lwp) WRITE(numout,*) '             open ocean restart_mld NetCDF file: '//clname 
     256         CALL iom_open( clname, nummldw, ldwrt = .TRUE., kiolib = jprstlib ) 
     257      ENDIF 
    248258 
    249259      ! ====================================================================== 
     
    702712      ! ====================================================================== 
    703713 
    704       CALL trd_mld_rst_write( kt )  
     714      IF( lrst_oce )   CALL trd_mld_rst_write( kt )  
    705715 
    706716   END SUBROUTINE trd_mld 
    707  
    708717 
    709718 
  • trunk/NEMO/OPA_SRC/TRD/trdmld_rst.F90

    r521 r557  
    1313   USE daymod          ! calendar 
    1414   USE iom             ! I/O module 
    15    USE restart         ! ocean restart  
    1615 
    1716   IMPLICIT NONE 
     
    2221   
    2322   CHARACTER (len=48) ::   crestart = 'initial.nc'   ! restart file name 
     23   INTEGER ::   nummldw                    ! logical unit for mld restart (write) 
     24 
    2425   !!--------------------------------------------------------------------------------- 
    25    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     26   !! OPA 9.0 , LOCEAN-IPSL (2006)  
     27   !! $Header$  
     28   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    2629   !!--------------------------------------------------------------------------------- 
    2730   
     
    3841      CHARACTER (len=35) :: charout 
    3942      INTEGER ::   jk                 ! loop indice 
     43      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
     44      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
    4045      !!-------------------------------------------------------------------------------- 
    41      
    42       IF( ( mod( kt, nstock ) == 0 ) .OR. ( kt == nitend ) ) THEN 
    43               
    44          IF(lwp) THEN 
    45             WRITE(numout,*) 
    46             WRITE(numout,*) 'trdmld_rst: output for ML diags. restart, with trd_mld_rst_write routine' 
    47             WRITE(numout,*) '~~~~~~~~~~' 
    48             WRITE(numout,*) 
     46 
     47      IF( kt == nitrst-1 ) THEN 
     48         IF( nitrst > 1.0e9 ) THEN    
     49            WRITE(clkt,*) nitrst 
     50         ELSE 
     51            WRITE(clkt,'(i8.8)') nitrst 
    4952         ENDIF 
     53         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_mld" 
     54         IF(lwp) WRITE(numout,*) '             open ocean restart_mld NetCDF file: '//clname 
     55         CALL iom_open( clname, nummldw, ldwrt = .TRUE., kiolib = jprstlib ) 
     56      ENDIF 
    5057 
    51          IF( ln_trdmld_instant ) THEN  
    52             !-- Temperature 
    53             CALL iom_rstput( kt, nitrst, nummldw, 'tmlbb'           , tmlbb           ) 
    54             CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           ) 
    55             CALL iom_rstput( kt, nitrst, nummldw, 'tmlatfb'         , tmlatfb         ) 
     58      IF( kt == nitrst .AND. lwp ) THEN 
     59         WRITE(numout,*) 
     60         WRITE(numout,*) 'trdmld_rst: output for ML diags. restart, with trd_mld_rst_write routine' 
     61         WRITE(numout,*) '~~~~~~~~~~' 
     62         WRITE(numout,*) 
     63      ENDIF 
    5664 
    57             !-- Salinity 
    58             CALL iom_rstput( kt, nitrst, nummldw, 'smlbb'           , smlbb           ) 
    59             CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           ) 
    60             CALL iom_rstput( kt, nitrst, nummldw, 'smlatfb'         , smlatfb         ) 
    61          ELSE 
    62             CALL iom_rstput( kt, nitrst, nummldw, 'rmldbn'          , rmldbn          ) 
     65      IF( ln_trdmld_instant ) THEN  
     66         !-- Temperature 
     67         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbb'           , tmlbb           ) 
     68         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           ) 
     69         CALL iom_rstput( kt, nitrst, nummldw, 'tmlatfb'         , tmlatfb         ) 
    6370 
    64             !-- Temperature 
    65             CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           ) 
    66             CALL iom_rstput( kt, nitrst, nummldw, 'tml_sumb'        , tml_sumb        ) 
    67             DO jk = 1, jpltrd 
    68                IF( jk < 10 )   THEN 
    69                   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk 
    70                ELSE 
    71                   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk 
    72                ENDIF 
    73                CALL iom_rstput( kt, nitrst, nummldw, charout,  tmltrd_csum_ub(:,:,jk) ) 
    74             ENDDO 
    75             CALL iom_rstput( kt, nitrst, nummldw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb ) 
     71         !-- Salinity 
     72         CALL iom_rstput( kt, nitrst, nummldw, 'smlbb'           , smlbb           ) 
     73         CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           ) 
     74         CALL iom_rstput( kt, nitrst, nummldw, 'smlatfb'         , smlatfb         ) 
     75      ELSE 
     76         CALL iom_rstput( kt, nitrst, nummldw, 'rmldbn'          , rmldbn          ) 
    7677 
    77             !-- Salinity 
    78             CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           ) 
    79             CALL iom_rstput( kt, nitrst, nummldw, 'sml_sumb'        , sml_sumb        ) 
    80             DO jk = 1, jpltrd 
    81                IF( jk < 10 )   THEN 
    82                   WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk 
    83                ELSE 
    84                   WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk 
    85                ENDIF 
    86                CALL iom_rstput( kt, nitrst, nummldw, charout , smltrd_csum_ub(:,:,jk) ) 
    87             ENDDO 
    88             CALL iom_rstput( kt, nitrst, nummldw, 'smltrd_atf_sumb' , smltrd_atf_sumb ) 
    89          ENDIF 
    90          ! 
    91          CALL iom_close( nummldw )     ! close the restart file (only at last time step) 
    92          !  
     78         !-- Temperature 
     79         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           ) 
     80         CALL iom_rstput( kt, nitrst, nummldw, 'tml_sumb'        , tml_sumb        ) 
     81         DO jk = 1, jpltrd 
     82            IF( jk < 10 )   THEN 
     83               WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk 
     84            ELSE 
     85               WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk 
     86            ENDIF 
     87            CALL iom_rstput( kt, nitrst, nummldw, charout,  tmltrd_csum_ub(:,:,jk) ) 
     88         ENDDO 
     89         CALL iom_rstput( kt, nitrst, nummldw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb ) 
     90 
     91         !-- Salinity 
     92         CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           ) 
     93         CALL iom_rstput( kt, nitrst, nummldw, 'sml_sumb'        , sml_sumb        ) 
     94         DO jk = 1, jpltrd 
     95            IF( jk < 10 )   THEN 
     96               WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk 
     97            ELSE 
     98               WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk 
     99            ENDIF 
     100            CALL iom_rstput( kt, nitrst, nummldw, charout , smltrd_csum_ub(:,:,jk) ) 
     101         ENDDO 
     102         CALL iom_rstput( kt, nitrst, nummldw, 'smltrd_atf_sumb' , smltrd_atf_sumb ) 
    93103      ENDIF 
     104      ! 
     105      CALL iom_close( nummldw )     ! close the restart file (only at last time step) 
     106      !  
    94107      !     
    95108   END SUBROUTINE trd_mld_rst_write 
     
    114127    ENDIF 
    115128 
    116     inum = 10 
    117     CALL iom_open( 'restart_mld', inum )                       ! Open 
     129    CALL iom_open( 'restart_mld', inum, kiolib = jprstlib )  
    118130 
    119131    IF( ln_trdmld_instant ) THEN  
  • trunk/NEMO/OPA_SRC/restart.F90

    r547 r557  
    2424   USE in_out_manager  ! I/O manager 
    2525   USE iom             ! I/O module 
    26    USE trdmld_oce      ! ! ocean active mixed layer tracers trends variables 
    2726   USE ini1d           ! re-initialization of u-v mask for the 1D configuration 
    2827   USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
     
    3736 
    3837   LOGICAL, PUBLIC ::   lrst_oce                  !: logical to control the oce restart write  
    39    INTEGER, PUBLIC ::   nitrst                    !: time step at which restart file should be written 
    4038   INTEGER, PUBLIC ::   numror, numrow, nummldw   !: logical unit for cean restart (read and write) 
    4139 
     
    7270       
    7371      IF    ( kt == nitrst-1 .AND. lrst_oce         ) THEN 
    74          CALL ctl_stop( 'rst_opn: we cannot create an ocean restart at every time step' ) 
     72         CALL ctl_stop( 'rst_opn: we cannot create an ocean restart at every time step',    & 
     73            &           'if the run ahs more than one tie step!!!' ) 
    7574         numrow = 0 
    7675      ELSEIF( kt == nitrst-1 .OR.  nitend == nit000 ) THEN   ! beware if model runs only one time step 
     
    8685         IF(lwp) WRITE(numout,*) '             open ocean restart.output NetCDF file: '//clname 
    8786         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib ) 
    88          IF( lk_trdmld )   THEN 
    89             clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_mld" 
    90             IF(lwp) WRITE(numout,*) '             open ocean restart_mld NetCDF file: '//clname 
    91             CALL iom_open( clname, nummldw, ldwrt = .TRUE., kiolib = jprstlib ) 
    92          ENDIF 
    9387         lrst_oce = .TRUE. 
    9488      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.