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 14361 – NEMO

Changeset 14361


Ignore:
Timestamp:
2021-01-29T14:52:00+01:00 (3 years ago)
Author:
mathiot
Message:

ticket #2581: correction based on Dave review (missing _wp, improve information wrote in iceberg.stat file)

Location:
NEMO/branches/2021/ticket2581_NEMO4.0-HEAD_icb_speeding_ticket/src/OCE/ICB
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/ticket2581_NEMO4.0-HEAD_icb_speeding_ticket/src/OCE/ICB/icbdia.F90

    r10570 r14361  
    8686   INTEGER                       ::  nbergs_start, nbergs_end, nbergs_calved 
    8787   INTEGER                       ::  nbergs_melted 
    88    INTEGER                       ::  nspeeding_tickets 
     88   INTEGER                       ::  nspeeding_tickets, nspeeding_tickets_all 
    8989   INTEGER , DIMENSION(nclasses) ::  nbergs_calved_by_class 
    9090 
     
    125125      nbergs_calved_by_class(:) = 0 
    126126      nspeeding_tickets         = 0 
     127      nspeeding_tickets_all     = 0 
    127128      stored_heat_end           = 0._wp 
    128129      floating_heat_end         = 0._wp 
     
    271272            CALL mpp_sum( 'icbdia', nsumbuf(1:nclasses+4), nclasses+4 ) 
    272273            ! 
    273             nbergs_end        = nsumbuf(1) 
    274             nbergs_calved     = nsumbuf(2) 
    275             nbergs_melted     = nsumbuf(3) 
    276             nspeeding_tickets = nsumbuf(4) 
     274            nbergs_end            = nsumbuf(1) 
     275            nbergs_calved         = nsumbuf(2) 
     276            nbergs_melted         = nsumbuf(3) 
     277            nspeeding_tickets_all = nsumbuf(4) 
    277278            DO ik = 1,nclasses 
    278279               nbergs_calved_by_class(ik)= nsumbuf(4+ik) 
     
    329330         IF (nn_verbose_level > 0) THEN 
    330331            WRITE( numicb, '("calved by class = ",i6,20(",",i6))') (nbergs_calved_by_class(ik),ik=1,nclasses) 
    331             IF( nspeeding_tickets > 0 )   WRITE( numicb, '("speeding tickets issued = ",i6)') nspeeding_tickets 
     332            IF( nspeeding_tickets_all > 0 ) THEN 
     333                WRITE( numicb, '("speeding tickets issued (this domain)  = ",i6)') nspeeding_tickets 
     334                WRITE( numicb, '("speeding tickets issued (all domains)  = ",i6)') nspeeding_tickets_all 
     335            END IF 
    332336         ENDIF 
    333337         ! 
     
    338342         nbergs_calved_by_class(:) = 0 
    339343         nspeeding_tickets         = 0 
     344         nspeeding_tickets_all     = 0 
    340345         stored_heat_start         = stored_heat_end 
    341346         floating_heat_start       = floating_heat_end 
  • NEMO/branches/2021/ticket2581_NEMO4.0-HEAD_icb_speeding_ticket/src/OCE/ICB/icbdyn.F90

    r14360 r14361  
    8585 
    8686         !                                         !**   A1 = A(X1,V1) 
    87          CALL icb_accel( berg , zxi1, ze1, zuvel1, zuvel1, zax1,     & 
    88             &                   zyj1, ze2, zvvel1, zvvel1, zay1, zdt_2, 1./2. ) 
     87         CALL icb_accel( kt, berg , zxi1, ze1, zuvel1, zuvel1, zax1,     & 
     88            &                   zyj1, ze2, zvvel1, zvvel1, zay1, zdt_2, 0.5_wp ) 
    8989         ! 
    9090         zu1 = zuvel1 / ze1                           !**   V1 in d(i,j)/dt 
     
    102102 
    103103         !                                         !**   A2 = A(X2,V2) 
    104          CALL icb_accel( berg , zxi2, ze1, zuvel2, zuvel1, zax2,    & 
    105             &                   zyj2, ze2, zvvel2, zvvel1, zay2, zdt_2, 1./2. ) 
     104         CALL icb_accel( kt, berg , zxi2, ze1, zuvel2, zuvel1, zax2,    & 
     105            &                   zyj2, ze2, zvvel2, zvvel1, zay2, zdt_2, 0.5_wp ) 
    106106         ! 
    107107         zu2 = zuvel2 / ze1                           !**   V2 in d(i,j)/dt 
     
    118118 
    119119         !                                         !**   A3 = A(X3,V3) 
    120          CALL icb_accel( berg , zxi3, ze1, zuvel3, zuvel1, zax3,    & 
    121             &                   zyj3, ze2, zvvel3, zvvel1, zay3, zdt, 1. ) 
     120         CALL icb_accel( kt, berg , zxi3, ze1, zuvel3, zuvel1, zax3,    & 
     121            &                   zyj3, ze2, zvvel3, zvvel1, zay3, zdt, 1._wp ) 
    122122         ! 
    123123         zu3 = zuvel3 / ze1                           !**   V3 in d(i,j)/dt 
     
    134134 
    135135         !                                         !**   A4 = A(X4,V4) 
    136          CALL icb_accel( berg , zxi4, ze1, zuvel4, zuvel1, zax4,    & 
    137             &                   zyj4, ze2, zvvel4, zvvel1, zay4, zdt, 1. ) 
     136         CALL icb_accel( kt, berg , zxi4, ze1, zuvel4, zuvel1, zax4,    & 
     137            &                   zyj4, ze2, zvvel4, zvvel1, zay4, zdt, 1._wp ) 
    138138 
    139139         zu4 = zuvel4 / ze1                           !**   V4 in d(i,j)/dt 
     
    235235 
    236236 
    237    SUBROUTINE icb_accel( berg , pxi, pe1, puvel, puvel0, pax,                & 
    238       &                         pyj, pe2, pvvel, pvvel0, pay, pdt, pcfl_scale ) 
     237   SUBROUTINE icb_accel( kt, berg , pxi, pe1, puvel, puvel0, pax,                 & 
     238      &                             pyj, pe2, pvvel, pvvel0, pay, pdt, pcfl_scale ) 
    239239      !!---------------------------------------------------------------------- 
    240240      !!                  ***  ROUTINE icb_accel  *** 
     
    245245      !!---------------------------------------------------------------------- 
    246246      TYPE(iceberg ), POINTER, INTENT(in   ) ::   berg             ! berg 
     247      INTEGER                , INTENT(in   ) ::   kt               ! time step 
    247248      REAL(wp)               , INTENT(in   ) ::   pcfl_scale 
    248249      REAL(wp)               , INTENT(in   ) ::   pxi   , pyj      ! berg position in (i,j) referential 
     
    371372               pax = (zuveln - puvel0)/pdt 
    372373               pay = (zvveln - pvvel0)/pdt 
    373                WRITE(numout,*) 'speeding ticket (zspeed_new, zspeed): ',zspeed_new, zspeed, pdt, pcfl_scale    
    374                CALL FLUSH(numout) 
     374               ! 
     375               ! print speeding ticket 
     376               IF (nn_verbose_level > 0) THEN 
     377                  WRITE(numicb, 9200) 'icb speeding : ',kt, nknberg, zspeed, & 
     378                       &                pxi, pyj, zuo, zvo, zua, zva, zui, zvi 
     379                  9200 FORMAT(a,i9,i6,f9.2,1x,4(1x,2f9.2)) 
     380               END IF 
     381               ! 
    375382               CALL icb_dia_speed() 
    376383            ENDIF 
  • NEMO/branches/2021/ticket2581_NEMO4.0-HEAD_icb_speeding_ticket/src/OCE/ICB/icbutl.F90

    r13263 r14361  
    428428      IF( ij == jpj ) THEN ; ij = ij-1 ; ierr = ierr + 1 ; END IF 
    429429      ! 
    430       IF ( ierr > 0 ) CALL ctl_stop('STOP','icb_utl_bilin_e: an icebergs coordinates is out of valid range (out of bound error)') 
     430      IF ( ierr > 0 ) THEN 
     431          CALL FLUSH(numicb) 
     432          CALL ctl_stop('STOP','icb_utl_bilin_e: an icebergs coordinates is out of valid range (out of bound error).'       , & 
     433               &                                'This can be fixed using rn_speed_limit=0.4 in &namberg.'                   , & 
     434               &                                'More details in the corresponding iceberg.stat file (nn_verbose_level > 0).' ) 
     435      END IF 
    431436      ! 
    432437      IF(    0.0_wp <= zi .AND. zi < 0.5_wp   ) THEN 
Note: See TracChangeset for help on using the changeset viewer.