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 5602 for branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

Ignore:
Timestamp:
2015-07-16T13:55:15+02:00 (9 years ago)
Author:
cbricaud
Message:

merge change from trunk rev 5003 to 5519 ( rev where branche 3.6_stable were created )

Location:
branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcadv.F90

    r5601 r5602  
    8484      IF( kt == nittrc000 )   CALL trc_adv_ctl          ! initialisation & control of options 
    8585 
    86       IF( ln_top_euler) THEN 
    87          r2dt(:) =  rdttrc(:)              ! = rdttrc (use Euler time stepping) 
    88       ELSE 
    89          IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
    90             r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    91          ELSEIF( kt <= nittrc000 + 1 ) THEN          ! at nittrc000 or nittrc000+1 
    92             r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    93          ENDIF 
     86      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN     ! at nittrc000 
     87         r2dt(:) =  rdttrc(:)           ! = rdttrc (use or restarting with Euler time stepping) 
     88      ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1 
     89         r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    9490      ENDIF 
    95  
    9691      !                                                   ! effective transport 
    9792      DO jk = 1, jpkm1 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r4990 r5602  
    2424   USE trdtra 
    2525   USE trd_oce 
     26   USE iom 
    2627 
    2728   IMPLICIT NONE 
     
    4243   !!---------------------------------------------------------------------- 
    4344   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    44    !! $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/TRP/trcdmp.F90,v 1.11 2006/09/01 14:03:49 opalod Exp $  
     45   !! $Id$  
    4546   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4647   !!---------------------------------------------------------------------- 
     
    125126                     DO jj = 2, jpjm1 
    126127                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    127                            IF( avt(ji,jj,jk) <= 5.e-4 )  THEN  
     128                           IF( avt(ji,jj,jk) <= 5.e-4_wp )  THEN  
    128129                              ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) 
    129130                              tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     
    184185      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    185186      ! 
    186       INTEGER :: ji, jj, jk, jn, jl, jc                     ! dummy loop indicesa 
     187      INTEGER :: ji , jj, jk, jn, jl, jc                     ! dummy loop indicesa 
     188      INTEGER :: isrow                                      ! local index 
    187189      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta       ! 3D  workspace 
    188190 
     
    200202            ! 
    201203            SELECT CASE ( jp_cfg ) 
     204            !                                           ! ======================= 
     205            CASE ( 1 )                                  ! eORCA_R1 configuration 
     206            !                                           ! ======================= 
     207            isrow = 332 - jpjglo 
     208            ! 
     209                                                        ! Caspian Sea 
     210            nctsi1(1)   = 332  ; nctsj1(1)   = 243 - isrow 
     211            nctsi2(1)   = 344  ; nctsj2(1)   = 275 - isrow 
     212            !                                         
    202213            !                                           ! ======================= 
    203214            CASE ( 2 )                                  !  ORCA_R2 configuration 
     
    302313      !!---------------------------------------------------------------------- 
    303314      ! 
     315      INTEGER :: imask  !local file handle 
     316 
    304317      IF( nn_timing == 1 )  CALL timing_start('trc_dmp_init') 
    305318      ! 
    306       SELECT CASE ( nn_hdmp_tr ) 
    307       CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '   tracer damping in the Med & Red seas only' 
    308       CASE ( 1:90 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping poleward of', nn_hdmp_tr, ' degrees' 
    309       CASE DEFAULT 
    310          WRITE(ctmp1,*) '          bad flag value for nn_hdmp_tr = ', nn_hdmp_tr 
    311          CALL ctl_stop(ctmp1) 
    312       END SELECT 
    313319 
    314320      IF( lzoom )   nn_zdmp_tr = 0           ! restoring to climatology at closed north or south boundaries 
     
    325331         &   CALL ctl_stop( 'passive trace damping need key_tradmp to compute damping coef.' ) 
    326332      ! 
    327       !                          ! Damping coefficients initialization 
    328       IF( lzoom ) THEN   ;   CALL dtacof_zoom( restotr ) 
    329       ELSE               ;   CALL dtacof( nn_hdmp_tr, rn_surf_tr, rn_bot_tr, rn_dep_tr,  & 
    330                              &            nn_file_tr, 'TRC'     , restotr                ) 
    331       ENDIF 
     333      !                          ! Read damping coefficients from file 
     334      !Read in mask from file 
     335      CALL iom_open ( cn_resto_tr, imask) 
     336      CALL iom_get  ( imask, jpdom_autoglo, 'resto', restotr) 
     337      CALL iom_close( imask ) 
    332338      ! 
    333339      IF( nn_timing == 1 )  CALL timing_stop('trc_dmp_init') 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90

    r4990 r5602  
    217217      ENDIF 
    218218 
    219       IF( .NOT. ln_trcldf_diff ) THEN 
    220          IF(lwp) WRITE(numout,*) '          No lateral diffusion on passive tracers' 
    221          nldf = -2 
    222       ENDIF 
    223  
    224219      IF(lwp) THEN 
    225220         WRITE(numout,*) 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90

    r4624 r5602  
    3333 
    3434   !                                        !!: ** lateral mixing namelist (nam_trcldf) ** 
    35    LOGICAL , PUBLIC ::   ln_trcldf_diff      !: flag of perform or not the lateral diff. 
    3635   LOGICAL , PUBLIC ::   ln_trcldf_lap       !: laplacian operator 
    3736   LOGICAL , PUBLIC ::   ln_trcldf_bilap     !: bilaplacian operator 
     
    5150   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) ** 
    5251   !                          !!* Namelist namtrc_dmp : passive tracer newtonian damping * 
    53    INTEGER , PUBLIC ::   nn_hdmp_tr    ! = 0/-1/'latitude' for damping over passive tracer 
    5452   INTEGER , PUBLIC ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer 
    55    REAL(wp), PUBLIC ::   rn_surf_tr    ! surface time scale for internal damping        [days] 
    56    REAL(wp), PUBLIC ::   rn_bot_tr     ! bottom time scale for internal damping         [days] 
    57    REAL(wp), PUBLIC ::   rn_dep_tr     ! depth of transition between rn_surf and rn_bot [meters] 
    58    INTEGER , PUBLIC ::   nn_file_tr    ! = 1 create a damping.coeff NetCDF file 
     53   CHARACTER(LEN=200) , PUBLIC :: cn_resto_tr    !File containing restoration coefficient 
    5954 
    6055   !!---------------------------------------------------------------------- 
     
    7772         &                 ln_trcadv_ubs  , ln_trcadv_qck, ln_trcadv_msc_ups 
    7873 
    79       NAMELIST/namtrc_ldf/ ln_trcldf_diff , ln_trcldf_lap  ,     & 
     74      NAMELIST/namtrc_ldf/ ln_trcldf_lap  ,     & 
    8075         &                 ln_trcldf_bilap, ln_trcldf_level,     & 
    8176         &                 ln_trcldf_hor  , ln_trcldf_iso  , rn_ahtrc_0, rn_ahtrb_0 
    8277      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp 
    8378      NAMELIST/namtrc_rad/ ln_trcrad 
    84       NAMELIST/namtrc_dmp/ nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, & 
    85         &                  rn_bot_tr , rn_dep_tr , nn_file_tr 
     79      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr 
    8680      !!---------------------------------------------------------------------- 
    8781 
     
    126120         WRITE(numout,*) '~~~~~~~~~~~' 
    127121         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)' 
    128          WRITE(numout,*) '      perform lateral diffusion or not                   ln_trcldf_diff  = ', ln_trcldf_diff 
    129122         WRITE(numout,*) '      laplacian operator                                 ln_trcldf_lap   = ', ln_trcldf_lap 
    130123         WRITE(numout,*) '      bilaplacian operator                               ln_trcldf_bilap = ', ln_trcldf_bilap 
     
    184177         WRITE(numout,*) '~~~~~~~' 
    185178         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter' 
    186          WRITE(numout,*) '      tracer damping option          nn_hdmp_tr = ', nn_hdmp_tr 
    187179         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)' 
    188          WRITE(numout,*) '      surface time scale (days)      rn_surf_tr = ', rn_surf_tr 
    189          WRITE(numout,*) '      bottom time scale (days)       rn_bot_tr  = ', rn_bot_tr 
    190          WRITE(numout,*) '      depth of transition (meters)   rn_dep_tr  = ', rn_dep_tr 
    191          WRITE(numout,*) '      create a damping.coeff file    nn_file_tr = ', nn_file_tr 
     180         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr 
    192181      ENDIF 
    193182      ! 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r4990 r5602  
    118118      ! set time step size (Euler/Leapfrog) 
    119119      IF( neuler == 0 .AND. kt ==  nittrc000 ) THEN  ;  r2dt(:) =     rdttrc(:)   ! at nittrc000             (Euler) 
    120       ELSEIF( kt <= nittrc000 + 1 )            THEN  ;  r2dt(:) = 2.* rdttrc(:)   ! at nit000 or nit000+1 (Leapfrog) 
     120      ELSEIF( kt <= nittrc000 + nn_dttrc )     THEN  ;  r2dt(:) = 2.* rdttrc(:)   ! at nit000 or nit000+1 (Leapfrog) 
    121121      ENDIF 
    122122 
     
    137137      ELSE 
    138138         ! Leap-Frog + Asselin filter time stepping 
    139          IF( lk_vvl ) THEN   ;   CALL tra_nxt_vvl( kt, nittrc000, 'TRC', trb, trn, tra, jptra )      ! variable volume level (vvl)  
    140          ELSE                ;   CALL tra_nxt_fix( kt, nittrc000, 'TRC', trb, trn, tra, jptra )      ! fixed    volume level  
     139         IF( lk_vvl ) THEN   ;   CALL tra_nxt_vvl( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
     140           &                                                                sbc_trc, sbc_trc_b, jptra )      ! variable volume level (vvl)  
     141         ELSE                ;   CALL tra_nxt_fix( kt, nittrc000,         'TRC', trb, trn, tra, jptra )      ! fixed    volume level  
    141142         ENDIF 
    142143      ENDIF 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r5601 r5602  
    1919   USE trc             ! ocean  passive tracers variables 
    2020   USE prtctl_trc      ! Print control for debbuging 
     21   USE iom 
    2122   USE trd_oce 
    2223   USE trdtra 
     
    2627 
    2728   PUBLIC   trc_sbc   ! routine called by step.F90 
     29 
     30   REAL(wp) ::   r2dt  !  time-step at surface 
    2831 
    2932   !! * Substitutions 
     
    6063      INTEGER, INTENT( in ) ::   kt          ! ocean time-step index 
    6164      ! 
    62       INTEGER  ::   ji, jj, jn           ! dummy loop indices 
    63       REAL(wp) ::   zsrau, zse3t   ! temporary scalars 
     65      INTEGER  ::   ji, jj, jn                                     ! dummy loop indices 
     66      REAL(wp) ::   zse3t, zrtrn, zratio, zfact                    ! temporary scalars 
     67      REAL(wp) ::   zswitch, zftra, zcd, zdtra, ztfx, ztra         ! temporary scalars 
    6468      CHARACTER (len=22) :: charout 
    6569      REAL(wp), POINTER, DIMENSION(:,:  ) :: zsfx 
    6670      REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrtrd 
     71 
    6772      !!--------------------------------------------------------------------- 
    6873      ! 
     
    7277                      CALL wrk_alloc( jpi, jpj,      zsfx   ) 
    7378      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrd ) 
     79      ! 
     80      zrtrn = 1.e-15_wp 
     81 
     82      SELECT CASE( nn_ice_embd )         ! levitating or embedded sea-ice option 
     83         CASE( 0    )   ;   zswitch = 1  ! (0) standard levitating sea-ice : salt exchange only 
     84         CASE( 1, 2 )   ;   zswitch = 0  ! (1) levitating sea-ice: salt and volume exchange but no pressure effect                                 
     85                                         ! (2) embedded sea-ice : salt and volume fluxes and pressure 
     86      END SELECT 
     87 
     88      IF( ln_top_euler) THEN 
     89         r2dt =  rdttrc(1)              ! = rdttrc (use Euler time stepping) 
     90      ELSE 
     91         IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
     92            r2dt = rdttrc(1)           ! = rdttrc (restarting with Euler time stepping) 
     93         ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1 
     94            r2dt = 2. * rdttrc(1)       ! = 2 rdttrc (leapfrog) 
     95         ENDIF 
     96      ENDIF 
     97 
    7498 
    7599      IF( kt == nittrc000 ) THEN 
     
    77101         IF(lwp) WRITE(numout,*) 'trc_sbc : Passive tracers surface boundary condition' 
    78102         IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
     103 
     104         IF( ln_rsttr .AND.    &                     ! Restart: read in restart  file 
     105            iom_varid( numrtr, 'sbc_'//TRIM(ctrcnm(1))//'_b', ldstop = .FALSE. ) > 0 ) THEN 
     106            IF(lwp) WRITE(numout,*) '          nittrc000-nn_dttrc surface tracer content forcing fields red in the restart file' 
     107            zfact = 0.5_wp 
     108            DO jn = 1, jptra 
     109               CALL iom_get( numrtr, jpdom_autoglo, 'sbc_'//TRIM(ctrcnm(jn))//'_b', sbc_trc_b(:,:,jn) )   ! before tracer content sbc 
     110            END DO 
     111         ELSE                                         ! No restart or restart not found: Euler forward time stepping 
     112           zfact = 1._wp 
     113           sbc_trc_b(:,:,:) = 0._wp 
     114         ENDIF 
     115      ELSE                                         ! Swap of forcing fields 
     116         IF( ln_top_euler ) THEN 
     117            zfact = 1._wp 
     118            sbc_trc_b(:,:,:) = 0._wp 
     119         ELSE 
     120            zfact = 0.5_wp 
     121            sbc_trc_b(:,:,:) = sbc_trc(:,:,:) 
     122         ENDIF 
     123         ! 
    79124      ENDIF 
    80125 
     
    90135 
    91136      ! 0. initialization 
    92       zsrau = 1. / rau0 
    93137      DO jn = 1, jptra 
    94138         ! 
    95139         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)  ! save trends 
    96140         !                                             ! add the trend to the general tracer trend 
    97          IF( lk_vvl ) THEN  ! online coupling with vvl 
    98  
    99              
     141 
     142         IF ( nn_ice_tr == -1 ) THEN  ! No tracers in sea ice (null concentration in sea ice) 
     143 
     144            DO jj = 2, jpj 
     145               DO ji = fs_2, fs_jpim1   ! vector opt. 
     146                  sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * trn(ji,jj,1,jn) 
     147               END DO 
     148            END DO 
     149 
     150         ELSE 
     151 
    100152            DO jj = 2, jpj 
    101153               DO ji = fs_2, fs_jpim1   ! vector opt. 
    102154                  zse3t = 1. / fse3t(ji,jj,1) 
    103                   tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) *  zsrau * trn(ji,jj,1,jn) * zse3t 
     155                  ! tracer flux at the ice/ocean interface (tracer/m2/s) 
     156                  zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 
     157                  zcd   =   trc_o(ji,jj,jn) * fmmflx(ji,jj) ! concentration dilution due to freezing-melting, 
     158                                                               ! only used in the levitating sea ice case 
     159                  ! tracer flux only       : add concentration dilution term in net tracer flux, no F-M in volume flux 
     160                  ! tracer and mass fluxes : no concentration dilution term in net tracer flux, F-M term in volume flux 
     161                  ztfx  = zftra + zswitch * zcd                ! net tracer flux (+C/D if no ice/ocean mass exchange) 
     162    
     163                  zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trn(ji,jj,1,jn) )  
     164                  IF ( zdtra < 0. ) THEN 
     165                     zratio = -zdtra * zse3t * r2dt / ( trn(ji,jj,1,jn) + zrtrn ) 
     166                     zdtra = MIN(1.0, zratio) * zdtra ! avoid negative concentrations to arise 
     167                  ENDIF 
     168                  sbc_trc(ji,jj,jn) =  zdtra  
    104169               END DO 
    105170            END DO 
    106          ELSE 
    107             DO jj = 2, jpj 
    108                DO ji = fs_2, fs_jpim1   ! vector opt. 
    109                   zse3t = 1. / fse3t(ji,jj,1) 
    110                   tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) *  zsrau * trn(ji,jj,1,jn) * zse3t 
    111                END DO 
    112             END DO 
    113          ENDIF 
    114  
     171         ENDIF 
     172         !                                       Concentration dilution effect on tracers due to evaporation & precipitation  
     173         DO jj = 2, jpj 
     174            DO ji = fs_2, fs_jpim1   ! vector opt. 
     175               zse3t = zfact / fse3t(ji,jj,1) 
     176               tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t 
     177            END DO 
     178         END DO 
     179         ! 
    115180         IF( l_trdtrc ) THEN 
    116181            ztrtrd(:,:,:) = tra(:,:,:,jn) - ztrtrd(:,:,:) 
     
    120185      END DO                                                     ! tracer loop 
    121186      !                                                          ! =========== 
     187 
     188      !                                           Write in the tracer restar  file 
     189      !                                          ******************************* 
     190      IF( lrst_trc ) THEN 
     191         IF(lwp) WRITE(numout,*) 
     192         IF(lwp) WRITE(numout,*) 'sbc : ocean surface tracer content forcing fields written in tracer restart file ',   & 
     193            &                    'at it= ', kt,' date= ', ndastp 
     194         IF(lwp) WRITE(numout,*) '~~~~' 
     195         DO jn = 1, jptra 
     196            CALL iom_rstput( kt, nitrst, numrtw, 'sbc_'//TRIM(ctrcnm(jn))//'_b', sbc_trc(:,:,jn) ) 
     197         END DO 
     198      ENDIF 
     199      ! 
    122200      IF( ln_ctl )   THEN 
    123201         WRITE(charout, FMT="('sbc ')") ;  CALL prt_ctl_trc_info(charout) 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r5601 r5602  
    108108          ! Partial steps: now horizontal gradient of passive 
    109109         IF( ln_zps    )THEN 
    110          IF( ln_crs_top ) THEN ;    CALL zps_hde_crs( kstp, jptra, trn, gtru, gtrv ) 
    111          ELSE              ;    CALL zps_hde( kstp, jptra, trn, pgtu=gtru, pgtv=gtrv, sgtu=gtrui, sgtv=gtrvi ) 
    112          ENDIF 
     110            IF( ln_crs_top ) THEN   
     111               CALL zps_hde_crs( kstp, jptra, trn, gtru, gtrv ) 
     112            ELSE 
     113               IF( ln_isfcav)        & 
     114                  CALL zps_hde_isf( kstp, jptra, trn, pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi )  ! Partial steps: now horizontal gradient of passive 
     115               ELSE 
     116                  CALL zps_hde    ( kstp, jptra, trn, gtru, gtrv )   ! Partial steps: now horizontal gradient of passive 
     117               ENDIF 
    113118         ENDIF 
    114119                                                                ! tracers at the bottom ocean level 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.F90

    r4990 r5602  
    7373      IF( kt == nittrc000 )   CALL zdf_ctl          ! initialisation & control of options 
    7474 
    75       IF( ln_top_euler) THEN 
    76          r2dt(:) =  rdttrc(:)              ! = rdttrc (use Euler time stepping) 
    77       ELSE 
    78          IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
    79             r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    80          ELSEIF( kt <= nittrc000 + 1 ) THEN          ! at nittrc000 or nittrc000+1 
    81             r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    82          ENDIF 
     75      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN     ! at nittrc000 
     76         r2dt(:) =  rdttrc(:)           ! = rdttrc (use or restarting with Euler time stepping) 
     77      ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1 
     78         r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    8379      ENDIF 
    8480 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trdmxl_trc.F90

    • Property svn:keywords set to Id
    r4990 r5602  
    7171   !!---------------------------------------------------------------------- 
    7272   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    73    !! $Header:  $  
     73   !! $Id$  
    7474   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    7575   !!---------------------------------------------------------------------- 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trdmxl_trc_rst.F90

    • Property svn:keywords set to Id
    r4990 r5602  
    2323   !!--------------------------------------------------------------------------------- 
    2424   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    25    !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/TRD/trdmxl_rst.F90,v 1.6 2006/11/14 09:46:13 opalod Exp $  
     25   !! $Id$  
    2626   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    2727   !!--------------------------------------------------------------------------------- 
     
    3939      ! 
    4040      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
    41       CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
     41      CHARACTER(LEN=50)   ::   clname   ! output restart file name 
     42      CHARACTER(LEN=256)  ::   clpath   ! full path to restart file 
    4243      CHARACTER (len=35) :: charout 
    4344      INTEGER :: jl,  jk, jn               ! loop indice 
     
    5152         ENDIF 
    5253         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trdrst_trc_out) 
    53          IF(lwp) WRITE(numout,*) '             open ocean restart_mld_trc NetCDF  '//clname 
    54          CALL iom_open( clname, nummldw_trc, ldwrt = .TRUE., kiolib = jprstlib ) 
     54         clpath = TRIM(cn_trcrst_outdir) 
     55         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
     56         IF(lwp) WRITE(numout,*) '             open ocean restart_mld_trc NetCDF  'TRIM(clpath)//TRIM(clname) 
     57         CALL iom_open( TRIM(clpath)//TRIM(clname), nummldw_trc, ldwrt = .TRUE., kiolib = jprstlib ) 
    5558      ENDIF 
    5659 
     
    133136      INTEGER ::  jlibalt = jprstlib 
    134137      LOGICAL ::  llok 
     138      CHARACTER(LEN=256)  ::   clpath   ! full path to restart file 
    135139      !!----------------------------------------------------------------------------- 
    136140       
     
    141145      ENDIF 
    142146       
     147      clpath = TRIM(cn_trcrst_indir) 
     148      IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
     149 
    143150      IF ( jprstlib == jprstdimg ) THEN 
    144151        ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    145152        ! if {cn_trdrst_trc_in}.nc exists, then set jlibalt to jpnf90 
    146         INQUIRE( FILE = TRIM(cn_trdrst_trc_in)//'.nc', EXIST = llok ) 
     153        INQUIRE( FILE = TRIM(clpath)//TRIM(cn_trdrst_trc_in)//'.nc', EXIST = llok ) 
    147154        IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    148155      ENDIF 
    149156 
    150       CALL iom_open( cn_trdrst_trc_in, inum, kiolib = jlibalt )  
     157      CALL iom_open( TRIM(clpath)//TRIM(cn_trdrst_trc_in), inum, kiolib = jlibalt )  
    151158       
    152159      IF( ln_trdmxl_trc_instant ) THEN  
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trdtrc.F90

    • Property svn:keywords set to Id
    r4990 r5602  
    3333   !!---------------------------------------------------------------------- 
    3434   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    35    !! $Header:  $  
     35   !! $Id$  
    3636   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    3737   !!---------------------------------------------------------------------- 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trdtrc_oce.F90

    • Property svn:keywords set to Id
    r4990 r5602  
    118118   !!---------------------------------------------------------------------- 
    119119   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    120    !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/TRD/trdmxl_oce.F90,v 1.2 2005/03/27 18:35:23 opalod Exp $  
     120   !! $Id$  
    121121   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    122122   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.