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 10946 for NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP – NEMO

Ignore:
Timestamp:
2019-05-08T10:56:14+02:00 (5 years ago)
Author:
acc
Message:

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Convert STO, TRD and USR modules and all knock on effects of these conversions. Note change to USR module may have implications for the TEST CASES (not tested yet). Standard SETTE tested only

Location:
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcadv.F90

    r10922 r10946  
    116116         ! 
    117117         IF( ln_ldfeiv .AND. .NOT. ln_traldf_triad )   &  
    118             &              CALL ldf_eiv_trp( kt, nittrc000, zun, zvn, zwn, 'TRC', Kmm )  ! add the eiv transport 
     118            &              CALL ldf_eiv_trp( kt, nittrc000, zun, zvn, zwn, 'TRC', Kmm, Krhs )  ! add the eiv transport 
    119119         ! 
    120120         IF( ln_mle    )   CALL tra_mle_trp( kt, nittrc000, zun, zvn, zwn, 'TRC' )  ! add the mle transport 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcbbl.F90

    r10068 r10946  
    3636CONTAINS 
    3737 
    38    SUBROUTINE trc_bbl( kt ) 
     38   SUBROUTINE trc_bbl( kt, Kmm, Krhs ) 
    3939      !!---------------------------------------------------------------------- 
    4040      !!                  ***  ROUTINE bbl  *** 
     
    4646      !!----------------------------------------------------------------------   
    4747      INTEGER, INTENT( in ) ::   kt   ! ocean time-step  
     48      INTEGER, INTENT( in ) ::   Kmm, Krhs  ! time level indices 
    4849      INTEGER :: jn                   ! loop index 
    4950      CHARACTER (len=22) :: charout 
     
    8889        DO jn = 1, jptra 
    8990           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn) 
    90            CALL trd_tra( kt, 'TRC', jn, jptra_bbl, ztrtrd(:,:,:,jn) ) 
     91           CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_bbl, ztrtrd(:,:,:,jn) ) 
    9192        END DO 
    9293        DEALLOCATE( ztrtrd ) ! temporary save of trends 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcdmp.F90

    r10351 r10946  
    6363 
    6464 
    65    SUBROUTINE trc_dmp( kt ) 
     65   SUBROUTINE trc_dmp( kt, Kmm, Krhs ) 
    6666      !!---------------------------------------------------------------------- 
    6767      !!                   ***  ROUTINE trc_dmp  *** 
     
    8383      !!---------------------------------------------------------------------- 
    8484      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     85      INTEGER, INTENT(in) ::   Kmm, Krhs  ! time level indices 
    8586      ! 
    8687      INTEGER ::   ji, jj, jk, jn, jl   ! dummy loop indices 
     
    146147            IF( l_trdtrc ) THEN 
    147148               ztrtrd(:,:,:) = tra(:,:,:,jn) -  ztrtrd(:,:,:) 
    148                CALL trd_tra( kt, 'TRC', jn, jptra_dmp, ztrtrd ) 
     149               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_dmp, ztrtrd ) 
    149150            END IF 
    150151            !                                                       ! =========== 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcldf.F90

    r10922 r10946  
    5151CONTAINS 
    5252 
    53    SUBROUTINE trc_ldf( kt, Kmm ) 
     53   SUBROUTINE trc_ldf( kt, Kmm, Krhs ) 
    5454      !!---------------------------------------------------------------------- 
    5555      !!                  ***  ROUTINE tra_ldf  *** 
     
    5959      !!---------------------------------------------------------------------- 
    6060      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    61       INTEGER, INTENT( in ) ::   Kmm  ! ocean time-level index 
     61      INTEGER, INTENT( in ) ::   Kmm, Krhs  ! ocean time-level index 
    6262      ! 
    6363      INTEGER            :: ji, jj, jk, jn 
     
    106106        DO jn = 1, jptra 
    107107           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn) 
    108            CALL trd_tra( kt, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) ) 
     108           CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) ) 
    109109        END DO 
    110110        DEALLOCATE( ztrtrd ) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcnxt.F90

    r10425 r10946  
    5454CONTAINS 
    5555 
    56    SUBROUTINE trc_nxt( kt ) 
     56   SUBROUTINE trc_nxt( kt, Kmm, Krhs ) 
    5757      !!---------------------------------------------------------------------- 
    5858      !!                   ***  ROUTINE trcnxt  *** 
     
    7979      !!---------------------------------------------------------------------- 
    8080      INTEGER, INTENT( in ) ::   kt     ! ocean time-step index 
     81      INTEGER, INTENT( in ) ::   Kmm, Krhs  ! time level indices 
    8182      ! 
    8283      INTEGER  ::   jk, jn   ! dummy loop indices 
     
    106107         IF( ln_traldf_iso ) THEN                       ! diagnose the "pure" Kz diffusive trend  
    107108            DO jn = 1, jptra 
    108                CALL trd_tra( kt, 'TRC', jn, jptra_zdfp, ztrdt(:,:,:,jn) ) 
     109               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_zdfp, ztrdt(:,:,:,jn) ) 
    109110            ENDDO 
    110111         ENDIF 
     
    128129         ! 
    129130         DO jn = 1, jptra 
    130             CALL trd_tra( kt, 'TRC', jn, jptra_tot, ztrdt(:,:,:,jn) ) 
     131            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_tot, ztrdt(:,:,:,jn) ) 
    131132         ENDDO 
    132133         ! 
     
    150151            ztrdt(:,:,:,:) = 0._wp             
    151152            DO jn = 1, jptra 
    152                CALL trd_tra( kt, 'TRC', jn, jptra_atf, ztrdt(:,:,:,jn) ) 
     153               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_atf, ztrdt(:,:,:,jn) ) 
    153154            ENDDO 
    154155         END IF 
     
    157158         IF( .NOT. l_offline ) THEN ! Leap-Frog + Asselin filter time stepping 
    158159            IF( ln_linssh ) THEN   ;   CALL tra_nxt_fix( kt, nittrc000,         'TRC', trb, trn, tra, jptra )  !     linear ssh 
    159             ELSE                   ;   CALL tra_nxt_vvl( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
     160            ELSE                   ;   CALL tra_nxt_vvl( kt, Kmm, Krhs, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
    160161              &                                                                   sbc_trc, sbc_trc_b, jptra )  ! non-linear ssh 
    161162            ENDIF 
     
    173174               ztrdt(:,:,jk,jn) = ( trb(:,:,jk,jn) - ztrdt(:,:,jk,jn) ) * zfact  
    174175            END DO 
    175             CALL trd_tra( kt, 'TRC', jn, jptra_atf, ztrdt(:,:,:,jn) ) 
     176            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_atf, ztrdt(:,:,:,jn) ) 
    176177         END DO 
    177178      END IF 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcrad.F90

    r10425 r10946  
    3737CONTAINS 
    3838 
    39    SUBROUTINE trc_rad( kt ) 
     39   SUBROUTINE trc_rad( kt, Kmm, Krhs ) 
    4040      !!---------------------------------------------------------------------- 
    4141      !!                  ***  ROUTINE trc_rad  *** 
     
    5353      !!---------------------------------------------------------------------- 
    5454      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     55      INTEGER, INTENT(in) ::   Kmm, Krhs  ! time level indices 
    5556      ! 
    5657      CHARACTER (len=22) :: charout 
     
    5960      IF( ln_timing )   CALL timing_start('trc_rad') 
    6061      ! 
    61       IF( ln_age     )   CALL trc_rad_sms( kt, trb, trn, jp_age , jp_age                )  !  AGE 
    62       IF( ll_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0, jp_cfc1               )  !  CFC model 
    63       IF( ln_c14     )   CALL trc_rad_sms( kt, trb, trn, jp_c14 , jp_c14                )  !  C14 
    64       IF( ln_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model 
    65       IF( ln_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0, jp_myt1               )  !  MY_TRC model 
     62      IF( ln_age     )   CALL trc_rad_sms( kt, Kmm, Krhs, trb, trn, jp_age , jp_age                )  !  AGE 
     63      IF( ll_cfc     )   CALL trc_rad_sms( kt, Kmm, Krhs, trb, trn, jp_cfc0, jp_cfc1               )  !  CFC model 
     64      IF( ln_c14     )   CALL trc_rad_sms( kt, Kmm, Krhs, trb, trn, jp_c14 , jp_c14                )  !  C14 
     65      IF( ln_pisces  )   CALL trc_rad_sms( kt, Kmm, Krhs, trb, trn, jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model 
     66      IF( ln_my_trc  )   CALL trc_rad_sms( kt, Kmm, Krhs, trb, trn, jp_myt0, jp_myt1               )  !  MY_TRC model 
    6667      ! 
    6768      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     
    113114 
    114115 
    115    SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv ) 
     116   SUBROUTINE trc_rad_sms( kt, Kmm, Krhs, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv ) 
    116117      !!----------------------------------------------------------------------------- 
    117118      !!                  ***  ROUTINE trc_rad_sms  *** 
     
    130131      !!-------------------------------------------------------------------------------- 
    131132      INTEGER                                , INTENT(in   ) ::   kt                 ! ocean time-step index 
     133      INTEGER                                , INTENT(in   ) ::   Kmm, Krhs          ! time level indices 
    132134      INTEGER                                , INTENT(in   ) ::   jp_sms0, jp_sms1   ! First & last index of the passive tracer model 
    133135      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT(inout) ::   ptrb    , ptrn     ! before and now traceur concentration 
     
    183185            IF( l_trdtrc ) THEN 
    184186               ztrtrd(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt 
    185                CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrd )       ! Asselin-like trend handling 
     187               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_radb, ztrtrd )       ! Asselin-like trend handling 
    186188            ENDIF 
    187189            ! 
     
    233235            IF( l_trdtrc ) THEN 
    234236               ztrtrd(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt 
    235                CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrd )       ! standard     trend handling 
     237               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_radn, ztrtrd )       ! standard     trend handling 
    236238            ENDIF 
    237239            ! 
     
    261263            IF( l_trdtrc ) THEN 
    262264               ztrtrd(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt 
    263                CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrd )       ! Asselin-like trend handling 
     265               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_radb, ztrtrd )       ! Asselin-like trend handling 
    264266            ENDIF 
    265267            ! 
     
    270272            IF( l_trdtrc ) THEN 
    271273               ztrtrd(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt 
    272                CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrd )       ! standard     trend handling 
     274               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_radn, ztrtrd )       ! standard     trend handling 
    273275            ENDIF 
    274276            ! 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcsbc.F90

    r10425 r10946  
    3737CONTAINS 
    3838 
    39    SUBROUTINE trc_sbc ( kt ) 
     39   SUBROUTINE trc_sbc ( kt, Kmm, Krhs ) 
    4040      !!---------------------------------------------------------------------- 
    4141      !!                  ***  ROUTINE trc_sbc  *** 
     
    5959      !!---------------------------------------------------------------------- 
    6060      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     61      INTEGER, INTENT(in) ::   Kmm, Krhs  ! time level indices 
    6162      ! 
    6263      INTEGER  ::   ji, jj, jn                      ! dummy loop indices 
     
    163164         IF( l_trdtrc ) THEN 
    164165            ztrtrd(:,:,:) = tra(:,:,:,jn) - ztrtrd(:,:,:) 
    165             CALL trd_tra( kt, 'TRC', jn, jptra_nsr, ztrtrd ) 
     166            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_nsr, ztrtrd ) 
    166167         END IF 
    167168         !                                                       ! =========== 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trctrp.F90

    r10922 r10946  
    6161      IF( .NOT. lk_c1d ) THEN 
    6262         ! 
    63                                 CALL trc_sbc    ( kt )      ! surface boundary condition 
    64          IF( ln_trabbl )        CALL trc_bbl    ( kt )      ! advective (and/or diffusive) bottom boundary layer scheme 
    65          IF( ln_trcdmp )        CALL trc_dmp    ( kt )      ! internal damping trends 
    66          IF( ln_bdy )           CALL trc_bdy_dmp( kt )      ! BDY damping trends 
     63                                CALL trc_sbc    ( kt, Kmm, Krhs )      ! surface boundary condition 
     64         IF( ln_trabbl )        CALL trc_bbl    ( kt, Kmm, Krhs )      ! advective (and/or diffusive) bottom boundary layer scheme 
     65         IF( ln_trcdmp )        CALL trc_dmp    ( kt, Kmm, Krhs )      ! internal damping trends 
     66         IF( ln_bdy )           CALL trc_bdy_dmp( kt )                 ! BDY damping trends 
    6767                                CALL trc_adv    ( kt, Kbb, Kmm, tr, Krhs )      ! horizontal & vertical advection  
    68          !                                                         ! Partial top/bottom cell: GRADh( trb )   
     68         !                                                             ! Partial top/bottom cell: GRADh( trb )   
    6969         IF( ln_zps ) THEN 
    7070           IF( ln_isfcav ) THEN ; CALL zps_hde_isf( kt, jptra, trb, pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi )  ! both top & bottom 
     
    7373         ENDIF 
    7474         !                                                       
    75                                 CALL trc_ldf    ( kt, Kmm ) ! lateral mixing 
     75                                CALL trc_ldf    ( kt, Kmm, Krhs ) ! lateral mixing 
    7676#if defined key_agrif 
    7777         IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_trc       ! tracers sponge 
    7878#endif 
    7979                                CALL trc_zdf( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer ==> after 
    80                                 CALL trc_nxt    ( kt )      ! tracer fields at next time step      
    81          IF( ln_trcrad )        CALL trc_rad    ( kt )      ! Correct artificial negative concentrations 
    82          IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kt )      ! internal damping trends on closed seas only 
     80                                CALL trc_nxt    ( kt, Kmm, Krhs )        ! tracer fields at next time step      
     81         IF( ln_trcrad )        CALL trc_rad    ( kt, Kmm, Krhs )        ! Correct artificial negative concentrations 
     82         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kt )                   ! internal damping trends on closed seas only 
    8383 
    8484         ! 
    8585      ELSE                                               ! 1D vertical configuration 
    86                                 CALL trc_sbc( kt )            ! surface boundary condition 
    87          IF( ln_trcdmp )        CALL trc_dmp( kt )            ! internal damping trends 
     86                                CALL trc_sbc( kt, Kmm, Krhs )            ! surface boundary condition 
     87         IF( ln_trcdmp )        CALL trc_dmp( kt, Kmm, Krhs )            ! internal damping trends 
    8888                                CALL trc_zdf( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer ==> after 
    89                                 CALL trc_nxt( kt )            ! tracer fields at next time step      
    90           IF( ln_trcrad )       CALL trc_rad( kt )            ! Correct artificial negative concentrations 
     89                                CALL trc_nxt( kt, Kmm, Krhs )            ! tracer fields at next time step      
     90          IF( ln_trcrad )       CALL trc_rad( kt, Kmm, Krhs )            ! Correct artificial negative concentrations 
    9191         ! 
    9292      END IF 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trczdf.F90

    r10893 r10946  
    6363               ztrtrd(:,:,jk,jn) = ( ( ptr(:,:,jk,jn,Kaa) - ptr(:,:,jk,jn,Kbb) ) / r2dttrc ) - ztrtrd(:,:,jk,jn) 
    6464            END DO 
    65             CALL trd_tra( kt, 'TRC', jn, jptra_zdf, ztrtrd(:,:,:,jn) ) 
     65            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_zdf, ztrtrd(:,:,:,jn) ) 
    6666         END DO 
    6767      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.