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 5535 for branches/UKMO/dev_r5107_eorca025_closea/NEMOGCM/NEMO/SAS_SRC – NEMO

Ignore:
Timestamp:
2015-07-02T16:00:36+02:00 (9 years ago)
Author:
davestorkey
Message:

Update UKMO/dev_r5107_eorca025_closea branch to rev 5518 of trunk
(= branching point of NEMO 3.6_stable).

Location:
branches/UKMO/dev_r5107_eorca025_closea/NEMOGCM/NEMO/SAS_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5107_eorca025_closea/NEMOGCM/NEMO/SAS_SRC/daymod.F90

    r5451 r5535  
    8080      ndt05   = NINT(0.5 * rdttra(1)) 
    8181 
    82       ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
    83       ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
    84       adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    85       IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error 
    86       ! 
    87       IF(lwp) THEN 
    88          WRITE(numout,*) ' *** Info used values : ' 
    89          WRITE(numout,*) '   date ndastp                                      : ', ndastp 
    90          WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
    91          WRITE(numout,*) 
    92       ENDIF 
     82      ! ==> clem: here we read the ocean restart for the date (only if it exists) 
     83      !           It is not clean and another solution should be found 
     84      CALL day_rst( nit000, 'READ' ) 
     85      ! ==> 
    9386 
    9487      ! set the calendar from ndastp (read in restart file and namelist) 
     
    285278      ! 
    286279   END SUBROUTINE day 
     280 
     281 
     282   SUBROUTINE day_rst( kt, cdrw ) 
     283      !!--------------------------------------------------------------------- 
     284      !!                   ***  ROUTINE ts_rst  *** 
     285      !! 
     286      !!  ** Purpose : Read or write calendar in restart file: 
     287      !! 
     288      !!  WRITE(READ) mode: 
     289      !!       kt        : number of time step since the begining of the experiment at the 
     290      !!                   end of the current(previous) run 
     291      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the 
     292      !!                   end of the current(previous) run (REAL -> keep fractions of day) 
     293      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer) 
     294      !! 
     295      !!   According to namelist parameter nrstdt, 
     296      !!       nrstdt = 0  no control on the date (nit000 is  arbitrary). 
     297      !!       nrstdt = 1  we verify that nit000 is equal to the last 
     298      !!                   time step of previous run + 1. 
     299      !!       In both those options, the  exact duration of the experiment 
     300      !!       since the beginning (cumulated duration of all previous restart runs) 
     301      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt. 
     302      !!       This is valid is the time step has remained constant. 
     303      !! 
     304      !!       nrstdt = 2  the duration of the experiment in days (adatrj) 
     305      !!                    has been stored in the restart file. 
     306      !!---------------------------------------------------------------------- 
     307      INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
     308      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
     309      ! 
     310      REAL(wp) ::   zkt, zndastp 
     311      !!---------------------------------------------------------------------- 
     312 
     313      IF( TRIM(cdrw) == 'READ' ) THEN 
     314 
     315         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
     316            ! Get Calendar informations 
     317            CALL iom_get( numror, 'kt', zkt )   ! last time-step of previous run 
     318            IF(lwp) THEN 
     319               WRITE(numout,*) ' *** Info read in restart : ' 
     320               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt ) 
     321               WRITE(numout,*) ' *** restart option' 
     322               SELECT CASE ( nrstdt ) 
     323               CASE ( 0 )   ;   WRITE(numout,*) ' nrstdt = 0 : no control of nit000' 
     324               CASE ( 1 )   ;   WRITE(numout,*) ' nrstdt = 1 : no control the date at nit000 (use ndate0 read in the namelist)' 
     325               CASE ( 2 )   ;   WRITE(numout,*) ' nrstdt = 2 : calendar parameters read in restart' 
     326               END SELECT 
     327               WRITE(numout,*) 
     328            ENDIF 
     329            ! Control of date 
     330            IF( nit000 - NINT( zkt ) /= 1 .AND. nrstdt /= 0 )                                         & 
     331                 &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
     332                 &                  ' verify the restart file or rerun with nrstdt = 0 (namelist)' ) 
     333            ! define ndastp and adatrj 
     334            IF ( nrstdt == 2 ) THEN 
     335               ! read the parameters correspondting to nit000 - 1 (last time step of previous run) 
     336               CALL iom_get( numror, 'ndastp', zndastp ) 
     337               ndastp = NINT( zndastp ) 
     338               CALL iom_get( numror, 'adatrj', adatrj  ) 
     339            ELSE 
     340               ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
     341               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
     342               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     343               ! note this is wrong if time step has changed during run 
     344            ENDIF 
     345         ELSE 
     346            ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
     347            ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
     348            adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     349         ENDIF 
     350         IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error 
     351         ! 
     352         IF(lwp) THEN 
     353            WRITE(numout,*) ' *** Info used values : ' 
     354            WRITE(numout,*) '   date ndastp                                      : ', ndastp 
     355            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     356            WRITE(numout,*) 
     357         ENDIF 
     358         ! 
     359      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN 
     360         ! 
     361         IF( kt == nitrst ) THEN 
     362            IF(lwp) WRITE(numout,*) 
     363            IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file  kt =', kt 
     364            IF(lwp) WRITE(numout,*) '~~~~~~~' 
     365         ENDIF 
     366         ! calendar control 
     367         CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step 
     368         CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date 
     369         CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
     370         !                                                                     ! the begining of the run [s] 
     371      ENDIF 
     372      ! 
     373   END SUBROUTINE day_rst 
    287374   !!====================================================================== 
    288375END MODULE daymod 
  • branches/UKMO/dev_r5107_eorca025_closea/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90

    r5451 r5535  
    5959   USE lbcnfd, ONLY: isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges 
    6060   USE icbstp          ! handle bergs, calving, themodynamics and transport 
     61#if defined key_bdy 
     62   USE bdyini          ! open boundary cond. setting       (bdy_init routine). clem: mandatory for LIM3 
     63   USE bdydta          ! open boundary cond. setting   (bdy_dta_init routine). clem: mandatory for LIM3 
     64#endif 
     65   USE bdy_par 
    6166 
    6267   IMPLICIT NONE 
     
    354359 
    355360                            CALL sbc_init   ! Forcings : surface module  
     361                             
     362      ! ==> clem: open boundaries init. is mandatory for LIM3 because ice BDY is not decoupled from   
     363      !           the environment of ocean BDY. Therefore bdy is called in both OPA and SAS modules.  
     364      !           This is not clean and should be changed in the future.  
     365      IF( lk_bdy        )   CALL     bdy_init 
     366      IF( lk_bdy        )   CALL bdy_dta_init 
     367      ! ==> 
    356368       
    357369      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
     
    502514      USE diawri    , ONLY: dia_wri_alloc 
    503515      USE dom_oce   , ONLY: dom_oce_alloc 
    504       USE oce       , ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass  
     516#if defined key_bdy    
     517      USE bdy_oce   , ONLY: bdy_oce_alloc 
     518      USE oce         ! clem: mandatory for LIM3 because needed for bdy arrays 
     519#else 
     520      USE oce       , ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass 
     521#endif 
    505522      ! 
    506523      INTEGER :: ierr,ierr1,ierr2,ierr3,ierr4,ierr5,ierr6 
     
    510527      ierr =        dia_wri_alloc   () 
    511528      ierr = ierr + dom_oce_alloc   ()          ! ocean domain 
    512       ALLOCATE( snwice_mass(jpi,jpj)  , snwice_mass_b(jpi,jpj),             & 
    513          &      snwice_fmass(jpi,jpj), STAT= ierr1 ) 
     529#if defined key_bdy 
     530      ierr = ierr + bdy_oce_alloc   ()          ! bdy masks (incl. initialization) 
     531      ierr = ierr + oce_alloc       ()          ! (tsn...) 
     532#endif 
     533 
     534#if ! defined key_bdy 
     535       ALLOCATE( snwice_mass(jpi,jpj)  , snwice_mass_b(jpi,jpj),             & 
     536         &      snwice_fmass(jpi,jpj)  , STAT= ierr1 ) 
    514537      ! 
    515538      ! lim code currently uses surface temperature and salinity in tsn array for initialisation 
    516       ! and ub, vb arrays in ice dynamics 
    517       ! so allocate enough of arrays to use 
    518       ! 
     539      ! and ub, vb arrays in ice dynamics, so allocate enough of arrays to use 
     540      ! clem: should not be needed. To be checked out 
    519541      jpm = MAX(jp_tem, jp_sal) 
    520542      ALLOCATE( tsn(jpi,jpj,1,jpm)  , STAT=ierr2 ) 
     
    523545      ALLOCATE( tsb(jpi,jpj,1,jpm)  , STAT=ierr5 ) 
    524546      ALLOCATE( sshn(jpi,jpj)       , STAT=ierr6 ) 
    525  
    526547      ierr = ierr + ierr1 + ierr2 + ierr3 + ierr4 + ierr5 + ierr6  
     548#endif 
    527549      ! 
    528550      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
  • branches/UKMO/dev_r5107_eorca025_closea/NEMOGCM/NEMO/SAS_SRC/step.F90

    r5451 r5535  
    3737 
    3838   USE timing           ! Timing             
     39 
     40   USE bdy_par          ! clem: mandatory for LIM3 
     41#if defined key_bdy 
     42   USE bdydta           ! clem: mandatory for LIM3 
     43#endif 
    3944 
    4045   IMPLICIT NONE 
     
    8186                             CALL iom_setkt( kstp - nit000 + 1, cxios_context )   ! tell iom we are at time step kstp 
    8287 
     88      ! ==> clem: open boundaries is mandatory for LIM3 because ice BDY is not decoupled from   
     89      !           the environment of ocean BDY. Therefore bdy is called in both OPA and SAS modules. 
     90      !           From SAS: ocean bdy data are wrong  (but we do not care) and ice bdy data are OK.   
     91      !           This is not clean and should be changed in the future.  
     92#if defined key_bdy 
     93      IF( lk_bdy     )       CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
     94#endif 
     95      ! ==> 
    8396                             CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
    8497 
Note: See TracChangeset for help on using the changeset viewer.