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 5282 for branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2015-05-18T17:19:50+02:00 (9 years ago)
Author:
diovino
Message:

Dev. branch CMCC4_simplification ticket #1456

Location:
branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC
Files:
8 deleted
63 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r4998 r5282  
    208208      ENDIF 
    209209 
    210       IF ( nacc /= 0 ) & 
    211          & CALL ctl_stop( ' nacc /= 0 and key_asminc :',  & 
    212          &                ' Assimilation increments have only been implemented', & 
    213          &                ' for synchronous time stepping' ) 
    214210 
    215211      IF ( ( ln_asmdin ).AND.( ln_asmiau ) )   & 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r4758 r5282  
    316316      ENDIF 
    317317 
    318       IF ( nsec_day == NINT(0.5_wp * rdttra(1)) .AND. zflag==1 ) THEN 
     318      IF ( nsec_day == NINT(0.5_wp * rdt) .AND. zflag==1 ) THEN 
    319319        ! 
    320320        kt_tide = kt 
     
    431431            ! We refresh nodal factors every day below 
    432432            ! This should be done somewhere else 
    433             IF ( nsec_day == NINT(0.5_wp * rdttra(1)) .AND. lk_first_btstp ) THEN 
    434                ! 
     433            IF ( nsec_day == NINT(0.5_wp * rdt) .AND. lk_first_btstp ) THEN 
     434                ! 
    435435               kt_tide = kt                
    436436               ! 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/C1D/domc1d.F90

    r4667 r5282  
    4444      !!---------------------------------------------------------------------- 
    4545      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    46          &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
    47          &             rn_rdtmax, rn_rdth     , nn_closea , ln_crs,    & 
    48          &             jphgr_msh, & 
     46         &             rn_atfp , rn_rdt,nn_closea , ln_crs,  jphgr_msh,        & 
    4947         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m, & 
    5048         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, & 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/CRS/crsfld.F90

    r4149 r5282  
    5252      !!      2. At time of output, rescale [1] by dimension and time 
    5353      !!         to yield the spatial and temporal average. 
    54       !!  See. diawri_dimg.h90, sbcmod.F90 
     54      !!  See. sbcmod.F90 
    5555      !! 
    5656      !! ** Method  :   
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DIA/diaar5.F90

    r4990 r5282  
    2121   USE timing         ! preformance summary 
    2222   USE wrk_nemo       ! working arrays 
     23   USE fldread        ! type FLD_N 
     24   USE phycst         ! physical constant 
     25   USE in_out_manager  ! I/O manager 
    2326 
    2427   IMPLICIT NONE 
     
    197200      REAL(wp) ::   zztmp   
    198201      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   zsaldta   ! Jan/Dec levitus salinity 
     202      ! reading initial file 
     203      LOGICAL  ::   ln_tsd_init      !: T & S data flag 
     204      LOGICAL  ::   ln_tsd_tradmp    !: internal damping toward input data flag 
     205      CHARACTER(len=100)            ::   cn_dir 
     206      TYPE(FLD_N)                   ::  sn_tem,sn_sal 
     207      INTEGER  ::   ios=0 
     208 
     209      NAMELIST/namtsd/ ln_tsd_init,ln_tsd_tradmp,cn_dir,sn_tem,sn_sal 
     210      ! 
     211 
     212      REWIND( numnam_ref )              ! Namelist namtsd in reference namelist : 
     213      READ  ( numnam_ref, namtsd, IOSTAT = ios, ERR = 901) 
     214901   IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtsd in reference namelist for dia_ar5', lwp ) 
     215      REWIND( numnam_cfg )              ! Namelist namtsd in configuration namelist : Parameters of the run 
     216      READ  ( numnam_cfg, namtsd, IOSTAT = ios, ERR = 902 ) 
     217902   IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtsd in configuration namelist for dia_ar5', lwp ) 
     218      IF(lwm) WRITE ( numond, namtsd ) 
     219      ! 
    199220      !!---------------------------------------------------------------------- 
    200221      ! 
     
    216237      END DO 
    217238      IF( lk_mpp )   CALL mpp_sum( vol0 ) 
    218        
    219       CALL iom_open ( 'data_1m_salinity_nomask', inum ) 
    220       CALL iom_get  ( inum, jpdom_data, 'vosaline', zsaldta(:,:,:,1), 1  ) 
    221       CALL iom_get  ( inum, jpdom_data, 'vosaline', zsaldta(:,:,:,2), 12 ) 
     239 
     240      CALL iom_open ( TRIM( cn_dir )//TRIM(sn_sal%clname), inum ) 
     241      CALL iom_get  ( inum, jpdom_data, TRIM(sn_sal%clvar), zsaldta(:,:,:,1), 1  ) 
     242      CALL iom_get  ( inum, jpdom_data, TRIM(sn_sal%clvar), zsaldta(:,:,:,2), 12 ) 
    222243      CALL iom_close( inum ) 
    223244      sn0(:,:,:) = 0.5_wp * ( zsaldta(:,:,:,1) + zsaldta(:,:,:,2) )         
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DIA/diafwb.F90

    r4990 r5282  
    115115          
    116116         ! Conversion in m3 
    117          a_fwf    = a_fwf * rdttra(1) * 1.e-3  
     117         a_fwf    = a_fwf * rdt * 1.e-3 
    118118          
    119119         ! fwf correction to bring back the mean ssh to zero 
     
    382382         WRITE(inum,*) 
    383383         WRITE(inum,*)    'Net freshwater budget ' 
    384          WRITE(inum,9010) '  fwf    = ',a_fwf,   ' m3 =', a_fwf   /(FLOAT(nitend-nit000+1)*rdttra(1)) * 1.e-6,' Sv' 
     384         WRITE(inum,9010) '  fwf    = ',a_fwf,   ' m3 =', a_fwf   /(FLOAT(nitend-nit000+1)*rdt) * 1.e-6,' Sv' 
    385385         WRITE(inum,*) 
    386386         WRITE(inum,9010) '  zarea =',zarea 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DIA/diaharm.F90

    r4990 r5282  
    2323   USE ioipsl          ! NetCDF IPSL library 
    2424   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    25    USE diadimg         ! To write dimg 
    2625   USE timing          ! preformance summary 
    2726   USE wrk_nemo        ! working arrays 
     
    388387      !!---------------------------------------------------------------------- 
    389388 
    390 #if defined key_dimgout 
    391       cdfile_name_T = TRIM(cexper)//'_Tidal_harmonics_gridT.dimgproc' 
    392       cdfile_name_U = TRIM(cexper)//'_Tidal_harmonics_gridU.dimgproc' 
    393       cdfile_name_V = TRIM(cexper)//'_Tidal_harmonics_gridV.dimgproc' 
    394 #endif 
     389!#if  
     390!#endif 
    395391 
    396392      IF(lwp) WRITE(numout,*) '  ' 
    397393      IF(lwp) WRITE(numout,*) 'dia_wri_harm : Write harmonic analysis results' 
    398 #if defined key_dimgout 
    399       IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~  Output files: ', TRIM(cdfile_name_T) 
    400       IF(lwp) WRITE(numout,*) '                             ', TRIM(cdfile_name_U) 
    401       IF(lwp) WRITE(numout,*) '                             ', TRIM(cdfile_name_V) 
    402 #endif 
     394!#if  
     395!#endif 
    403396      IF(lwp) WRITE(numout,*) '  ' 
    404397 
     
    406399      !///////////// 
    407400      ! 
    408 #if defined key_dimgout 
    409       cltext='Elevation amplitude and phase' 
    410       CALL dia_wri_dimg(TRIM(cdfile_name_T), TRIM(cltext), out_eta, 2*nb_ana, '2') 
    411 #else 
     401!#if  
     402!#else 
    412403      DO jh = 1, nb_ana 
    413404      CALL iom_put( TRIM(tname(jh))//'x', out_eta(:,:,jh) ) 
    414405      CALL iom_put( TRIM(tname(jh))//'y', out_eta(:,:,nb_ana+jh) ) 
    415406      END DO 
    416 #endif 
     407!#endif 
    417408 
    418409      ! B) ubar 
    419410      !///////// 
    420411      ! 
    421 #if defined key_dimgout 
    422       cltext='ubar amplitude and phase' 
    423       CALL dia_wri_dimg(TRIM(cdfile_name_U), TRIM(cltext), out_u, 2*nb_ana, '2') 
    424 #else 
     412!#if  
     413!#else 
    425414      DO jh = 1, nb_ana 
    426415      CALL iom_put( TRIM(tname(jh))//'x_u', out_u(:,:,jh) ) 
    427416      CALL iom_put( TRIM(tname(jh))//'y_u', out_u(:,:,nb_ana+jh) ) 
    428417      END DO 
    429 #endif 
     418!#endif 
    430419 
    431420      ! C) vbar 
    432421      !///////// 
    433422      ! 
    434 #if defined key_dimgout 
    435       cltext='vbar amplitude and phase' 
    436       CALL dia_wri_dimg(TRIM(cdfile_name_V), TRIM(cltext), out_v, 2*nb_ana, '2') 
    437 #else 
     423!#if  
     424!#else 
    438425      DO jh = 1, nb_ana 
    439426         CALL iom_put( TRIM(tname(jh))//'x_v', out_v(:,:,jh       ) ) 
    440427         CALL iom_put( TRIM(tname(jh))//'y_v', out_v(:,:,jh+nb_ana) ) 
    441428      END DO 
    442 #endif 
     429!#endif 
    443430      ! 
    444431   END SUBROUTINE dia_wri_harm 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DIA/dianam.F90

    r2528 r5282  
    7272 
    7373      IF( llfsec .OR. kfreq < 0 ) THEN   ;   inbsec = kfreq                       ! output frequency already in seconds 
    74       ELSE                               ;   inbsec = kfreq * NINT( rdttra(1) )   ! from time-step to seconds 
     74      ELSE                               ;   inbsec = kfreq * NINT( rdt )   ! from time-step to seconds 
    7575      ENDIF 
    7676      iddss = NINT( rday          )                                         ! number of seconds in 1 day 
     
    116116      ! date of the beginning and the end of the run 
    117117 
    118       zdrun = rdttra(1) / rday * REAL( nitend - nit000, wp )                ! length of the run in days 
    119       zjul  = fjulday - rdttra(1) / rday 
     118      zdrun = rdt / rday * REAL( nitend - nit000, wp )                ! length of the run in days 
     119      zjul  = fjulday - rdt / rday 
    120120      CALL ju2ymds( zjul        , iyear1, imonth1, iday1, zsec1 )           ! year/month/day of the beginning of run 
    121121      CALL ju2ymds( zjul + zdrun, iyear2, imonth2, iday2, zsec2 )           ! year/month/day of the end       of run 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DIA/diaptr.F90

    r4990 r5282  
    585585         niter = ( nit000 - 1 ) / nn_fptr 
    586586         zdt = rdt 
    587          IF( nacc == 1 )   zdt = rdtmin 
    588587         ! 
    589588         IF(lwp) THEN 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r4990 r5282  
    4343   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    4444   USE in_out_manager  ! I/O manager 
    45    USE diadimg         ! dimg direct access file format output 
    4645   USE iom 
    4746   USE ioipsl 
     
    9796  END FUNCTION dia_wri_alloc 
    9897 
    99 #if defined key_dimgout 
    100    !!---------------------------------------------------------------------- 
    101    !!   'key_dimgout'                                      DIMG output file 
    102    !!---------------------------------------------------------------------- 
    103 #   include "diawri_dimg.h90" 
    104  
    105 #else 
    10698   !!---------------------------------------------------------------------- 
    10799   !!   Default option                                   NetCDF output file 
    108100   !!---------------------------------------------------------------------- 
    109 # if defined key_iomput 
     101#if defined key_iomput 
    110102   !!---------------------------------------------------------------------- 
    111103   !!   'key_iomput'                                        use IOM library 
     
    418410      ! Define frequency of output and means 
    419411      zdt = rdt 
    420       IF( nacc == 1 ) zdt = rdtmin 
    421412      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!) 
    422413      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time) 
     
    762753      IF( lk_vvl ) THEN 
    763754         zw3d(:,:,:) = ( ( fse3t_n(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 
    764          CALL histwrite( nid_T, "vovvle3t", it, fse3t_n (:,:,:) , ndim_T , ndex_T  )   ! level thickness 
     755         CALL histwrite( nid_T, "vovvle3t", it, fse3t_n(:,:,:) , ndim_T , ndex_T  )   ! level thickness 
    765756         CALL histwrite( nid_T, "vovvldep", it, fsdept_n(:,:,:) , ndim_T , ndex_T  )   ! t-point depth 
    766757         CALL histwrite( nid_T, "vovvldef", it, zw3d             , ndim_T , ndex_T  )   ! level thickness deformation 
     
    914905      ! 
    915906   END SUBROUTINE dia_wri 
    916 # endif 
    917  
    918 #endif 
     907#endif 
     908 
     909 
    919910 
    920911   SUBROUTINE dia_wri_state( cdfile_name, kt ) 
     
    10351026      ! ----------------- 
    10361027      CALL histclo( id_i ) 
    1037 #if ! defined key_iomput && ! defined key_dimgout 
     1028#if ! defined key_iomput 
    10381029      IF( ninist /= 1  ) THEN 
    10391030         CALL histclo( nid_T ) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r5002 r5282  
    2020   !! 
    2121   !!   we suppose that the time step is deviding the number of second of in a day 
    22    !!             ---> MOD( rday, rdttra(1) ) == 0 
     22   !!             ---> MOD( rday, rdt ) == 0 
    2323   !! 
    2424   !!           ----------- WARNING ----------- 
     
    7373      !!---------------------------------------------------------------------- 
    7474      ! 
    75       ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0 
    76       IF( MOD( rday     , rdttra(1) ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
     75      ! all calendar staff is based on the fact that MOD( rday, rdt ) == 0 
     76      IF( MOD( rday     , rdt ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
    7777      IF( MOD( rday     , 2.        ) /= 0. )   CALL ctl_stop( 'the number of second of in a day must be an even number'    ) 
    78       IF( MOD( rdttra(1), 2.        ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
     78      IF( MOD( rdt, 2.        ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           ) 
    7979      nsecd   = NINT(rday           ) 
    8080      nsecd05 = NINT(0.5 * rday     ) 
    81       ndt     = NINT(      rdttra(1)) 
    82       ndt05   = NINT(0.5 * rdttra(1)) 
     81      ndt     = NINT(      rdt) 
     82      ndt05   = NINT(0.5 * rdt) 
    8383 
    8484      IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' ) 
     
    218218      nsec_week  = nsec_week  + ndt 
    219219      nsec_day   = nsec_day   + ndt 
    220       adatrj  = adatrj  + rdttra(1) / rday 
    221       fjulday = fjulday + rdttra(1) / rday 
     220      adatrj  = adatrj  + rdt / rday 
     221      fjulday = fjulday + rdt / rday 
    222222      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < zprec )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error 
    223223      IF( ABS(adatrj  - REAL(NINT(adatrj ),wp)) < zprec )   adatrj  = REAL(NINT(adatrj ),wp)   ! avoid truncation error 
     
    334334               ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    335335               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
    336                adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     336               adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 
    337337               ! note this is wrong if time step has changed during run 
    338338            ENDIF 
     
    340340            ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    341341            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 
     342            adatrj = ( REAL( nit000-1, wp ) * rdt ) / rday 
    343343         ENDIF 
    344344         IF( ABS(adatrj  - REAL(NINT(adatrj),wp)) < 0.1 / rday )   adatrj = REAL(NINT(adatrj),wp)   ! avoid truncation error 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r4990 r5282  
    3535   REAL(wp), PUBLIC ::   rn_e3zps_rat    !: minimum thickness ration for partial steps 
    3636   INTEGER , PUBLIC ::   nn_msh          !: = 1 create a mesh-mask file 
    37    INTEGER , PUBLIC ::   nn_acc          !: = 0/1 use of the acceleration of convergence technique 
    3837   REAL(wp), PUBLIC ::   rn_atfp         !: asselin time filter parameter 
    39    REAL(wp), PUBLIC ::   rn_rdt          !: time step for the dynamics (and tracer if nacc=0) 
    40    REAL(wp), PUBLIC ::   rn_rdtmin       !: minimum time step on tracers 
    41    REAL(wp), PUBLIC ::   rn_rdtmax       !: maximum time step on tracers 
    42    REAL(wp), PUBLIC ::   rn_rdth         !: depth variation of tracer step 
     38   REAL(wp), PUBLIC ::   rn_rdt          !: time step for the dynamics and tracer 
    4339   INTEGER , PUBLIC ::   nn_closea       !: =0 suppress closed sea/lake from the ORCA domain or not (=1) 
    4440   INTEGER , PUBLIC ::   nn_euler        !: =0 start with forward time step or not (=1) 
     
    9490   REAL(wp), PUBLIC ::   e3zps_rat       !: minimum thickness ration for partial steps 
    9591   INTEGER , PUBLIC ::   nmsh            !: = 1 create a mesh-mask file 
    96    INTEGER , PUBLIC ::   nacc            !: = 0/1 use of the acceleration of convergence technique 
    9792   REAL(wp), PUBLIC ::   atfp            !: asselin time filter parameter 
    98    REAL(wp), PUBLIC ::   rdt             !: time step for the dynamics (and tracer if nacc=0) 
    99    REAL(wp), PUBLIC ::   rdtmin          !: minimum time step on tracers 
    100    REAL(wp), PUBLIC ::   rdtmax          !: maximum time step on tracers 
    101    REAL(wp), PUBLIC ::   rdth            !: depth variation of tracer step 
     93   REAL(wp), PUBLIC ::   rdt             !: time step for the dynamics and tracer 
    10294 
    10395   !                                                  !!! associated variables 
    10496   INTEGER , PUBLIC                 ::   neuler        !: restart euler forward option (0=Euler) 
    10597   REAL(wp), PUBLIC                 ::   atfp1         !: asselin time filter coeff. (atfp1= 1-2*atfp) 
    106    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   rdttra  !: vertical profile of tracer time step 
    107    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dtra  !: = 2*rdttra except at nit000 (=rdttra) if neuler=0 
    108  
    109    !                                         !!* Namelist namcla : cross land advection 
    110    INTEGER, PUBLIC ::   nn_cla               !: =1 cross land advection for exchanges through some straits (ORCA2) 
     98   REAL(wp), PUBLIC ::   r2dt         !: = 2*rdt except at nit000 (=rdt) if neuler=0 
    11199 
    112100   !!---------------------------------------------------------------------- 
     
    336324      ierr(:) = 0 
    337325      ! 
    338       ALLOCATE( rdttra(jpk), r2dtra(jpk), mig(jpi), mjg(jpj), nfiimpp(jpni,jpnj),  & 
     326      ALLOCATE( mig(jpi), mjg(jpj), nfiimpp(jpni,jpnj),  & 
    339327         &      nfipproc(jpni,jpnj), nfilcit(jpni,jpnj), STAT=ierr(1) ) 
    340          ! 
     328        ! 
    341329      ALLOCATE( nimppt(jpnij) , ibonit(jpnij) , nlcit(jpnij) , nlcjt(jpnij) ,     & 
    342330         &      njmppt(jpnij) , ibonjt(jpnij) , nldit(jpnij) , nldjt(jpnij) ,     & 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r4990 r5282  
    8181      ENDIF 
    8282      ! 
    83                              CALL dom_nam      ! read namelist ( namrun, namdom, namcla ) 
     83                             CALL dom_nam      ! read namelist ( namrun, namdom ) 
    8484                             CALL dom_clo      ! Closed seas and lake 
    8585                             CALL dom_hgr      ! Horizontal mesh 
     
    131131      !! ** input   : - namrun namelist 
    132132      !!              - namdom namelist 
    133       !!              - namcla namelist 
    134133      !!              - namnc4 namelist   ! "key_netcdf4" only 
    135134      !!---------------------------------------------------------------------- 
     
    137136      NAMELIST/namrun/ nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   & 
    138137         &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
    139          &             nn_write, ln_dimgnnn, ln_mskland  , ln_clobber   , nn_chunksz, nn_euler 
     138         &             nn_write, ln_mskland  , ln_clobber   , nn_chunksz, nn_euler 
    140139      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    141          &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
    142          &             rn_rdtmax, rn_rdth     , nn_closea , ln_crs,    & 
    143          &             jphgr_msh, & 
     140         &             rn_atfp, rn_rdt ,  nn_closea , ln_crs,  jphgr_msh,       & 
    144141         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m, & 
    145142         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, & 
    146143         &             ppa2, ppkth2, ppacr2 
    147       NAMELIST/namcla/ nn_cla 
     144 
    148145#if defined key_netcdf4 
    149146      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
     
    180177         WRITE(numout,*) '      frequency of restart file       nn_stock   = ', nn_stock 
    181178         WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write 
    182          WRITE(numout,*) '      multi file dimgout              ln_dimgnnn = ', ln_dimgnnn 
    183179         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland 
    184180         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber 
     
    259255         WRITE(numout,*) '      ocean time step                       rn_rdt    = ', rn_rdt 
    260256         WRITE(numout,*) '      asselin time filter parameter         rn_atfp   = ', rn_atfp 
    261          WRITE(numout,*) '      acceleration of converge              nn_acc    = ', nn_acc 
    262          WRITE(numout,*) '        nn_acc=1: surface tracer rdt        rn_rdtmin = ', rn_rdtmin 
    263          WRITE(numout,*) '                  bottom  tracer rdt        rdtmax    = ', rn_rdtmax 
    264          WRITE(numout,*) '                  depth of transition       rn_rdth   = ', rn_rdth 
    265257         WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea = ', nn_closea 
    266258         WRITE(numout,*) '      online coarsening of dynamical fields ln_crs    = ', ln_crs 
     
    289281      e3zps_rat = rn_e3zps_rat 
    290282      nmsh      = nn_msh 
    291       nacc      = nn_acc 
    292283      atfp      = rn_atfp 
    293284      rdt       = rn_rdt 
    294       rdtmin    = rn_rdtmin 
    295       rdtmax    = rn_rdtmin 
    296       rdth      = rn_rdth 
    297  
    298       REWIND( numnam_ref )              ! Namelist namcla in reference namelist : Cross land advection 
    299       READ  ( numnam_ref, namcla, IOSTAT = ios, ERR = 905) 
    300 905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in reference namelist', lwp ) 
    301  
    302       REWIND( numnam_cfg )              ! Namelist namcla in configuration namelist : Cross land advection 
    303       READ  ( numnam_cfg, namcla, IOSTAT = ios, ERR = 906 ) 
    304 906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in configuration namelist', lwp ) 
    305       IF(lwm) WRITE( numond, namcla ) 
    306  
    307       IF(lwp) THEN 
    308          WRITE(numout,*) 
    309          WRITE(numout,*) '   Namelist namcla' 
    310          WRITE(numout,*) '      cross land advection                 nn_cla    = ', nn_cla 
    311       ENDIF 
    312       IF ( nn_cla .EQ. 1 ) THEN 
    313          IF  ( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN   ! ORCA R2  
    314             CONTINUE 
    315          ELSE 
    316             CALL ctl_stop( 'STOP', 'Cross land advation iplemented only for ORCA2 configuration: cp_cfg = "orca" and jp_cfg = 2 ' ) 
    317          ENDIF 
    318       ENDIF 
    319285 
    320286#if defined key_netcdf4 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/domhgr.F90

    r4990 r5282  
    134134         IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN    ! ORCA R2 configuration 
    135135            !                                             ! ===================== 
    136             IF( nn_cla == 0 ) THEN 
    137                ! 
    138136               ii0 = 139   ;   ii1 = 140        ! Gibraltar Strait (e2u = 20 km) 
    139137               ij0 = 102   ;   ij1 = 102   ;   e2u( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) =  20.e3 
     
    147145               IF(lwp) WRITE(numout,*) '             orca_r2: Bab el Mandeb: e2u reduced to 30 km' 
    148146               IF(lwp) WRITE(numout,*) '                                     e1v reduced to 18 km' 
    149             ENDIF 
    150147 
    151148            ii0 = 145   ;   ii1 = 146        ! Danish Straits (e2u = 10 km) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r4990 r5282  
    366366      IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN   ! ORCA_R2 configuration 
    367367         !                                                 ! Increased lateral friction near of some straits 
    368          IF( nn_cla == 0 ) THEN 
    369368            !                                ! Gibraltar strait  : partial slip (fmask=0.5) 
    370369            ij0 = 101   ;   ij1 = 101 
     
    379378            ii0 = 159   ;   ii1 = 159   ;   fmask( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 1:jpk ) =  1._wp 
    380379            ! 
    381          ENDIF 
    382380         !                                ! Danish straits  : strong slip (fmask > 2) 
    383381! We keep this as an example but it is instable in this case  
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/domstp.F90

    r4292 r5282  
    4141      !!      filter parameter read in namelist 
    4242      !!              - Model time step: 
    43       !!      nacc = 0 : synchronous time intergration.  
    44       !!      There is one time step only, defined by: rdt, rdttra(k)=rdt 
    45       !!      nacc = 1 : accelerating the convergence. There is 2 different 
    46       !!      time steps for dynamics and tracers: 
    47       !!        rdt      : dynamical part 
    48       !!        rdttra(k): temperature and salinity 
    49       !!      The tracer time step is a function of vertical level. the model 
    50       !!      reference time step ( i.e. for wind stress, surface heat and 
    51       !!      salt fluxes) is the surface tracer time step is rdttra(1). 
    52       !!         N.B. depth dependent acceleration of convergence is not im- 
    53       !!      plemented for s-coordinate. 
     43      !!                synchronous time intergration. 
     44      !!      There is one time step only, defined by: rdt for dynamics and 
     45      !!      tracer,wind stress, surface heat and salt fluxes 
    5446      !! 
    55       !! ** Action  : - rdttra   : vertical profile of tracer time step 
     47      !! ** Action  : [REMOVED - rdttra: vertical profile of tracer time step] 
    5648      !!              - atfp1    : = 1 - 2*atfp 
    5749      !! 
     
    7264      atfp1 = 1. - 2. * atfp 
    7365 
    74       SELECT CASE ( nacc ) 
     66      IF(lwp) WRITE(numout,*)'               synchronous time stepping' 
     67      IF(lwp) WRITE(numout,*)'               dynamics and tracer time step = ', rdt/3600., ' hours' 
    7568 
    76          CASE ( 0 )                ! Synchronous time stepping 
    77             IF(lwp) WRITE(numout,*)'               synchronous time stepping' 
    78             IF(lwp) WRITE(numout,*)'               dynamics and tracer time step = ', rdt/3600., ' hours' 
    79  
    80             rdttra(:) = rdt 
    81  
    82          CASE ( 1 )                ! Accelerating the convergence 
    83             IF(lwp) WRITE(numout,*) '              no tracer damping in the turbocline' 
    84             IF(lwp) WRITE(numout,*)'               accelerating the convergence' 
    85             IF(lwp) WRITE(numout,*)'               dynamics time step = ', rdt/3600., ' hours' 
    86             IF( ln_sco .AND. rdtmin /= rdtmax .AND. lk_vvl )   & 
    87                  & CALL ctl_stop ( ' depth dependent acceleration of convergence not implemented in s-coordinates & 
    88                  &                   nor in variable volume' ) 
    89             IF(lwp) WRITE(numout,*)'         tracers   time step :  dt (hours)  level' 
    90  
    91             DO jk = 1, jpk 
    92                IF( gdept_1d(jk) <= rdth ) rdttra(jk) = rdtmin 
    93                IF( gdept_1d(jk) >  rdth ) THEN 
    94                   rdttra(jk) = rdtmin + ( rdtmax - rdtmin )   & 
    95                                       * ( EXP( ( gdept_1d(jk ) - rdth ) / rdth ) - 1. )   & 
    96                                       / ( EXP( ( gdept_1d(jpk) - rdth ) / rdth ) - 1. ) 
    97                ENDIF 
    98                IF(lwp) WRITE(numout,"(36x,f5.2,5x,i3)") rdttra(jk)/3600., jk 
    99             END DO   
    100  
    101          CASE DEFAULT              ! E R R O R  
    102  
    103             WRITE(ctmp1,*) ' nacc value e r r o r, nacc= ',nacc 
    104             CALL ctl_stop( ctmp1 ) 
    105  
    106       END SELECT 
    10769 
    10870   END SUBROUTINE dom_stp 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/domvvl.F90

    r4998 r5282  
    156156      ! Vertical scale factor interpolations 
    157157      ! ------------------------------------ 
    158       CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n (:,:,:), 'W'  ) 
     158      CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n(:,:,:), 'W'  ) 
    159159      CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3uw_n(:,:,:), 'UW' ) 
    160160      CALL dom_vvl_interpol( fse3v_n(:,:,:), fse3vw_n(:,:,:), 'VW' ) 
    161       CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3w_b (:,:,:), 'W'  ) 
     161      CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3w_b(:,:,:), 'W'  ) 
    162162      CALL dom_vvl_interpol( fse3u_b(:,:,:), fse3uw_b(:,:,:), 'UW' ) 
    163163      CALL dom_vvl_interpol( fse3v_b(:,:,:), fse3vw_b(:,:,:), 'VW' ) 
     
    627627      ! - ML - fse3u_b and fse3v_b are allready computed in dynnxt 
    628628      ! - JC - hu_b, hv_b, hur_b, hvr_b also 
    629       CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3f_n (:,:,:), 'F'  ) 
     629      CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3f_n(:,:,:), 'F'  ) 
    630630      ! Vertical scale factor interpolations 
    631631      ! ------------------------------------ 
    632       CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n (:,:,:), 'W'  ) 
     632      CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n(:,:,:), 'W'  ) 
    633633      CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3uw_n(:,:,:), 'UW' ) 
    634634      CALL dom_vvl_interpol( fse3v_n(:,:,:), fse3vw_n(:,:,:), 'VW' ) 
    635       CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3w_b (:,:,:), 'W'  ) 
     635      CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3w_b(:,:,:), 'W'  ) 
    636636      CALL dom_vvl_interpol( fse3u_b(:,:,:), fse3uw_b(:,:,:), 'UW' ) 
    637637      CALL dom_vvl_interpol( fse3v_b(:,:,:), fse3vw_b(:,:,:), 'VW' ) 
     
    663663      ! Local depth and Inverse of the local depth of the water column at u- and v- points 
    664664      ! ---------------------------------------------------------------------------------- 
    665       hu (:,:) = hu_a (:,:) 
    666       hv (:,:) = hv_a (:,:) 
     665      hu(:,:) = hu_a(:,:) 
     666      hv(:,:) = hv_a(:,:) 
    667667 
    668668      ! Inverse of the local depth 
     
    680680      ! ============= 
    681681      z_e3t_def(:,:,:) = ( ( fse3t_n(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 
    682       CALL iom_put( "cellthc" , fse3t_n  (:,:,:) ) 
    683       CALL iom_put( "tpt_dep" , fsde3w_n (:,:,:) ) 
     682      CALL iom_put( "cellthc" , fse3t_n(:,:,:) ) 
     683      CALL iom_put( "tpt_dep" , fsde3w_n(:,:,:) ) 
    684684      CALL iom_put( "e3tdef"  , z_e3t_def(:,:,:) ) 
    685685 
     
    10571057         !                                             ! ===================== 
    10581058      !! acc 
    1059          IF( nn_cla == 0 ) THEN 
    1060             ! 
    10611059            ii0 = 139   ;   ii1 = 140        ! Gibraltar Strait (e2u was modified) 
    10621060            ij0 = 102   ;   ij1 = 102 
     
    11051103               END DO 
    11061104            END DO 
    1107          ENDIF 
    11081105 
    11091106         ii0 = 145   ;   ii1 = 146        ! Danish Straits (e2u was modified) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r5040 r5282  
    507507            IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN    ! ORCA R2 configuration 
    508508               !                                             ! ===================== 
    509                IF( nn_cla == 0 ) THEN 
    510                   ii0 = 140   ;   ii1 = 140                  ! Gibraltar Strait open  
     509                  ii0 = 140   ;   ii1 = 140                  ! Gibraltar Strait open 
    511510                  ij0 = 102   ;   ij1 = 102                  ! (Thomson, Ocean Modelling, 1995) 
    512511                  DO ji = mi0(ii0), mi1(ii1) 
     
    527526                  IF(lwp) WRITE(numout,*) 
    528527                  IF(lwp) WRITE(numout,*) '      orca_r2: Bab el Mandeb strait open at i=',ii0,' j=',ij0 
    529                ENDIF 
    530528               ! 
    531529            ENDIF 
     
    548546            IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN    ! ORCA R2 configuration 
    549547               ! 
    550               IF( nn_cla == 0 ) THEN 
    551                  ii0 = 140   ;   ii1 = 140                   ! Gibraltar Strait open  
     548                 ii0 = 140   ;   ii1 = 140                   ! Gibraltar Strait open 
    552549                 ij0 = 102   ;   ij1 = 102                   ! (Thomson, Ocean Modelling, 1995) 
    553550                 DO ji = mi0(ii0), mi1(ii1) 
     
    568565                 IF(lwp) WRITE(numout,*) 
    569566                 IF(lwp) WRITE(numout,*) '             orca_r2: Bab el Mandeb strait open at i=',ii0,' j=',ij0 
    570               ENDIF 
    571567              ! 
    572568           ENDIF 
     
    19951991 
    19961992      IF( nprint == 1 .AND. lwp )   THEN 
    1997          WRITE(numout,*) ' MAX val hif   t ', MAXVAL( hift (:,:) ), ' f ', MAXVAL( hiff (:,:) ),  & 
    1998             &                        ' u ',   MAXVAL( hifu (:,:) ), ' v ', MAXVAL( hifv (:,:) ) 
    1999          WRITE(numout,*) ' MIN val hif   t ', MINVAL( hift (:,:) ), ' f ', MINVAL( hiff (:,:) ),  & 
    2000             &                        ' u ',   MINVAL( hifu (:,:) ), ' v ', MINVAL( hifv (:,:) ) 
     1993         WRITE(numout,*) ' MAX val hif   t ', MAXVAL( hift(:,:) ), ' f ', MAXVAL( hiff(:,:) ),  & 
     1994            &                        ' u ',   MAXVAL( hifu(:,:) ), ' v ', MAXVAL( hifv(:,:) ) 
     1995         WRITE(numout,*) ' MIN val hif   t ', MINVAL( hift(:,:) ), ' f ', MINVAL( hiff(:,:) ),  & 
     1996            &                        ' u ',   MINVAL( hifu(:,:) ), ' v ', MINVAL( hifv(:,:) ) 
    20011997         WRITE(numout,*) ' MAX val hbat  t ', MAXVAL( hbatt(:,:) ), ' f ', MAXVAL( hbatf(:,:) ),  & 
    20021998            &                        ' u ',   MAXVAL( hbatu(:,:) ), ' v ', MAXVAL( hbatv(:,:) ) 
     
    20682064#endif 
    20692065 
    2070       fsdept(:,:,:) = gdept_0 (:,:,:) 
    2071       fsdepw(:,:,:) = gdepw_0 (:,:,:) 
     2066      fsdept(:,:,:) = gdept_0(:,:,:) 
     2067      fsdepw(:,:,:) = gdepw_0(:,:,:) 
    20722068      fsde3w(:,:,:) = gdep3w_0(:,:,:) 
    2073       fse3t (:,:,:) = e3t_0   (:,:,:) 
    2074       fse3u (:,:,:) = e3u_0   (:,:,:) 
    2075       fse3v (:,:,:) = e3v_0   (:,:,:) 
    2076       fse3f (:,:,:) = e3f_0   (:,:,:) 
    2077       fse3w (:,:,:) = e3w_0   (:,:,:) 
    2078       fse3uw(:,:,:) = e3uw_0  (:,:,:) 
    2079       fse3vw(:,:,:) = e3vw_0  (:,:,:) 
     2069      fse3t(:,:,:) = e3t_0(:,:,:) 
     2070      fse3u(:,:,:) = e3u_0(:,:,:) 
     2071      fse3v(:,:,:) = e3v_0(:,:,:) 
     2072      fse3f(:,:,:) = e3f_0(:,:,:) 
     2073      fse3w(:,:,:) = e3w_0(:,:,:) 
     2074      fse3uw(:,:,:) = e3uw_0(:,:,:) 
     2075      fse3vw(:,:,:) = e3vw_0(:,:,:) 
    20802076!! 
    20812077      ! HYBRID :  
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DOM/dtatsd.F90

    r4990 r5282  
    174174            END DO 
    175175         END DO 
    176          IF( nn_cla == 1 ) THEN                          ! Cross Land advection 
    177             il0 = 138   ;   il1 = 138                          ! set T & S profile at Gibraltar Strait 
    178             ij0 = 101   ;   ij1 = 102 
    179             ii0 = 139   ;   ii1 = 139 
    180             DO jl = mi0(il0), mi1(il1) 
    181                DO jj = mj0(ij0), mj1(ij1) 
    182                   DO ji = mi0(ii0), mi1(ii1) 
    183                      sf_tsd(jp_tem)%fnow(ji,jj,:) = sf_tsd(jp_tem)%fnow(jl,jj,:) 
    184                      sf_tsd(jp_sal)%fnow(ji,jj,:) = sf_tsd(jp_sal)%fnow(jl,jj,:) 
    185                   END DO 
    186                END DO 
    187             END DO 
    188             il0 = 164   ;   il1 = 164                          ! set T & S profile at Bab el Mandeb Strait 
    189             ij0 =  87   ;   ij1 =  88 
    190             ii0 = 161   ;   ii1 = 163 
    191             DO jl = mi0(il0), mi1(il1) 
    192                DO jj = mj0(ij0), mj1(ij1) 
    193                   DO ji = mi0(ii0), mi1(ii1) 
    194                      sf_tsd(jp_tem)%fnow(ji,jj,:) = sf_tsd(jp_tem)%fnow(jl,jj,:) 
    195                      sf_tsd(jp_sal)%fnow(ji,jj,:) = sf_tsd(jp_sal)%fnow(jl,jj,:) 
    196                   END DO 
    197                END DO 
    198             END DO 
    199          ELSE                                            ! No Cross Land advection 
    200176            ij0 =  87   ;   ij1 =  96                          ! Reduced temperature in Red Sea 
    201177            ii0 = 148   ;   ii1 = 160 
     
    203179            sf_tsd(jp_tem)%fnow( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 11:13 ) = 6.5_wp 
    204180            sf_tsd(jp_tem)%fnow( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 14:20 ) = 6.0_wp 
    205          ENDIF 
    206181      ENDIF 
    207182      ! 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DYN/divcur.F90

    r4990 r5282  
    1717   !!            3.3  ! 2010-09  (D.Storkey and E.O'Dea) bug fixes for BDY module 
    1818   !!             -   ! 2010-10  (R. Furner, G. Madec) runoff and cla added directly here 
     19   !!            3.6  ! 2014-15  cla removed 
    1920   !!---------------------------------------------------------------------- 
    2021 
     
    2829   USE sbcrnf          ! river runoff  
    2930   USE sbcisf          ! ice shelf  
    30    USE cla             ! cross land advection             (cla_div routine) 
    3131   USE in_out_manager  ! I/O manager 
    3232   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
     
    6868      !!         hdivn = 1/(e1t*e2t*e3t) ( di[e2u*e3u un] + dj[e1v*e3v vn] ) 
    6969      !!      correct hdiv with runoff inflow (div_rnf), ice shelf melting (div_isf) 
    70       !!      and cross land flow (div_cla)  
     70      !!      [REMOVED cross land flow (div_cla)] 
    7171      !!              II. vorticity : 
    7272      !!         - save the curl computed at the previous time-step 
     
    229229      IF( ln_rnf      )   CALL sbc_rnf_div( hdivn )          ! runoffs   (update hdivn field) 
    230230      IF( ln_divisf .AND. (nn_isf /= 0) )   CALL sbc_isf_div( hdivn )          ! ice shelf (update hdivn field) 
    231       IF( nn_cla == 1 )   CALL cla_div    ( kt )             ! Cross Land Advection (Update Hor. divergence) 
    232        
     231 
    233232      ! 4. Lateral boundary conditions on hdivn and rotn 
    234233      ! ---------------------------------=======---====== 
     
    259258      !!      - compute the now divergence given by : 
    260259      !!         hdivn = 1/(e1t*e2t*e3t) ( di[e2u*e3u un] + dj[e1v*e3v vn] ) 
    261       !!      correct hdiv with runoff inflow (div_rnf) and cross land flow (div_cla)  
     260      !!      correct hdiv with runoff inflow (div_rnf)  
     261      !!      [REMOVED cross land flow (div_cla)] 
    262262      !!              - Relavtive Vorticity : 
    263263      !!      - save the curl computed at the previous time-step (rotb = rotn) 
     
    328328      IF( ln_rnf      )   CALL sbc_rnf_div( hdivn )                            ! runoffs (update hdivn field) 
    329329      IF( ln_divisf .AND. (nn_isf .GT. 0) )   CALL sbc_isf_div( hdivn )          ! ice shelf (update hdivn field) 
    330       IF( nn_cla == 1 )   CALL cla_div    ( kt )             ! Cross Land Advection (update hdivn field) 
    331330      ! 
    332331      CALL lbc_lnk( hdivn, 'T', 1. )   ;   CALL lbc_lnk( rotn , 'F', 1. )     ! lateral boundary cond. (no sign change) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DYN/dynhpg.F90

    r4990 r5282  
    753753               &                   * (  rhd(ji,jj,1)                                    & 
    754754               &                     + 0.5_wp * ( rhd(ji,jj,2) - rhd(ji,jj,1) )         & 
    755                &                              * ( fse3w (ji,jj,1) - fsde3w(ji,jj,1) )   & 
     755               &                              * ( fse3w(ji,jj,1) - fsde3w(ji,jj,1) )   & 
    756756               &                              / ( fsde3w(ji,jj,2) - fsde3w(ji,jj,1) )  ) 
    757757         END DO 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DYN/dynldf_bilap.F90

    r4990 r5282  
    140140          
    141141         ! Multiply by the eddy viscosity coef. (at u- and v-points) 
    142          zlu(:,:,jk) = zlu(:,:,jk) * ( fsahmu(:,:,jk) * (1-nkahm_smag) + nkahm_smag) 
    143  
    144          zlv(:,:,jk) = zlv(:,:,jk) * ( fsahmv(:,:,jk) * (1-nkahm_smag) + nkahm_smag) 
    145           
     142          zlu(:,:,jk) = zlu(:,:,jk) * ( fsahmu(:,:,jk) ) 
     143 
     144          zlv(:,:,jk) = zlv(:,:,jk) * ( fsahmv(:,:,jk) ) 
    146145         ! Contravariant "laplacian" 
    147146         zcu(:,:) = e1u(:,:) * zlu(:,:,jk) 
     
    197196                  &  + ( zut(ji,jj+1,jk) - zut(ji  ,jj,jk) ) / e2v(ji,jj) 
    198197               ! add it to the general momentum trends 
    199                ua(ji,jj,jk) = ua(ji,jj,jk) + zua * ( fsahmu(ji,jj,jk)*nkahm_smag +(1 -nkahm_smag )) 
    200                va(ji,jj,jk) = va(ji,jj,jk) + zva * ( fsahmv(ji,jj,jk)*nkahm_smag +(1 -nkahm_smag )) 
     198               ua(ji,jj,jk) = ua(ji,jj,jk) + zua 
     199               va(ji,jj,jk) = va(ji,jj,jk) + zva 
    201200            END DO 
    202201         END DO 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DYN/dynldf_bilapg.F90

    r4990 r5282  
    434434         ! II.3 Divergence of vertical fluxes added to the horizontal divergence 
    435435         ! --------------------------------------------------------------------- 
    436          IF( (kahm -nkahm_smag) ==1 ) THEN 
     436         IF( kahm ==1 ) THEN 
    437437            ! multiply the laplacian by the eddy viscosity coefficient 
    438438            DO jk = 1, jpkm1 
     
    449449               END DO 
    450450            END DO 
    451          ELSEIF( (kahm +nkahm_smag ) == 2 ) THEN 
     451         ELSEIF( kahm == 2 ) THEN 
    452452            ! second call, no multiplication 
    453453            DO jk = 1, jpkm1 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r4990 r5282  
    272272#endif 
    273273 
    274       !                        ! Control of timestep choice 
    275       IF( lk_dynspg_ts .OR. lk_dynspg_exp ) THEN 
    276          IF( nn_cla == 1 )   CALL ctl_stop( 'Crossland advection not implemented for this free surface formulation' ) 
    277       ENDIF 
    278  
    279274      !               ! Control of hydrostatic pressure choice 
    280275      IF( lk_dynspg_ts .AND. ln_dynhpg_imp ) THEN 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_flt.F90

    r4990 r5282  
    3636   USE bdydyn          ! ocean open boundary condition on dynamics 
    3737   USE bdyvol          ! ocean open boundary condition (bdy_vol routine) 
    38    USE cla             ! cross land advection 
    3938   USE trd_oce         ! trends: ocean variables 
    4039   USE trddyn          ! trend manager: dynamics 
     
    206205      CALL Agrif_dyn( kt )    ! Update velocities on each coarse/fine interfaces  
    207206#endif 
    208       IF( nn_cla == 1 .AND. cp_cfg == 'orca' .AND. jp_cfg == 2 )   CALL cla_dynspg( kt )      ! Cross Land Advection (update (ua,va)) 
    209207 
    210208      ! compute the next vertically averaged velocity (effect of the additional force not included) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/DYN/dynzdf.F90

    r4990 r5282  
    3535 
    3636   INTEGER  ::   nzdf = 0   ! type vertical diffusion algorithm used, defined from ln_zdf... namlist logicals 
    37    REAL(wp) ::   r2dt       ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0 
    3837 
    3938   !! * Substitutions 
     
    6463      ! 
    6564      !                                          ! set time step 
    66       IF( neuler == 0 .AND. kt == nit000     ) THEN   ;   r2dt =      rdt   ! = rdtra (restart with Euler time stepping) 
    67       ELSEIF(               kt <= nit000 + 1 ) THEN   ;   r2dt = 2. * rdt   ! = 2 rdttra (leapfrog) 
     65      IF( neuler == 0 .AND. kt == nit000     ) THEN   ;   r2dt =      rdt   ! = rdt(restart with Euler time stepping) 
     66      ELSEIF(               kt <= nit000 + 1 ) THEN   ;   r2dt = 2. * rdt   ! = 2 rdt (leapfrog) 
    6867      ENDIF 
    6968 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r4990 r5282  
    3838   INTEGER       ::   nn_write         !: model standard output frequency 
    3939   INTEGER       ::   nn_stock         !: restart file frequency 
    40    LOGICAL       ::   ln_dimgnnn       !: type of dimgout. (F): 1 file for all proc 
    41                                                        !:                  (T): 1 file per proc 
    4240   LOGICAL       ::   ln_mskland       !: mask land points in NetCDF outputs (costly: + ~15%) 
    4341   LOGICAL       ::   ln_clobber       !: clobber (overwrite) an existing file 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r5043 r5282  
    88   !!            3.0  ! 2007-07  (D. Storkey) Changes to iom_gettime 
    99   !!            3.4  ! 2012-12  (R. Bourdalle-Badie and G. Reffray)  add C1D case   
     10   !!            3.6  ! 2014-15  DIMG format removed 
    1011   !!-------------------------------------------------------------------- 
    1112 
     
    2324   USE lbclnk          ! lateal boundary condition / mpp exchanges 
    2425   USE iom_def         ! iom variables definitions 
    25    USE iom_ioipsl      ! NetCDF format with IOIPSL library 
    2626   USE iom_nf90        ! NetCDF format with native NetCDF library 
    27    USE iom_rstdimg     ! restarts access direct format "dimg" style... 
    2827   USE in_out_manager  ! I/O manager 
    2928   USE lib_mpp           ! MPP library 
     
    205204      CHARACTER(LEN=256)    ::   clname    ! the name of the file based on cdname [[+clcpu]+clcpu] 
    206205      CHARACTER(LEN=256)    ::   cltmpn    ! tempory name to store clname (in writting mode) 
    207       CHARACTER(LEN=10)     ::   clsuffix  ! ".nc" or ".dimg" 
     206      CHARACTER(LEN=10)     ::   clsuffix  ! ".nc"  
    208207      CHARACTER(LEN=15)     ::   clcpu     ! the cpu number (max jpmax_digits digits) 
    209208      CHARACTER(LEN=256)    ::   clinfo    ! info character 
     
    268267      ! which suffix should we use? 
    269268      SELECT CASE (iolib) 
    270       CASE (jpioipsl ) ;   clsuffix = '.nc' 
    271269      CASE (jpnf90   ) ;   clsuffix = '.nc' 
    272       CASE (jprstdimg) ;   clsuffix = '.dimg' 
    273270      CASE DEFAULT     ;   clsuffix = '' 
    274          CALL ctl_stop( TRIM(clinfo), 'accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     271         CALL ctl_stop( TRIM(clinfo), 'accepted IO library is only jpnf90 (jpioipsl option has been removed) ' ) 
    275272      END SELECT 
    276273      ! Add the suffix if needed 
     
    285282      IF( .NOT.llok ) THEN 
    286283         ! we try to add the cpu number to the name 
    287          IF( iolib == jprstdimg ) THEN   ;   WRITE(clcpu,*) narea 
    288          ELSE                            ;   WRITE(clcpu,*) narea-1 
    289          ENDIF 
     284         WRITE(clcpu,*) narea-1 
     285 
    290286         clcpu  = TRIM(ADJUSTL(clcpu)) 
    291287         iln = INDEX(clname,TRIM(clsuffix), back = .TRUE.) 
     
    334330         END SELECT 
    335331      ENDIF 
    336       ! Open the NetCDF or RSTDIMG file 
     332      ! Open the NetCDF file 
    337333      ! ============= 
    338334      ! do we have some free file identifier? 
     
    358354      IF( istop == nstop ) THEN   ! no error within this routine 
    359355         SELECT CASE (iolib) 
    360          CASE (jpioipsl )   ;   CALL iom_ioipsl_open(  clname, kiomid, llwrt, llok, idompar ) 
    361356         CASE (jpnf90   )   ;   CALL iom_nf90_open(    clname, kiomid, llwrt, llok, idompar ) 
    362          CASE (jprstdimg)   ;   CALL iom_rstdimg_open( clname, kiomid, llwrt, llok, idompar ) 
    363357         CASE DEFAULT 
    364             CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     358            CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed) ' ) 
    365359         END SELECT 
    366360      ENDIF 
     
    397391            IF( iom_file(jf)%nfid > 0 ) THEN 
    398392               SELECT CASE (iom_file(jf)%iolib) 
    399                CASE (jpioipsl )   ;   CALL iom_ioipsl_close(  jf ) 
    400393               CASE (jpnf90   )   ;   CALL iom_nf90_close(    jf ) 
    401                CASE (jprstdimg)   ;   CALL iom_rstdimg_close( jf ) 
    402394               CASE DEFAULT 
    403                   CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     395                  CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    404396               END SELECT 
    405397               iom_file(jf)%nfid       = 0          ! free the id  
     
    456448               IF( iiv <= jpmax_vars ) THEN 
    457449                  SELECT CASE (iom_file(kiomid)%iolib) 
    458                   CASE (jpioipsl )   ;   iom_varid = iom_ioipsl_varid( kiomid, cdvar, iiv, kdimsz ) 
    459450                  CASE (jpnf90   )   ;   iom_varid = iom_nf90_varid  ( kiomid, cdvar, iiv, kdimsz, kndims ) 
    460                   CASE (jprstdimg)   ;   iom_varid = -1   ! all variables are listed in iom_file 
    461                   CASE DEFAULT    
    462                      CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     451                  CASE DEFAULT 
     452                     CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    463453                  END SELECT 
    464454               ELSE 
     
    518508                                 &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
    519509            SELECT CASE (iom_file(kiomid)%iolib) 
    520             CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar, itime ) 
    521510            CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar, itime ) 
    522             CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar ) 
    523             CASE DEFAULT     
    524                CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     511            CASE DEFAULT 
     512               CALL ctl_stop( 'iom_g0d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    525513            END SELECT 
    526514         ENDIF 
     
    785773       
    786774         SELECT CASE (iom_file(kiomid)%iolib) 
    787          CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
    788             &                                         pv_r1d, pv_r2d, pv_r3d ) 
    789775         CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
    790776            &                                         pv_r1d, pv_r2d, pv_r3d ) 
    791          CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idom, idvar, ix1, ix2, iy1, iy2,   & 
    792             &                                         pv_r1d, pv_r2d, pv_r3d ) 
    793          CASE DEFAULT     
    794             CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     777         CASE DEFAULT 
     778            CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    795779         END SELECT 
    796780 
     
    879863                  IF( iom_file(kiomid)%dimsz(1,idvar) <= size(ptime) ) THEN 
    880864                     SELECT CASE (iom_file(kiomid)%iolib) 
    881                      CASE (jpioipsl )   ;   CALL iom_ioipsl_gettime( kiomid, idvar, ptime, cdunits, cdcalendar ) 
    882865                     CASE (jpnf90   )   ;   CALL iom_nf90_gettime(   kiomid, idvar, ptime, cdunits, cdcalendar ) 
    883                      CASE (jprstdimg)   ;   CALL ctl_stop( TRIM(clinfo)//' case IO library == jprstdimg not coded...' ) 
    884                      CASE DEFAULT     
    885                         CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     866                     CASE DEFAULT 
     867                        CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    886868                     END SELECT 
    887869                  ELSE 
     
    914896         IF( iom_file(kiomid)%nfid > 0 ) THEN 
    915897            SELECT CASE (iom_file(kiomid)%iolib) 
    916             CASE (jpioipsl )   ;   CALL ctl_stop('iom_getatt: only nf90 available') 
    917898            CASE (jpnf90   )   ;   CALL iom_nf90_getatt( kiomid, cdatt, pvar ) 
    918             CASE (jprstdimg)   ;   CALL ctl_stop('iom_getatt: only nf90 available') 
    919             CASE DEFAULT     
    920                CALL ctl_stop( 'iom_g0d_att: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     899            CASE DEFAULT 
     900               CALL ctl_stop( 'iom_g0d_att: accepted IO library is only jpnf90' ) 
    921901            END SELECT 
    922902         ENDIF 
     
    940920            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    941921            SELECT CASE (iom_file(kiomid)%iolib) 
    942             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
    943922            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
    944             CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pvar ) 
    945             CASE DEFAULT      
    946                CALL ctl_stop( 'iom_rp0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     923            CASE DEFAULT 
     924               CALL ctl_stop( 'iom_rp0d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    947925            END SELECT 
    948926         ENDIF 
     
    962940            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    963941            SELECT CASE (iom_file(kiomid)%iolib) 
    964             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
    965942            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
    966             CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r1d = pvar ) 
    967             CASE DEFAULT      
    968                CALL ctl_stop( 'iom_rp1d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     943            CASE DEFAULT 
     944               CALL ctl_stop( 'iom_rp1d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    969945            END SELECT 
    970946         ENDIF 
     
    984960            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    985961            SELECT CASE (iom_file(kiomid)%iolib) 
    986             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
    987962            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
    988             CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r2d = pvar )  
    989             CASE DEFAULT      
    990                CALL ctl_stop( 'iom_rp2d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     963            CASE DEFAULT 
     964               CALL ctl_stop( 'iom_rp2d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    991965            END SELECT 
    992966         ENDIF 
     
    1006980            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) 
    1007981            SELECT CASE (iom_file(kiomid)%iolib) 
    1008             CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
    1009982            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
    1010             CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r3d = pvar ) 
    1011             CASE DEFAULT      
    1012                CALL ctl_stop( 'iom_rp3d: accepted IO library are only jpioipsl and jprstdimg' ) 
     983            CASE DEFAULT 
     984               CALL ctl_stop( 'iom_rp3d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 
    1013985            END SELECT 
    1014986         ENDIF 
     
    14171389            idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@') 
    14181390            DO WHILE ( idx /= 0 )  
    1419                cldate = iom_sdate( fjulday - rdttra(1) / rday ) 
     1391               cldate = iom_sdate( fjulday - rdt / rday ) 
    14201392               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+11:LEN_TRIM(clname)) 
    14211393               idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@') 
     
    14241396            idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@') 
    14251397            DO WHILE ( idx /= 0 )  
    1426                cldate = iom_sdate( fjulday - rdttra(1) / rday, ldfull = .TRUE. ) 
     1398               cldate = iom_sdate( fjulday - rdt / rday, ldfull = .TRUE. ) 
    14271399               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+15:LEN_TRIM(clname)) 
    14281400               idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@') 
     
    14311403            idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@') 
    14321404            DO WHILE ( idx /= 0 )  
    1433                cldate = iom_sdate( fjulday + rdttra(1) / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE. ) 
     1405               cldate = iom_sdate( fjulday + rdt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE. ) 
    14341406               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+9:LEN_TRIM(clname)) 
    14351407               idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@') 
     
    14381410            idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@') 
    14391411            DO WHILE ( idx /= 0 )  
    1440                cldate = iom_sdate( fjulday + rdttra(1) / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE., ldfull = .TRUE. ) 
     1412               cldate = iom_sdate( fjulday + rdt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE., ldfull = .TRUE. ) 
    14411413               clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+13:LEN_TRIM(clname)) 
    14421414               idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@') 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/IOM/iom_def.F90

    r4205 r5282  
    2828   INTEGER, PARAMETER, PUBLIC ::   jpdom_autodta       = 9   !:  
    2929 
    30    INTEGER, PARAMETER, PUBLIC ::   jpioipsl    = 100      !: Use ioipsl (fliocom only) library 
    3130   INTEGER, PARAMETER, PUBLIC ::   jpnf90      = 101      !: Use nf90 library 
    32    INTEGER, PARAMETER, PUBLIC ::   jprstdimg   = 102      !: Use restart dimgs (fortran direct acces) library 
    33 #if defined key_dimgout 
    34    INTEGER, PARAMETER, PUBLIC ::   jprstlib  = jprstdimg  !: restarts io library 
    35 #else 
     31 
    3632   INTEGER, PARAMETER, PUBLIC ::   jprstlib  = jpnf90     !: restarts io library 
    37 #endif 
    3833 
    3934   INTEGER, PARAMETER, PUBLIC ::   jp_r8    = 200      !: write REAL(8) 
     
    5449      CHARACTER(LEN=240)                        ::   name     !: name of the file 
    5550      INTEGER                                   ::   nfid     !: identifier of the file (0 if closed) 
    56       INTEGER                                   ::   iolib    !: library used to read the file (jpioipsl, jpnf90 or jprstdimg) 
     51      INTEGER                                   ::   iolib    !: library used to read the file (jpnf90 or new formats, 
     52                                                              !: jpioipsl option has been removed) 
    5753      INTEGER                                   ::   nvars    !: number of identified varibles in the file 
    5854      INTEGER                                   ::   iduld    !: id of the unlimited dimension 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r4990 r5282  
    8282            WRITE(numout,*) 
    8383            SELECT CASE ( jprstlib ) 
    84             CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart binary file: '//clname 
    8584            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname 
    8685            END SELECT 
     
    110109      !!---------------------------------------------------------------------- 
    111110 
    112                      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step 
    113                      CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step 
     111                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics and tracer time step 
    114112 
    115113                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields 
     
    165163            SELECT CASE ( jprstlib ) 
    166164            CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file' 
    167             CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    168165            END SELECT 
    169166            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support' 
     
    171168         ENDIF 
    172169 
    173          IF ( jprstlib == jprstdimg ) THEN 
    174            ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    175            ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90 
    176            INQUIRE( FILE = TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
    177            IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    178          ENDIF 
    179170         CALL iom_open( cn_ocerst_in, numror, kiolib = jlibalt ) 
    180171      ENDIF 
     
    189180      !! ** Method  :   Read in restart.nc file fields which are necessary for restart 
    190181      !!---------------------------------------------------------------------- 
    191       REAL(wp) ::   zrdt, zrdttra1 
     182      REAL(wp) ::   zrdt 
    192183      INTEGER  ::   jk 
    193184      LOGICAL  ::   llok 
     
    201192         IF( zrdt /= rdt )   neuler = 0 
    202193      ENDIF 
    203       IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN 
    204          CALL iom_get( numror, 'rdttra1', zrdttra1 ) 
    205          IF( zrdttra1 /= rdttra(1) )   neuler = 0 
    206       ENDIF 
    207       !  
     194      ! 
    208195      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN 
    209196         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r4990 r5282  
    297297 
    298298      IF( mynode == 0 ) THEN 
    299         CALL ctl_opn( kumond, 'output.namelist.dyn', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. , 1 ) 
     299        CALL ctl_opn( kumond, 'output.namelist.dyn', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -2, 6, .TRUE. , 1 ) 
    300300        WRITE(kumond, nammpp)       
    301301      ENDIF 
     
    31983198      IF( PRESENT( localComm ) .OR. .NOT.PRESENT( localComm ) )   function_value = 0 
    31993199      IF( .FALSE. )   ldtxt(:) = 'never done' 
    3200       CALL ctl_opn( kumond, 'output.namelist.dyn', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. , 1 ) 
     3200      CALL ctl_opn( kumond, 'output.namelist.dyn', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, 6, .TRUE. , 1 ) 
    32013201   END FUNCTION mynode 
    32023202 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90

    r4679 r5282  
    457457#  include "mppini_2.h90" 
    458458 
    459 # if defined key_dimgout 
    460    !!---------------------------------------------------------------------- 
    461    !!   'key_dimgout'                  NO use of NetCDF files 
    462    !!---------------------------------------------------------------------- 
    463    SUBROUTINE mpp_init_ioipsl       ! Dummy routine 
    464    END SUBROUTINE mpp_init_ioipsl   
    465 # else 
    466459   SUBROUTINE mpp_init_ioipsl 
    467460      !!---------------------------------------------------------------------- 
     
    509502   END SUBROUTINE mpp_init_ioipsl   
    510503 
    511 # endif 
    512504#endif 
    513505 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/LDF/ldfdyn.F90

    r4624 r5282  
    6969         &                 ln_dynldf_level, ln_dynldf_hor  , ln_dynldf_iso,   & 
    7070         &                 rn_ahm_0_lap   , rn_ahmb_0      , rn_ahm_0_blp ,   & 
    71          &                 rn_cmsmag_1    , rn_cmsmag_2    , rn_cmsh,         & 
    7271         &                 rn_ahm_m_lap   , rn_ahm_m_blp 
    7372 
     
    155154      IF(lwp) WRITE(numout,*) '        ahm1 = ahm2 = ahm0 =  ',ahm0 
    156155#endif 
    157      nkahm_smag = 0 
    158 #if defined key_dynldf_smag 
    159      nkahm_smag = 1 
    160 #endif 
    161156 
    162157      ! 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/LDF/ldfdyn_oce.F90

    r4147 r5282  
    2323   REAL(wp), PUBLIC ::   rn_ahm_0_blp       !: lateral bilaplacian eddy viscosity (m4/s) 
    2424   REAL(wp), PUBLIC ::   ahm0, ahmb0, ahm0_blp         !: OLD namelist names 
    25    REAL(wp), PUBLIC ::   rn_cmsmag_1        !: constant in laplacian Smagorinsky viscosity 
    26    REAL(wp), PUBLIC ::   rn_cmsmag_2        !: constant in bilaplacian Smagorinsky viscosity 
    27    REAL(wp), PUBLIC ::   rn_cmsh            !: 1 or 0 , if 0 -use only shear for Smagorinsky viscosity 
    2825   REAL(wp), PUBLIC ::   rn_ahm_m_blp       !: upper limit for bilap  abs(ahm) < min( dx^4/128rdt, rn_ahm_m_blp) 
    2926   REAL(wp), PUBLIC ::   rn_ahm_m_lap       !: upper limit for lap  ahm < min(dx^2/16rdt, rn_ahm_m_lap) 
    3027 
    31    INTEGER , PUBLIC ::   nkahm_smag      =  0          !:  
    3228 
    3329   !                                                                                  !!! eddy coeff. at U-,V-,W-pts [m2/s] 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/LDF/ldftra.F90

    r4624 r5282  
    7070         &                 ln_triad_iso   , ln_botmix_grif ,                  & 
    7171         &                 rn_aht_0       , rn_ahtb_0      , rn_aeiv_0,       & 
    72          &                 rn_slpmax      , rn_chsmag      ,    rn_smsh,      & 
    73          &                 rn_aht_m 
     72         &                 rn_slpmax      , rn_aht_m 
    7473      !!---------------------------------------------------------------------- 
    7574 
     
    167166#endif 
    168167 
    169 #if defined key_traldf_smag && ! defined key_traldf_c3d 
    170         CALL ctl_stop( 'key_traldf_smag can only be used with key_traldf_c3d' ) 
    171 #endif 
    172 #if defined key_traldf_smag 
    173         IF(lwp) WRITE(numout,*)' SMAGORINSKY DIFFUSION' 
    174         IF(lwp .AND. rn_smsh < 1)  WRITE(numout,*)' only  shear is used ' 
    175         IF(lwp.and.ln_traldf_bilap) CALL ctl_stop(' SMAGORINSKY + BILAPLACIAN - UNSTABLE OR NON_CONSERVATIVE' ) 
    176 #endif 
    177  
    178168      ! 
    179169   END SUBROUTINE ldf_tra_init 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/LDF/ldftra_oce.F90

    r4147 r5282  
    3030   REAL(wp), PUBLIC ::   rn_aeiv_0        !: eddy induced velocity coefficient (m2/s) 
    3131   REAL(wp), PUBLIC ::   rn_slpmax        !: slope limit 
    32    REAL(wp), PUBLIC ::   rn_chsmag        !:  multiplicative factor in Smagorinsky diffusivity 
    33    REAL(wp), PUBLIC ::   rn_smsh          !:  Smagorinsky diffusivity: = 0 - use only sheer 
    3432   REAL(wp), PUBLIC ::   rn_aht_m         !:  upper limit or stability criteria for lateral eddy diffusivity (m2/s) 
    3533 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90

    r4784 r5282  
    162162         isecsbc = nsec_year + nsec1jan000 + (kit+it_offset)*NINT( rdt/REAL(nn_baro,wp) ) 
    163163      ELSE                      ! middle of sbc time step 
    164          isecsbc = nsec_year + nsec1jan000 + NINT(0.5 * REAL(kn_fsbc - 1,wp) * rdttra(1)) + it_offset * NINT(rdttra(1)) 
     164        isecsbc = nsec_year + nsec1jan000 + NINT(0.5 * REAL(kn_fsbc - 1,wp) * rdt) + it_offset * NINT(rdt) 
    165165      ENDIF 
    166166      imf = SIZE( sd ) 
     
    189189               CALL fld_rec( kn_fsbc, sd(jf), kt_offset = it_offset, kit = kit )    ! update after record informations 
    190190 
    191                ! if kn_fsbc*rdttra is larger than nfreqh (which is kind of odd), 
     191               ! if kn_fsbc*rdt is larger than nfreqh (which is kind of odd), 
    192192               ! it is possible that the before value is no more the good one... we have to re-read it 
    193193               ! if before is not the last record of the file currently opened and after is the first record to be read 
     
    210210               IF( sd(jf)%ln_tint ) THEN 
    211211                   
    212                   ! if kn_fsbc*rdttra is larger than nfreqh (which is kind of odd), 
     212                  ! if kn_fsbc*rdt is larger than nfreqh (which is kind of odd), 
    213213                  ! it is possible that the before value is no more the good one... we have to re-read it 
    214214                  ! if before record is not just just before the after record... 
     
    241241                        ! year/month/week/day file to be not present. If the run continue further than the current 
    242242                        ! year/month/week/day, next year/month/week/day file must exist 
    243                         isecend = nsec_year + nsec1jan000 + (nitend - kt) * NINT(rdttra(1))   ! second at the end of the run  
     243                        isecend = nsec_year + nsec1jan000 + (nitend - kt) * NINT(rdt)   ! second at the end of the run 
    244244                        llstop = isecend > sd(jf)%nrec_a(2)                                   ! read more than 1 record of next year 
    245245                        ! we suppose that the date of next file is next day (should be ok even for weekly files...) 
     
    454454      IF( PRESENT(kt_offset) )   it_offset = kt_offset 
    455455      IF( PRESENT(kit) ) THEN   ;   it_offset = ( kit + it_offset ) * NINT( rdt/REAL(nn_baro,wp) ) 
    456       ELSE                      ;   it_offset =         it_offset   * NINT(       rdttra(1)      ) 
     456      ELSE                      ;   it_offset =         it_offset   * NINT(       rdt      ) 
    457457      ENDIF 
    458458      ! 
     
    531531         ELSE                                           ;   ztmp = REAL(nsec_year ,wp)  ! since 00h on Jan 1 of the current year 
    532532         ENDIF 
    533          ztmp = ztmp + 0.5 * REAL(kn_fsbc - 1, wp) * rdttra(1) + REAL( it_offset, wp )  ! centrered in the middle of sbc time step 
    534          ztmp = ztmp + 0.01 * rdttra(1)                                                 ! avoid truncation error  
     533         ztmp = ztmp + 0.5 * REAL(kn_fsbc - 1, wp) * rdt + REAL( it_offset, wp )  ! centrered in the middle of sbc time step 
     534         ztmp = ztmp + 0.01 * rdt                                                 ! avoid truncation error 
    535535         IF( sdjf%ln_tint ) THEN                ! time interpolation, shift by 1/2 record 
    536536            ! 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r5009 r5282  
    645645      LOGICAL ::    llnewtx, llnewtau      ! update wind stress components and module?? 
    646646      INTEGER  ::   ji, jj, jn             ! dummy loop indices 
    647       INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdttra did not change since nit000) 
     647      INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdt did not change since nit000) 
    648648      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars      
    649649      REAL(wp) ::   zcoef                  ! temporary scalar 
     
    658658      CALL wrk_alloc( jpi,jpj, ztx, zty ) 
    659659      !                                                 ! Receive all the atmos. fields (including ice information) 
    660       isec = ( kt - nit000 ) * NINT( rdttra(1) )             ! date of exchanges 
     660      isec = ( kt - nit000 ) * NINT( rdt )             ! date of exchanges 
    661661      DO jn = 1, jprcv                                       ! received fields sent by the atmosphere 
    662662         IF( srcv(jn)%laction )   CALL cpl_rcv( jn, isec, frcv(jn)%z3, xcplmask, nrcvinfo(jn) ) 
     
    13381338      CALL wrk_alloc( jpi,jpj,jpl, ztmp3, ztmp4 ) 
    13391339 
    1340       isec = ( kt - nit000 ) * NINT(rdttra(1))        ! date of exchanges 
     1340      isec = ( kt - nit000 ) * NINT(rdt)        ! date of exchanges 
    13411341 
    13421342      zfr_l(:,:) = 1.- fr_i(:,:) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/SBC/sbcdcy.F90

    r3764 r5282  
    9090 
    9191      ! When are we during the day (from 0 to 1) 
    92       zlo = ( REAL(nsec_day, wp) - 0.5_wp * rdttra(1) ) / rday 
    93       zup = zlo + ( REAL(nn_fsbc, wp)     * rdttra(1) ) / rday 
     92      zlo = ( REAL(nsec_day, wp) - 0.5_wp * rdt ) / rday 
     93      zup = zlo + ( REAL(nn_fsbc, wp)     * rdt ) / rday 
    9494      !                                           
    9595      IF( nday_qsr == -1 ) THEN       ! first time step only   
     
    189189         END DO   
    190190         ! 
    191          ztmp = rday / ( rdttra(1) * REAL(nn_fsbc, wp) ) 
     191         ztmp = rday / ( rdt * REAL(nn_fsbc, wp) ) 
    192192         rscal(:,:) = rscal(:,:) * ztmp 
    193193         ! 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/SBC/sbcfwb.F90

    r4990 r5282  
    125125         ENDIF    
    126126         !                                         ! Update fwfold if new year start 
    127          ikty = 365 * 86400 / rdttra(1)    !!bug  use of 365 days leap year or 360d year !!!!!!! 
     127         ikty = 365 * 86400 / rdt       !!bug  use of 365 days leap year or 360d year !!!!!!! 
    128128         IF( MOD( kt, ikty ) == 0 ) THEN 
    129129            a_fwb_b = a_fwb                           ! mean sea level taking into account the ice+snow 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r4990 r5282  
    255255            CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3u_b(:,:,:), 'U' ) 
    256256            CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3v_b(:,:,:), 'V' ) 
    257             CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3u_n(:,:,:), 'U' ) 
     257            CALL dom_vvl_interpol( fse333333333333333333333333333333333t_n(:,:,:), fse3u_n(:,:,:), 'U' ) 
    258258            CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3v_n(:,:,:), 'V' ) 
    259259            CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3f_n(:,:,:), 'F' ) 
    260260            ! Vertical scale factor interpolations 
    261261            ! ------------------------------------ 
    262             CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n (:,:,:), 'W'  ) 
     262            CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n(:,:,:), 'W'  ) 
    263263            CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3uw_n(:,:,:), 'UW' ) 
    264264            CALL dom_vvl_interpol( fse3v_n(:,:,:), fse3vw_n(:,:,:), 'VW' ) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r4990 r5282  
    461461      CALL iom_close( inum )                                      ! close file 
    462462      ! 
    463       IF( nn_closea == 1 )   CALL clo_rnf( rnfmsk )               ! closed sea inflow set as ruver mouth 
     463      IF( nn_closea == 1 )   CALL clo_rnf( rnfmsk )               ! closed sea inflow set as river mouth 
    464464      ! 
    465465      rnfmsk_z(:)   = 0._wp                                       ! vertical structure 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/SBC/sbctide.F90

    r4292 r5282  
    4949      !!---------------------------------------------------------------------- 
    5050 
    51       IF( nsec_day == NINT(0.5_wp * rdttra(1)) ) THEN      ! start a new day 
     51      IF( nsec_day == NINT(0.5_wp * rdt) ) THEN      ! start a new day 
    5252         ! 
    5353         IF( kt == nit000 ) THEN 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/traadv.F90

    r4990 r5282  
    2424   USE traadv_eiv      ! eddy induced velocity     (tra_adv_eiv    routine) 
    2525   USE traadv_mle      ! ML eddy induced velocity  (tra_adv_mle    routine) 
    26    USE cla             ! cross land advection      (cla_traadv     routine) 
    2726   USE ldftra_oce      ! lateral diffusion coefficient on tracers 
    2827   USE in_out_manager  ! I/O manager 
     
    8483      !                                          ! set time step 
    8584      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000 
    86          r2dtra(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping) 
     85         r2dt =  rdt                          ! = rdt (restarting with Euler time stepping) 
    8786      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1 
    88          r2dtra(:) = 2._wp * rdttra(:)                   ! = 2 rdttra (leapfrog) 
    89       ENDIF 
    90       ! 
    91       IF( nn_cla == 1 .AND. cp_cfg == 'orca' .AND. jp_cfg == 2 )   CALL cla_traadv( kt )       !==  Cross Land Advection  ==! (hor. advection) 
     87         r2dt = 2._wp * rdt                   ! = 2 rdt (leapfrog) 
     88      ENDIF 
    9289      ! 
    9390      !                                               !==  effective transport  ==! 
     
    117114      SELECT CASE ( nadv )                            !==  compute advection trend and add it to general trend  ==! 
    118115      CASE ( 1 )   ;    CALL tra_adv_cen2  ( kt, nit000, 'TRA',         zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  2nd order centered 
    119       CASE ( 2 )   ;    CALL tra_adv_tvd   ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  TVD  
    120       CASE ( 3 )   ;    CALL tra_adv_muscl ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb,      tsa, jpts, ln_traadv_msc_ups )   !  MUSCL  
    121       CASE ( 4 )   ;    CALL tra_adv_muscl2( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  MUSCL2  
    122       CASE ( 5 )   ;    CALL tra_adv_ubs   ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  UBS  
    123       CASE ( 6 )   ;    CALL tra_adv_qck   ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  QUICKEST  
    124       CASE ( 7 )   ;   CALL tra_adv_tvd_zts( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  TVD ZTS 
     116      CASE ( 2 )   ;    CALL tra_adv_tvd   ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  TVD 
     117      CASE ( 3 )   ;    CALL tra_adv_muscl ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb,      tsa, jpts, ln_traadv_msc_ups )   !  MUSCL 
     118      CASE ( 4 )   ;    CALL tra_adv_muscl2( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  MUSCL2 
     119      CASE ( 5 )   ;    CALL tra_adv_ubs   ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  UBS 
     120      CASE ( 6 )   ;    CALL tra_adv_qck   ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  QUICKEST 
     121      CASE ( 7 )   ;   CALL tra_adv_tvd_zts( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts )   !  TVD ZTS 
    125122      ! 
    126123      CASE (-1 )                                      !==  esopa: test all possibility with control print  ==! 
     
    128125         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' adv0 - Ta: ', mask1=tmask,               & 
    129126            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    130          CALL tra_adv_tvd   ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )           
     127         CALL tra_adv_tvd   ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts ) 
    131128         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' adv1 - Ta: ', mask1=tmask,               & 
    132129            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    133          CALL tra_adv_muscl ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb,      tsa, jpts, ln_traadv_msc_ups )           
     130         CALL tra_adv_muscl ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb,      tsa, jpts, ln_traadv_msc_ups ) 
    134131         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' adv3 - Ta: ', mask1=tmask,               & 
    135132            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    136          CALL tra_adv_muscl2( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )           
     133         CALL tra_adv_muscl2( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts ) 
    137134         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' adv4 - Ta: ', mask1=tmask,               & 
    138135            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    139          CALL tra_adv_ubs   ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )           
     136         CALL tra_adv_ubs   ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts ) 
    140137         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' adv5 - Ta: ', mask1=tmask,               & 
    141138            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    142          CALL tra_adv_qck   ( kt, nit000, 'TRA', r2dtra, zun, zvn, zwn, tsb, tsn, tsa, jpts )           
     139         CALL tra_adv_qck   ( kt, nit000, 'TRA', r2dt, zun, zvn, zwn, tsb, tsn, tsa, jpts ) 
    143140         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' adv6 - Ta: ', mask1=tmask,               & 
    144141            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_muscl.F90

    r4990 r5282  
    7272      INTEGER                              , INTENT(in   ) ::   kjpt            ! number of tracers 
    7373      LOGICAL                              , INTENT(in   ) ::   ld_msc_ups      ! use upstream scheme within muscl 
    74       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt            ! vertical profile of tracer time-step 
     74      REAL(wp)                             , INTENT(in   ) ::   p2dt            ! tracer time-step 
    7575      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pun, pvn, pwn   ! 3 ocean velocity components 
    7676      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb             ! before tracer field 
     
    176176         !                                             !-- MUSCL horizontal advective fluxes 
    177177         DO jk = 1, jpkm1                                     ! interior values 
    178             zdt  = p2dt(jk) 
     178            zdt  = p2dt 
    179179            DO jj = 2, jpjm1 
    180180               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    259259         ! 
    260260         DO jk = 1, jpkm1                                     ! interior values 
    261             zdt  = p2dt(jk) 
     261            zdt  = p2dt 
    262262            DO jj = 2, jpjm1       
    263263               DO ji = fs_2, fs_jpim1   ! vector opt. 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_muscl2.F90

    r4990 r5282  
    6363      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype          ! =TRA or TRC (tracer indicator) 
    6464      INTEGER                              , INTENT(in   ) ::   kjpt            ! number of tracers 
    65       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt            ! vertical profile of tracer time-step 
     65      REAL(wp)                             , INTENT(in   ) ::   p2dt            ! tracer time-step 
    6666      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pun, pvn, pwn   ! 3 ocean velocity components 
    6767      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb, ptn        ! before & now tracer fields 
     
    133133        !                                             !-- MUSCL horizontal advective fluxes 
    134134         DO jk = 1, jpkm1                                     ! interior values 
    135             zdt  = p2dt(jk) 
     135            zdt  = p2dt 
    136136            DO jj = 2, jpjm1 
    137137               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    240240         ! 
    241241         DO jk = 1, jpkm1                                     ! interior values 
    242             zdt  = p2dt(jk) 
     242            zdt  = p2dt 
    243243            DO jj = 2, jpjm1 
    244244               DO ji = fs_2, fs_jpim1   ! vector opt. 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_qck.F90

    r4990 r5282  
    8888      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype          ! =TRA or TRC (tracer indicator) 
    8989      INTEGER                              , INTENT(in   ) ::   kjpt            ! number of tracers 
    90       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt            ! vertical profile of tracer time-step 
     90      REAL(wp)                             , INTENT(in   ) ::   p2dt            ! tracer time-step 
    9191      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pun, pvn, pwn   ! 3 ocean velocity components 
    9292      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb, ptn        ! before and now tracer fields 
     
    125125      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator) 
    126126      INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers 
    127       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt       ! vertical profile of tracer time-step 
     127      REAL(wp)                             , INTENT(in   ) ::   p2dt       ! tracer time-step 
    128128      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pun        ! i-velocity components 
    129129      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb, ptn   ! before and now tracer fields 
     
    170170         ! 
    171171         DO jk = 1, jpkm1   
    172             zdt =  p2dt(jk) 
     172            zdt =  p2dt 
    173173            DO jj = 2, jpjm1 
    174174               DO ji = fs_2, fs_jpim1   ! vector opt.    
     
    246246      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator) 
    247247      INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers 
    248       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt       ! vertical profile of tracer time-step 
     248      REAL(wp)                             , INTENT(in   ) ::   p2dt       ! tracer time-step 
    249249      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pvn        ! j-velocity components 
    250250      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb, ptn   ! before and now tracer fields 
     
    293293         ! 
    294294         DO jk = 1, jpkm1   
    295             zdt =  p2dt(jk) 
     295            zdt =  p2dt 
    296296            DO jj = 2, jpjm1 
    297297               DO ji = fs_2, fs_jpim1   ! vector opt.    
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_tvd.F90

    r4990 r5282  
    7474      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype          ! =TRA or TRC (tracer indicator) 
    7575      INTEGER                              , INTENT(in   ) ::   kjpt            ! number of tracers 
    76       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt            ! vertical profile of tracer time-step 
     76      REAL(wp)                             , INTENT(in   ) ::   p2dt            ! tracer time-step 
    7777      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pun, pvn, pwn   ! 3 ocean velocity components 
    7878      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb, ptn        ! before and now tracer fields 
     
    161161         ! total advective trend 
    162162         DO jk = 1, jpkm1 
    163             z2dtt = p2dt(jk) 
     163            z2dtt = p2dt 
    164164            DO jj = 2, jpjm1 
    165165               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    287287      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype          ! =TRA or TRC (tracer indicator) 
    288288      INTEGER                              , INTENT(in   ) ::   kjpt            ! number of tracers 
    289       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt            ! vertical profile of tracer time-step 
     289      REAL(wp)                             , INTENT(in   ) ::   p2dt            ! tracer time-step 
    290290      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pun, pvn, pwn   ! 3 ocean velocity components 
    291291      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb, ptn        ! before and now tracer fields 
    292292      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta             ! tracer trend  
    293293      ! 
    294       REAL(wp), DIMENSION( jpk )                           ::   zts             ! length of sub-timestep for vertical advection 
    295       REAL(wp), DIMENSION( jpk )                           ::   zr_p2dt         ! reciprocal of tracer timestep 
     294      REAL(wp)                                             ::   zts             ! length of sub-timestep for vertical advection 
     295      REAL(wp)                                             ::   zr_p2dt         ! reciprocal of tracer timestep 
    296296      INTEGER  ::   ji, jj, jk, jl, jn       ! dummy loop indices   
    297297      INTEGER  ::   jnzts = 5       ! number of sub-timesteps for vertical advection 
     
    330330      zwi(:,:,:) = 0._wp 
    331331      z_rzts = 1._wp / REAL( jnzts, wp ) 
    332       zr_p2dt(:) = 1._wp / p2dt(:) 
     332      zr_p2dt = 1._wp / p2dt 
    333333      ! 
    334334      !                                                          ! =========== 
     
    375375         ! total advective trend 
    376376         DO jk = 1, jpkm1 
    377             z2dtt = p2dt(jk) 
     377            z2dtt = p2dt 
    378378            DO jj = 2, jpjm1 
    379379               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    446446            IF( jl == 1 ) THEN              ! Euler forward to kick things off 
    447447              jtb = 1   ;   jtn = 1   ;   jta = 2 
    448               zts(:) = p2dt(:) * z_rzts 
     448              zts = p2dt * z_rzts 
    449449              jtaken = MOD( jnzts + 1 , 2)  ! Toggle to collect every second flux 
    450450                                            ! starting at jl =1 if jnzts is odd;  
     
    452452            ELSEIF( jl == 2 ) THEN          ! First leapfrog step 
    453453              jtb = 1   ;   jtn = 2   ;   jta = 3 
    454               zts(:) = 2._wp * p2dt(:) * z_rzts 
     454              zts = 2._wp * p2dt * z_rzts 
    455455            ELSE                            ! Shuffle pointers for subsequent leapfrog steps 
    456456              jtb = MOD(jtb,3) + 1 
     
    462462                  DO ji = fs_2, fs_jpim1 
    463463                     zwz(ji,jj,jk) = 0.5_wp * pwn(ji,jj,jk) * ( ztrs(ji,jj,jk,jtn) + ztrs(ji,jj,jk-1,jtn) ) 
    464                      IF( jtaken == 0 ) zwzts(ji,jj,jk) = zwzts(ji,jj,jk) + zwz(ji,jj,jk)*zts(jk)           ! Accumulate time-weighted vertcal flux 
     464                     IF( jtaken == 0 ) zwzts(ji,jj,jk) = zwzts(ji,jj,jk) + zwz(ji,jj,jk)*zts           ! Accumulate time-weighted vertcal flux 
    465465                  END DO 
    466466               END DO 
     
    475475                     ! total advective trends 
    476476                     ztra = - zbtr * (  zhdiv(ji,jj,jk) + zwz(ji,jj,jk) - zwz(ji  ,jj  ,jk+1) ) 
    477                      ztrs(ji,jj,jk,jta) = ztrs(ji,jj,jk,jtb) + zts(jk) * ztra 
     477                     ztrs(ji,jj,jk,jta) = ztrs(ji,jj,jk,jtb) + zts * ztra 
    478478                  END DO 
    479479               END DO 
     
    485485            DO jj = 2, jpjm1 
    486486               DO ji = fs_2, fs_jpim1 
    487                   zwz(ji,jj,jk) = zwzts(ji,jj,jk) * zr_p2dt(jk) - zwz_sav(ji,jj,jk) 
     487                  zwz(ji,jj,jk) = zwzts(ji,jj,jk) * zr_p2dt - zwz_sav(ji,jj,jk) 
    488488               END DO 
    489489            END DO 
     
    553553      !!       in-space based differencing for fluid 
    554554      !!---------------------------------------------------------------------- 
    555       REAL(wp), DIMENSION(jpk)         , INTENT(in   ) ::   p2dt            ! vertical profile of tracer time-step 
     555      REAL(wp)                         , INTENT(in   ) ::   p2dt            ! tracer time-step 
    556556      REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT(in   ) ::   pbef, paft      ! before & after field 
    557557      REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT(inout) ::   paa, pbb, pcc   ! monotonic fluxes in the 3 directions 
     
    584584            DO jk = mikt(ji,jj), jpkm1 
    585585               ikm1 = MAX(jk-1,mikt(ji,jj)) 
    586                z2dtt = p2dt(jk) 
     586               z2dtt = p2dt 
    587587                
    588588               ! search maximum in neighbourhood 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_ubs.F90

    r4990 r5282  
    8181      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype          ! =TRA or TRC (tracer indicator) 
    8282      INTEGER                              , INTENT(in   ) ::   kjpt            ! number of tracers 
    83       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt            ! vertical profile of tracer time-step 
     83      REAL(wp)                             , INTENT(in   ) ::   p2dt            ! tracer time-step 
    8484      REAL(wp), DIMENSION(jpi,jpj,jpk     ), INTENT(in   ) ::   pun, pvn, pwn   ! 3 ocean transport components 
    8585      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb, ptn        ! before and now tracer fields 
     
    207207         ! update and guess with monotonic sheme 
    208208         DO jk = 1, jpkm1 
    209             z2dtt = p2dt(jk) 
     209            z2dtt = p2dt 
    210210            DO jj = 2, jpjm1 
    211211               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    281281      !!       in-space based differencing for fluid 
    282282      !!---------------------------------------------------------------------- 
    283       REAL(wp), INTENT(in   ), DIMENSION(jpk)          ::   p2dt   ! vertical profile of tracer time-step 
     283      REAL(wp), INTENT(in   )                          ::   p2dt   ! tracer time-step 
    284284      REAL(wp),                DIMENSION (jpi,jpj,jpk) ::   pbef   ! before field 
    285285      REAL(wp), INTENT(inout), DIMENSION (jpi,jpj,jpk) ::   paft   ! after field 
     
    340340 
    341341      DO jk = 1, jpkm1 
    342          z2dtt = p2dt(jk) 
     342         z2dtt = p2dt 
    343343         DO jj = 2, jpjm1 
    344344            DO ji = fs_2, fs_jpim1   ! vector opt. 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/trabbl.F90

    r4990 r5282  
    362362         DO ji = 1, jpi 
    363363            ik = mbkt(ji,jj)                             ! bottom T-level index 
    364             zts (ji,jj,jp_tem) = tsb(ji,jj,ik,jp_tem)    ! bottom before T and S 
    365             zts (ji,jj,jp_sal) = tsb(ji,jj,ik,jp_sal) 
     364            zts(ji,jj,jp_tem) = tsb(ji,jj,ik,jp_tem)    ! bottom before T and S 
     365            zts(ji,jj,jp_sal) = tsb(ji,jj,ik,jp_sal) 
    366366            ! 
    367367            zdep(ji,jj) = fsdept(ji,jj,ik)               ! bottom T-level reference depth 
    368             zub (ji,jj) = un(ji,jj,mbku(ji,jj))          ! bottom velocity 
    369             zvb (ji,jj) = vn(ji,jj,mbkv(ji,jj)) 
     368            zub(ji,jj) = un(ji,jj,mbku(ji,jj))          ! bottom velocity 
     369            zvb(ji,jj) = vn(ji,jj,mbkv(ji,jj)) 
    370370         END DO 
    371371      END DO 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/traldf.F90

    r4990 r5282  
    326326      ELSE 
    327327         DO jk = 1, jpkm1 
    328             t0_ldf(:,:,jk) = ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / ( z12 *rdttra(jk) ) 
    329             s0_ldf(:,:,jk) = ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / ( z12 *rdttra(jk) ) 
     328            t0_ldf(:,:,jk) = ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / ( z12 *rdt ) 
     329            s0_ldf(:,:,jk) = ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / ( z12 *rdt ) 
    330330         END DO 
    331331      ENDIF 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90

    r4990 r5282  
    120120  
    121121      ! set time step size (Euler/Leapfrog) 
    122       IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   r2dtra(:) =     rdttra(:)      ! at nit000             (Euler) 
    123       ELSEIF( kt <= nit000 + 1 )           THEN   ;   r2dtra(:) = 2._wp* rdttra(:)      ! at nit000 or nit000+1 (Leapfrog) 
     122IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   r2dt =     rdt      ! at nit000             (Euler) 
     123ELSEIF( kt <= nit000 + 1 )           THEN   ;   r2dt = 2._wp* rdt      ! at nit000 or nit000+1 (Leapfrog) 
    124124      ENDIF 
    125125 
     
    155155      ! trends computation 
    156156      IF( l_trdtra ) THEN      ! trend of the Asselin filter (tb filtered - tb)/dt      
    157          DO jk = 1, jpkm1 
    158             zfact = 1._wp / r2dtra(jk)              
     157      zfact = 1._wp / r2dt 
     158        DO jk = 1, jpkm1 
     159!            zfact = 1._wp / r2dt 
    159160            ztrdt(:,:,jk) = ( tsb(:,:,jk,jp_tem) - ztrdt(:,:,jk) ) * zfact 
    160161            ztrds(:,:,jk) = ( tsb(:,:,jk,jp_sal) - ztrds(:,:,jk) ) * zfact 
     
    297298      DO jn = 1, kjpt       
    298299         DO jk = 1, jpkm1 
    299             zfact1 = atfp * rdttra(jk) 
     300            zfact1 = atfp * rdt 
    300301            zfact2 = zfact1 / rau0 
    301302            DO jj = 1, jpj 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/trasbc.F90

    r4990 r5282  
    2828   USE sbcrnf          ! River runoff   
    2929   USE sbcisf          ! Ice shelf    
    30    USE sbcmod          ! ln_rnf   
    3130   USE iom 
    3231   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90

    r4990 r5282  
    6666      ! 
    6767      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000 
    68          r2dtra(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping) 
     68         r2dt =  rdt                          ! = rdt (restarting with Euler time stepping) 
    6969      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1 
    70          r2dtra(:) = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog) 
     70         r2dt = 2. * rdt                      ! = 2 rdt (leapfrog) 
    7171      ENDIF 
    7272 
     
    7878 
    7979      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend 
    80       CASE ( 0 )    ;    CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )  !   explicit scheme  
    81       CASE ( 1 )    ;    CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts )  !   implicit scheme  
     80      CASE ( 0 )    ;    CALL tra_zdf_exp( kt, nit000, 'TRA', r2dt, nn_zdfexp, tsb, tsa, jpts )  !   explicit scheme 
     81      CASE ( 1 )    ;    CALL tra_zdf_imp( kt, nit000, 'TRA', r2dt,            tsb, tsa, jpts )  !   implicit scheme 
    8282      CASE ( -1 )                                       ! esopa: test all possibility with control print 
    83          CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts ) 
     83         CALL tra_zdf_exp( kt, nit000, 'TRA', r2dt, nn_zdfexp, tsb, tsa, jpts ) 
    8484         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf0 - Ta: ', mask1=tmask,               & 
    8585         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    86          CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts )  
     86         CALL tra_zdf_imp( kt, nit000, 'TRA', r2dt,            tsb, tsa, jpts ) 
    8787         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf1 - Ta: ', mask1=tmask,               & 
    8888         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     
    9191      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics 
    9292         DO jk = 1, jpkm1 
    93             ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(:,:,jk) 
    94             ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(:,:,jk) 
     93            ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dt ) - ztrdt(:,:,jk) 
     94            ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dt ) - ztrds(:,:,jk) 
    9595         END DO 
    9696         CALL lbc_lnk( ztrdt, 'T', 1. ) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_exp.F90

    r3294 r5282  
    8181      INTEGER                              , INTENT(in   ) ::   kjpt        ! number of tracers 
    8282      INTEGER                              , INTENT(in   ) ::   kn_zdfexp   ! number of sub-time step 
    83       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt        ! vertical profile of tracer time-step 
     83      REAL(wp)                             , INTENT(in   ) ::   p2dt        ! tracer time-step 
    8484      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb         ! before and now tracer fields 
    8585      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta         ! tracer trend  
     
    136136                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    137137                     ze3tr = zlavmr / fse3t_n(ji,jj,jk) 
    138                      zwx(ji,jj,jk) = zwx(ji,jj,jk) + p2dt(jk) * ( zwy(ji,jj,jk) - zwy(ji,jj,jk+1) ) * ze3tr 
     138                     zwx(ji,jj,jk) = zwx(ji,jj,jk) + p2dt * ( zwy(ji,jj,jk) - zwy(ji,jj,jk+1) ) * ze3tr 
    139139                  END DO 
    140140               END DO 
     
    150150                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    151151                     ze3tb = fse3t_b(ji,jj,jk) / fse3t(ji,jj,jk)                          ! before e3t 
    152                      ztra  = zwx(ji,jj,jk) - ptb(ji,jj,jk,jn) + p2dt(jk) * pta(ji,jj,jk,jn)       ! total trends * 2*rdt  
     152                     ztra  = zwx(ji,jj,jk) - ptb(ji,jj,jk,jn) + p2dt * pta(ji,jj,jk,jn)       ! total trends * 2*rdt 
    153153                     pta(ji,jj,jk,jn) = ( ze3tb * ptb(ji,jj,jk,jn) + ztra ) * tmask(ji,jj,jk) 
    154154                  END DO 
     
    159159               DO jj = 2, jpjm1  
    160160                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    161                      pta(ji,jj,jk,jn) = ( zwx(ji,jj,jk) + p2dt(jk) * pta(ji,jj,jk,jn) ) * tmask(ji,jj,jk) 
     161                     pta(ji,jj,jk,jn) = ( zwx(ji,jj,jk) + p2dt * pta(ji,jj,jk,jn) ) * tmask(ji,jj,jk) 
    162162                  END DO 
    163163               END DO 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_imp.F90

    r4990 r5282  
    8282      CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator) 
    8383      INTEGER                              , INTENT(in   ) ::   kjpt     ! number of tracers 
    84       REAL(wp), DIMENSION(        jpk     ), INTENT(in   ) ::   p2dt     ! vertical profile of tracer time-step 
     84      REAL(wp)                             , INTENT(in   ) ::   p2dt     ! tracer time-step 
    8585      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb      ! before and now tracer fields 
    8686      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta      ! tracer trend  
     
    154154                     ze3ta =  ( 1. - r_vvl ) +        r_vvl   * fse3t_a(ji,jj,jk)   ! after scale factor at T-point 
    155155                     ze3tn =         r_vvl   + ( 1. - r_vvl ) * fse3t_n(ji,jj,jk)   ! now   scale factor at T-point 
    156                      zwi(ji,jj,jk) = - p2dt(jk) * zwt(ji,jj,jk  ) / ( ze3tn * fse3w(ji,jj,jk  ) ) 
    157                      zws(ji,jj,jk) = - p2dt(jk) * zwt(ji,jj,jk+1) / ( ze3tn * fse3w(ji,jj,jk+1) ) 
     156                     zwi(ji,jj,jk) = - p2dt * zwt(ji,jj,jk  ) / ( ze3tn * fse3w(ji,jj,jk  ) ) 
     157                     zws(ji,jj,jk) = - p2dt * zwt(ji,jj,jk+1) / ( ze3tn * fse3w(ji,jj,jk+1) ) 
    158158                     zwd(ji,jj,jk) = ze3ta - zwi(ji,jj,jk) - zws(ji,jj,jk) 
    159159                 END DO 
     
    199199               ze3tn = ( 1. - r_vvl ) + r_vvl * fse3t(ji,jj,mikt(ji,jj)) 
    200200               pta(ji,jj,mikt(ji,jj),jn) = ze3tb * ptb(ji,jj,mikt(ji,jj),jn)                     & 
    201                   &                      + p2dt(mikt(ji,jj)) * ze3tn * pta(ji,jj,mikt(ji,jj),jn) 
     201                  &                      + p2dt * ze3tn * pta(ji,jj,mikt(ji,jj),jn) 
    202202               DO jk = mikt(ji,jj)+1, jpkm1 
    203203                  ze3tb = ( 1. - r_vvl ) + r_vvl * fse3t_b(ji,jj,jk) 
    204                   ze3tn = ( 1. - r_vvl ) + r_vvl * fse3t  (ji,jj,jk) 
    205                   zrhs = ze3tb * ptb(ji,jj,jk,jn) + p2dt(jk) * ze3tn * pta(ji,jj,jk,jn)   ! zrhs=right hand side  
     204                  ze3tn = ( 1. - r_vvl ) + r_vvl * fse3t(ji,jj,jk) 
     205                  zrhs = ze3tb * ptb(ji,jj,jk,jn) + p2dt * ze3tn * pta(ji,jj,jk,jn)   ! zrhs=right hand side 
    206206                  pta(ji,jj,jk,jn) = zrhs - zwi(ji,jj,jk) / zwt(ji,jj,jk-1) * pta(ji,jj,jk-1,jn) 
    207207               END DO 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl.F90

    r4990 r5282  
    3232   USE ioipsl          ! NetCDF library 
    3333   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    34    USE diadimg         ! dimg direct access file format output 
    3534   USE trdmxl_rst      ! restart for diagnosing the ML trends 
    3635   USE prtctl          ! Print control 
     
    298297      !!  
    299298      !! ** Purpose :  Compute and cumulate the mixed layer trends over an analysis 
    300       !!               period, and write NetCDF (or dimg) outputs. 
     299      !!               period, and write NetCDF outputs. 
    301300      !! 
    302301      !! ** Method/usage : 
     
    349348      REAL(wp), POINTER, DIMENSION(:,:  ) ::  ztmltot2, zsmltot2, ztmlres2, zsmlres2, ztmlatf2, zsmlatf2, ztmltrdm2, zsmltrdm2   
    350349      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztmltrd2, zsmltrd2   ! only needed for mean diagnostics 
    351 #if defined key_dimgout 
    352       INTEGER ::  iyear,imon,iday 
    353       CHARACTER(LEN=80) :: cltext, clmode 
    354 #endif 
    355350      !!---------------------------------------------------------------------- 
    356351   
     
    801796      END IF 
    802797 
    803       IF( nn_cla == 1 )   CALL ctl_warn( '      You set n_cla = 1. Note that the Mixed-Layer diagnostics  ',   & 
    804          &                               '      are not exact along the corresponding straits.            ') 
    805  
    806798      !                                   ! allocate trdmxl arrays 
    807799      IF( trd_mxl_alloc()    /= 0 )   CALL ctl_stop( 'STOP', 'trd_mxl_init : unable to allocate trdmxl     arrays' ) 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl_rst.F90

    r4990 r5282  
    5959            WRITE(numout,*) 
    6060            SELECT CASE ( jprstlib ) 
    61             CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart_mxl binary file: '//clname 
    6261            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart_mxl NetCDF file: '//clname 
    6362            END SELECT 
     
    140139         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~' 
    141140      ENDIF 
    142       IF ( jprstlib == jprstdimg ) THEN 
    143          ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    144          ! if {cn_trdrst_in}.nc exists, then set jlibalt to jpnf90 
    145          INQUIRE( FILE = TRIM(cn_trdrst_in)//'.nc', EXIST = llok ) 
    146          IF ( llok ) THEN   ;   jlibalt = jpnf90    
    147          ELSE               ;   jlibalt = jprstlib    
    148          ENDIF 
    149       ENDIF 
    150141 
    151142      CALL iom_open( cn_trdrst_in, inum, kiolib = jlibalt )  
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRD/trdtra.F90

    r4990 r5282  
    3636   PUBLIC   trd_tra   ! called by all tra_... modules 
    3737 
    38    REAL(wp) ::   r2dt   ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0 
     38!   REAL(wp) ::   r2dt   ! time-step, = 2 rdt except at nit000 (=rdt) if neuler=0 
    3939 
    4040   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   trdtx, trdty, trdt   ! use to store the temperature trends 
     
    227227      !!---------------------------------------------------------------------- 
    228228 
    229       IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt      ! = rdtra (restart with Euler time stepping) 
    230       ELSEIF(               kt <= nit000 + 1) THEN   ;   r2dt = 2. * rdt      ! = 2 rdttra (leapfrog) 
     229      IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt      ! = rdt (restart with Euler time stepping) 
     230      ELSEIF(               kt <= nit000 + 1) THEN   ;   r2dt = 2. * rdt      ! = 2 rdt (leapfrog) 
    231231      ENDIF 
    232232 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/TRD/trdvor.F90

    r4990 r5282  
    8585      !!  
    8686      !! ** Purpose :  computation of cumulated trends over analysis period 
    87       !!               and make outputs (NetCDF or DIMG format) 
     87      !!               and make outputs (NetCDF format) 
    8888      !!---------------------------------------------------------------------- 
    8989      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   putrd, pvtrd   ! U and V trends  
     
    318318      !!  
    319319      !! ** Purpose :  computation of cumulated trends over analysis period 
    320       !!               and make outputs (NetCDF or DIMG format) 
     320      !!               and make outputs (NetCDF format) 
    321321      !!---------------------------------------------------------------------- 
    322322      INTEGER                   , INTENT(in   ) ::   kt             ! time step 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r4990 r5282  
    4242   !!---------------------------------------------------------------------- 
    4343   USE step_oce        ! module used in the ocean time stepping module 
    44    USE cla             ! cross land advection               (tra_cla routine) 
    4544   USE domcfg          ! domain configuration               (dom_cfg routine) 
    4645   USE mppini          ! shared/distributed memory setting (mpp_init routine) 
     
    388387         &                  CALL bdytide_init   ! Open boundaries initialisation of tidal harmonic forcing 
    389388 
    390                             CALL dyn_nept_init  ! simplified form of Neptune effect 
    391389 
    392390      !      
     
    429427 
    430428      !                                     ! Misc. options 
    431       IF( nn_cla == 1 .AND. cp_cfg == 'orca' .AND. jp_cfg == 2 )   CALL cla_init       ! Cross Land Advection 
    432429                            CALL icb_init( rdt, nit000)   ! initialise icebergs instance 
    433430      
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/step.F90

    r5012 r5282  
    158158      IF( lk_traldf_eiv )   CALL ldf_eiv( kstp )      ! eddy induced velocity coefficient 
    159159#endif 
    160 #if defined key_traldf_c3d && key_traldf_smag 
    161                           CALL ldf_tra_smag( kstp )      ! eddy induced velocity coefficient 
    162 #  endif 
    163 #if defined key_dynldf_c3d && key_dynldf_smag 
    164                           CALL ldf_dyn_smag( kstp )      ! eddy induced velocity coefficient 
    165 #  endif 
    166160 
    167161      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    185179          IF(  ln_asmiau .AND. & 
    186180             & ln_dyninc       )  CALL dyn_asm_inc  ( kstp )   ! apply dynamics assimilation increment 
    187           IF( ln_neptsimp )       CALL dyn_nept_cor ( kstp )   ! subtract Neptune velocities (simplified) 
    188181          IF( lk_bdy           )  CALL bdy_dyn3d_dmp( kstp )   ! bdy damping trends 
    189182                                  CALL dyn_adv      ( kstp )   ! advection (vector or flux form) 
    190183                                  CALL dyn_vor      ( kstp )   ! vorticity term including Coriolis 
    191184                                  CALL dyn_ldf      ( kstp )   ! lateral mixing 
    192           IF( ln_neptsimp )       CALL dyn_nept_cor ( kstp )   ! add Neptune velocities (simplified) 
    193185#if defined key_agrif 
    194186          IF(.NOT. Agrif_Root())  CALL Agrif_Sponge_dyn        ! momentum sponge 
     
    289281           & ln_dyninc      )  CALL dyn_asm_inc( kstp )     ! apply dynamics assimilation increment 
    290282        IF( ln_bkgwri )        CALL asm_bkg_wri( kstp )     ! output background fields 
    291         IF( ln_neptsimp )      CALL dyn_nept_cor( kstp )    ! subtract Neptune velocities (simplified) 
    292283        IF( lk_bdy          )  CALL bdy_dyn3d_dmp(kstp )    ! bdy damping trends 
    293284                               CALL dyn_adv( kstp )         ! advection (vector or flux form) 
    294285                               CALL dyn_vor( kstp )         ! vorticity term including Coriolis 
    295286                               CALL dyn_ldf( kstp )         ! lateral mixing 
    296         IF( ln_neptsimp )      CALL dyn_nept_cor( kstp )    ! add Neptune velocities (simplified) 
    297287#if defined key_agrif 
    298288        IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_dyn        ! momemtum sponge 
  • branches/2015/dev_r5056_CMCC4_simplification/NEMOGCM/NEMO/OPA_SRC/step_oce.F90

    r4990 r5282  
    5050   USE dynspg_oce       ! surface pressure gradient        (dyn_spg routine) 
    5151   USE dynspg           ! surface pressure gradient        (dyn_spg routine) 
    52    USE dynnept          ! simp. form of Neptune effect(dyn_nept_cor routine) 
    5352 
    5453   USE dynnxt           ! time-stepping                    (dyn_nxt routine) 
     
    6867   USE ldfslp           ! iso-neutral slopes               (ldf_slp routine) 
    6968   USE ldfeiv           ! eddy induced velocity coef.      (ldf_eiv routine) 
    70    USE ldftra_smag      ! Smagirinsky diffusion            (ldftra_smag routine) 
    71    USE ldfdyn_smag      ! Smagorinsky viscosity            (ldfdyn_smag routine)  
    7269 
    7370   USE zdftmx           ! tide-induced vertical mixing     (zdf_tmx routine) 
Note: See TracChangeset for help on using the changeset viewer.