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 3680 for branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

Ignore:
Timestamp:
2012-11-27T15:42:24+01:00 (12 years ago)
Author:
rblod
Message:

First commit of the final branch for 2012 (future nemo_3_5), see ticket #1028

Location:
branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trcadv.F90

    r3294 r3680  
    8282      IF( kt == nittrc000 )   CALL trc_adv_ctl          ! initialisation & control of options 
    8383 
    84 #if ! defined key_pisces 
    85       IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
    86          r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    87       ELSEIF( kt <= nittrc000 + 1 ) THEN          ! at nittrc000 or nittrc000+1 
    88          r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
     84      IF( ln_top_euler) THEN 
     85         r2dt(:) =  rdttrc(:)              ! = rdttrc (use Euler time stepping) 
     86      ELSE 
     87         IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
     88            r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
     89         ELSEIF( kt <= nittrc000 + 1 ) THEN          ! at nittrc000 or nittrc000+1 
     90            r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
     91         ENDIF 
    8992      ENDIF 
    90 #else 
    91       r2dt(:) =  rdttrc(:)              ! = rdttrc (for PISCES use Euler time stepping) 
    92 #endif 
    9393 
    9494      !                                                   ! effective transport 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90

    r3294 r3680  
    8181      NAMELIST/namtrc_rad/ ln_trcrad 
    8282#if defined key_trcdmp 
    83       NAMELIST/namtrc_dmp/ nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, & 
     83      NAMELIST/namtrc_dmp/ ln_trcdmp, nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, & 
    8484        &                  rn_bot_tr , rn_dep_tr , nn_file_tr 
    8585#endif 
     
    156156         WRITE(numout,*) '~~~~~~~' 
    157157         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter' 
     158         WRITE(numout,*) '      add a damping term or not      ln_trcdmp = ', ln_trcdmp 
    158159         WRITE(numout,*) '      tracer damping option          nn_hdmp_tr = ', nn_hdmp_tr 
    159160         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)' 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r3294 r3680  
    3434   USE tranxt 
    3535# if defined key_agrif 
    36    USE agrif_top_update 
    3736   USE agrif_top_interp 
    3837# endif 
     
    146145      ENDIF 
    147146 
    148 #if defined key_agrif 
    149       ! Update tracer at AGRIF zoom boundaries 
    150       IF( .NOT.Agrif_Root() )    CALL Agrif_Update_Trc( kt )      ! children only 
    151 #endif       
    152  
    153147      ! trends computation 
    154148      IF( l_trdtrc ) THEN                                      ! trends 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90

    r3294 r3680  
    6363      IF( lk_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0 , jp_cfc1               )  ! CFC model 
    6464      IF( lk_c14b    )   CALL trc_rad_sms( kt, trb, trn, jp_c14b0, jp_c14b1              )  ! bomb C14 
    65       IF( lk_lobster )   CALL trc_rad_sms( kt, trb, trn, jp_lob0 , jp_lob1, cpreserv='Y' )  ! LOBSTER model 
    6665      IF( lk_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0 , jp_pcs1, cpreserv='Y' )  ! PISCES model 
    6766      IF( lk_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0 , jp_myt1               )  ! MY_TRC model 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r3625 r3680  
    5050      !!            tra = tra + emp * trn / e3t   for k=1 
    5151      !!         where emp, the surface freshwater budget (evaporation minus 
    52       !!         precipitation minus runoff) given in kg/m2/s is divided 
     52      !!         precipitation ) given in kg/m2/s is divided 
    5353      !!         by 1035 kg/m3 (density of ocean water) to obtain m/s. 
    5454      !! 
     
    7979      ENDIF 
    8080 
     81      ! Coupling online : river runoff is added to the horizontal divergence (hdivn) in the subroutine sbc_rnf_div  
     82      ! one only consider the concentration/dilution effect due to evaporation minus precipitation + freezing/melting of sea-ice 
    8183 
    82       IF( lk_offline ) THEN          ! sfx in dynamical files contains sfx  - rnf 
    83          zsfx(:,:) = sfx(:,:)   
    84       ELSE                           ! Concentration dilution effect on tracer due to evaporation, precipitation, and river runoff 
    85          IF( lk_vvl ) THEN                      ! volume variable 
    86             zsfx(:,:) = sfx(:,:) - emp(:,:)    
    87 !!ch         zsfx(:,:) = 0. 
    88          ELSE                                   ! linear free surface 
    89             IF( ln_rnf ) THEN  ;  zsfx(:,:) = sfx(:,:) - rnf(:,:)   !  E-P-R 
    90             ELSE               ;  zsfx(:,:) = sfx(:,:) 
    91             ENDIF  
    92          ENDIF  
    93       ENDIF  
     84      IF( .NOT. lk_offline .AND. lk_vvl ) THEN  ! online coupling + volume variable 
     85         zemps(:,:) = sfx(:,:) - emp(:,:) 
     86      ELSE 
     87         zemps(:,:) = emp(:,:) 
     88      ENDIF 
    9489 
    9590      ! 0. initialization 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r3294 r3680  
    2929 
    3030#if defined key_agrif 
    31    USE agrif_top_sponge ! Momemtum and tracers sponges 
     31   USE agrif_top_sponge ! tracers sponges 
     32   USE agrif_top_update ! tracers updates 
    3233#endif 
    3334 
     
    7677                                CALL trc_nxt( kstp )            ! tracer fields at next time step      
    7778         IF( ln_trcrad )        CALL trc_rad( kstp )            ! Correct artificial negative concentrations 
     79 
     80#if defined key_agrif 
     81      IF( .NOT. Agrif_Root())   CALL Agrif_Update_Trc( kstp )   ! Update tracer at AGRIF zoom boundaries : children only 
     82#endif 
    7883         IF( ln_zps    )        CALL zps_hde( kstp, jptra, trn, gtru, gtrv )  ! Partial steps: now horizontal gradient of passive 
    7984                                                                ! tracers at the bottom ocean level 
     
    98103   !!---------------------------------------------------------------------- 
    99104CONTAINS 
    100    SUBROUTINE trc_trp( kt )              ! Empty routine 
    101       INTEGER, INTENT(in) ::   kt 
    102       WRITE(*,*) 'trc_trp: You should not have seen this print! error?', kt 
     105   SUBROUTINE trc_trp( kstp )              ! Empty routine 
     106      INTEGER, INTENT(in) ::   kstp 
     107      WRITE(*,*) 'trc_trp: You should not have seen this print! error?', kstp 
    103108   END SUBROUTINE trc_trp 
    104109#endif 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.F90

    r3632 r3680  
    7373      IF( kt == nittrc000 )   CALL zdf_ctl          ! initialisation & control of options 
    7474 
    75 #if ! defined key_pisces 
    76       IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
    77          r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    78       ELSEIF( kt <= nittrc000 + 1 ) THEN          ! at nittrc000 or nittrc000+1 
    79          r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
     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 
    8083      ENDIF 
    81 #else 
    82       r2dt(:) =  rdttrc(:)              ! = rdttrc (for PISCES use Euler time stepping) 
    83 #endif 
    8484 
    8585      IF( l_trdtrc )  THEN 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trdmld_trc.F90

    r3320 r3680  
    3434   USE prtctl            ! print control 
    3535   USE sms_pisces        ! PISCES bio-model 
    36    USE sms_lobster       ! LOBSTER bio-model 
    3736   USE wrk_nemo          ! Memory allocation 
    3837 
     
    5352   INTEGER ::   ndimtrd1                         
    5453   INTEGER, SAVE ::  ionce, icount 
    55 #if defined key_lobster 
     54#if defined key_pisces_reduced 
    5655   INTEGER ::   nidtrdbio, nh_tb 
    5756   INTEGER, SAVE ::  ioncebio, icountbio 
     
    6261 
    6362   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  ztmltrd2   ! 
    64 #if defined key_lobster 
     63#if defined key_pisces_reduced 
    6564   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ztmltrdbio2  ! only needed for mean diagnostics in trd_mld_bio() 
    6665#endif 
     
    8180      !!---------------------------------------------------------------------- 
    8281      ALLOCATE( ztmltrd2(jpi,jpj,jpltrd_trc,jptra) ,      & 
    83 #if defined key_lobster 
     82#if defined key_pisces_reduced 
    8483         &      ztmltrdbio2(jpi,jpj,jpdiabio)      ,      & 
    8584#endif 
     
    133132         SELECT CASE ( nn_ctls_trc )                                ! choice of the control surface 
    134133            CASE ( -2  )   ;   STOP 'trdmld_trc : not ready '     !     -> isopycnal surface (see ???) 
    135 #if defined key_pisces || defined key_lobster 
     134#if defined key_pisces || defined key_pisces_reduced 
    136135            CASE ( -1  )   ;   nmld_trc(:,:) = neln(:,:)          !     -> euphotic layer with light criterion 
    137136#endif 
     
    232231      INTEGER                         , INTENT(in) ::   ktrd          ! bio trend index 
    233232      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in) ::   ptrc_trdmld   ! passive trc trend 
    234 #if defined key_lobster 
     233#if defined key_pisces_reduced 
    235234      ! 
    236235      INTEGER ::   ji, jj, jk, isum 
     
    940939      !!---------------------------------------------------------------------- 
    941940      INTEGER, INTENT( in ) ::   kt                       ! ocean time-step index 
    942 #if defined key_lobster 
     941#if defined key_pisces_reduced 
    943942      INTEGER  ::  jl, it, itmod 
    944943      LOGICAL  :: llwarn  = .TRUE., lldebug = .TRUE. 
     
    12171216      tmltrd_csum_ln_trc (:,:,:,:) = 0.e0   ;   rmld_sum_trc       (:,:)     = 0.e0 
    12181217 
    1219 #if defined key_lobster 
     1218#if defined key_pisces_reduced 
    12201219      nmoymltrdbio   = 0 
    12211220      tmltrd_sum_bio     (:,:,:) = 0.e0     ;   tmltrd_csum_ln_bio (:,:,:) = 0.e0 
    1222       DO jl = 1, jp_lobster_trd 
     1221      DO jl = 1, jp_pisces_trd 
    12231222          ctrd_bio(jl,1) = ctrbil(jl)   ! long name 
    12241223          ctrd_bio(jl,2) = ctrbio(jl)   ! short name 
     
    12341233         tml_sumb_trc       (:,:,:)   = 0.e0   ;   tmltrd_csum_ub_trc (:,:,:,:) = 0.e0     ! mean 
    12351234         tmltrd_atf_sumb_trc(:,:,:)   = 0.e0   ;   tmltrd_rad_sumb_trc(:,:,:)   = 0.e0  
    1236 #if defined key_lobster 
     1235#if defined key_pisces_reduced 
    12371236         tmltrd_csum_ub_bio (:,:,:) = 0.e0 
    12381237#endif 
     
    12421241      icount = 1   ;   ionce  = 1  ! open specifier    
    12431242 
    1244 #if defined key_lobster 
     1243#if defined key_pisces_reduced 
    12451244      icountbio = 1   ;   ioncebio  = 1  ! open specifier 
    12461245#endif 
     
    13371336      END DO 
    13381337 
    1339 #if defined key_lobster 
     1338#if defined key_pisces_reduced 
    13401339          !-- Create a NetCDF file and enter the define mode 
    13411340          CALL dia_nam( clhstnam, nn_trd_trc, 'trdbio' ) 
     
    13831382      END DO 
    13841383 
    1385 #if defined key_lobster 
    1386       DO jl = 1, jp_lobster_trd 
     1384#if defined key_pisces_reduced 
     1385      DO jl = 1, jp_pisces_trd 
    13871386         CALL histdef(nidtrdbio, TRIM("ML_"//ctrd_bio(jl,2)), TRIM(clmxl//" ML_"//ctrd_bio(jl,1))   ,            & 
    13881387             &    cltrcu, jpi, jpj, nh_tb, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) ! IOIPSL: time mean 
     
    13951394      END DO 
    13961395 
    1397 #if defined key_lobster 
     1396#if defined key_pisces_reduced 
    13981397      !-- Leave IOIPSL/NetCDF define mode 
    13991398      CALL histend( nidtrdbio, snc4set ) 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trdmld_trc_rst.F90

    r2528 r3680  
    105105            END DO                                                     ! tracer loop 
    106106            !                                                          ! =========== 
    107 #if defined key_lobster 
    108             DO jl = 1, jp_lobster_trd 
     107#if defined key_pisces_reduced 
     108            DO jl = 1, jp_pisces_trd 
    109109               CALL iom_rstput( kt, nitrst, nummldw_trc, 'tmltrd_csum_ub_bio'//ctrd_bio(jl,2), tmltrd_csum_ub_bio(:,:,jl) ) 
    110110            ENDDO 
     
    190190         !                                                          ! =========== 
    191191 
    192 #if defined key_lobster 
    193          DO jl = 1, jp_lobster_trd 
     192#if defined key_pisces_reduced 
     193         DO jl = 1, jp_pisces_trd 
    194194            CALL iom_get( inum, jpdom_autoglo, 'tmltrd_csum_ub_bio'//ctrd_bio(jl,2), tmltrd_csum_ub_bio(:,:,jl) ) 
    195195         ENDDO 
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trdmod_trc_oce.F90

    r3320 r3680  
    106106# endif 
    107107 
    108 # if defined key_lobster 
     108# if defined key_pisces_reduced 
    109109   CHARACTER(LEN=80) :: clname_bio, ctrd_bio(jpdiabio,2) 
    110110   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  & 
     
    154154#endif 
    155155      ! 
    156 # if defined key_lobster 
     156# if defined key_pisces_reduced 
    157157      ALLOCATE( tmltrd_bio        (jpi,jpj,jpdiabio) ,     & 
    158158         &      tmltrd_sum_bio    (jpi,jpj,jpdiabio) ,     & 
Note: See TracChangeset for help on using the changeset viewer.