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 14789 for NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/OCE/TRA/tranpc.F90 – NEMO

Ignore:
Timestamp:
2021-05-05T13:18:04+02:00 (3 years ago)
Author:
mcastril
Message:

[2021/HPC-11_mcastril_HPDAonline_DiagGPU] Update externals

Location:
NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
         5^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8^/vendors/PPR@HEAD            ext/PPR 
        89 
        910# SETTE 
        10 ^/utils/CI/sette@13559        sette 
         11^/utils/CI/sette@14244        sette 
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/OCE/TRA/tranpc.F90

    r13497 r14789  
    1717   USE oce            ! ocean dynamics and active tracers 
    1818   USE dom_oce        ! ocean space and time domain 
     19   ! TEMP: [tiling] This change not necessary after extra haloes development (lbc_lnk removed) 
     20   USE domtile 
    1921   USE phycst         ! physical constants 
    2022   USE zdf_oce        ! ocean vertical physics 
     
    3234 
    3335   PUBLIC   tra_npc    ! routine called by step.F90 
     36 
     37   INTEGER  ::   nnpcc        ! number of statically instable water column 
    3438 
    3539   !! * Substitutions 
     
    6468      ! 
    6569      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
    66       INTEGER  ::   inpcc        ! number of statically instable water column 
    6770      INTEGER  ::   jiter, ikbot, ikp, ikup, ikdown, ilayer, ik_low   ! local integers 
    6871      LOGICAL  ::   l_bottom_reached, l_column_treated 
     
    7073      REAL(wp) ::   zsa, zbeta, zsum_sali, zsum_beta, zbw, zrw, z1_rDt 
    7174      REAL(wp), PARAMETER ::   zn2_zero = 1.e-14_wp             ! acceptance criteria for neutrality (N2==0) 
    72       REAL(wp), DIMENSION(        jpk     )   ::   zvn2         ! vertical profile of N2 at 1 given point... 
    73       REAL(wp), DIMENSION(        jpk,jpts)   ::   zvts, zvab   ! vertical profile of T & S , and  alpha & betaat 1 given point 
    74       REAL(wp), DIMENSION(jpi,jpj,jpk     )   ::   zn2          ! N^2  
    75       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts)   ::   zab          ! alpha and beta 
     75      REAL(wp), DIMENSION(    jpk     )   ::   zvn2             ! vertical profile of N2 at 1 given point... 
     76      REAL(wp), DIMENSION(    jpk,jpts)   ::   zvts, zvab       ! vertical profile of T & S , and  alpha & betaat 1 given point 
     77      REAL(wp), DIMENSION(A2D(nn_hls),jpk     )   ::   zn2              ! N^2 
     78      REAL(wp), DIMENSION(A2D(nn_hls),jpk,jpts)   ::   zab              ! alpha and beta 
    7679      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds ! 3D workspace 
    7780      ! 
    7881      LOGICAL, PARAMETER :: l_LB_debug = .FALSE. ! set to true if you want to follow what is 
    7982      INTEGER :: ilc1, jlc1, klc1, nncpu         ! actually happening in a water column at point "ilc1, jlc1" 
     83      INTEGER :: isi, isj, iei, iej 
    8084      LOGICAL :: lp_monitor_point = .FALSE.      ! in CPU domain "nncpu" 
    8185      !!---------------------------------------------------------------------- 
     
    8791         IF( l_trdtra )   THEN                    !* Save initial after fields 
    8892            ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
    89             ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kaa)  
     93            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kaa) 
    9094            ztrds(:,:,:) = pts(:,:,:,jp_sal,Kaa) 
    9195         ENDIF 
     
    9397         IF( l_LB_debug ) THEN 
    9498            ! Location of 1 known convection site to follow what's happening in the water column 
    95             ilc1 = 45 ;  jlc1 = 3 ; !  ORCA2 4x4, Antarctic coast, more than 2 unstable portions in the  water column...            
     99            ilc1 = 45 ;  jlc1 = 3 ; !  ORCA2 4x4, Antarctic coast, more than 2 unstable portions in the  water column... 
    96100            nncpu = 1  ;            ! the CPU domain contains the convection spot 
    97             klc1 =  mbkt(ilc1,jlc1) ! bottom of the ocean for debug point...           
     101            klc1 =  mbkt(ilc1,jlc1) ! bottom of the ocean for debug point... 
    98102         ENDIF 
    99103         ! 
     
    101105         CALL bn2    ( pts(:,:,:,:,Kaa), zab, zn2, Kmm )    ! after Brunt-Vaisala  (given on W-points) 
    102106         ! 
    103          inpcc = 0 
    104          ! 
    105          DO_2D( 0, 0, 0, 0 )                                ! interior column only 
     107         IF( ntile == 0 .OR. ntile == 1 ) nnpcc = 0         ! Do only on the first tile 
     108         ! 
     109         IF( ntsi == Nis0 ) THEN ; isi = nn_hls ; ELSE ; isi = 0 ; ENDIF    ! Avoid double-counting when using tiling 
     110         IF( ntsj == Njs0 ) THEN ; isj = nn_hls ; ELSE ; isj = 0 ; ENDIF 
     111         IF( ntei == Nie0 ) THEN ; iei = nn_hls ; ELSE ; iei = 0 ; ENDIF 
     112         IF( ntej == Nje0 ) THEN ; iej = nn_hls ; ELSE ; iej = 0 ; ENDIF 
     113         ! 
     114         DO_2D( isi, iei, isj, iej )                        ! interior column only 
    106115            ! 
    107116            IF( tmask(ji,jj,2) == 1 ) THEN      ! At least 2 ocean points 
    108                !                                     ! consider one ocean column  
     117               !                                     ! consider one ocean column 
    109118               zvts(:,jp_tem) = pts(ji,jj,:,jp_tem,Kaa)      ! temperature 
    110119               zvts(:,jp_sal) = pts(ji,jj,:,jp_sal,Kaa)      ! salinity 
    111120               ! 
    112                zvab(:,jp_tem)  = zab(ji,jj,:,jp_tem)     ! Alpha  
    113                zvab(:,jp_sal)  = zab(ji,jj,:,jp_sal)     ! Beta   
    114                zvn2(:)         = zn2(ji,jj,:)            ! N^2  
     121               zvab(:,jp_tem)  = zab(ji,jj,:,jp_tem)     ! Alpha 
     122               zvab(:,jp_sal)  = zab(ji,jj,:,jp_sal)     ! Beta 
     123               zvn2(:)         = zn2(ji,jj,:)            ! N^2 
    115124               ! 
    116125               IF( l_LB_debug ) THEN                  !LB debug: 
     
    118127                  IF( ( ji == ilc1 ).AND.( jj == jlc1 ) ) lp_monitor_point = .TRUE. 
    119128                  ! writing only if on CPU domain where conv region is: 
    120                   lp_monitor_point = (narea == nncpu).AND.lp_monitor_point                       
     129                  lp_monitor_point = (narea == nncpu).AND.lp_monitor_point 
    121130               ENDIF                                  !LB debug  end 
    122131               ! 
     
    130139                  ! 
    131140                  jiter = jiter + 1 
    132                   !  
     141                  ! 
    133142                  IF( jiter >= 400 ) EXIT 
    134143                  ! 
     
    145154                        ilayer = ilayer + 1    ! yet another instable portion of the water column found.... 
    146155                        ! 
    147                         IF( lp_monitor_point ) THEN  
     156                        IF( lp_monitor_point ) THEN 
    148157                           WRITE(numout,*) 
    149158                           IF( ilayer == 1 .AND. jiter == 1 ) THEN   ! first time a column is spoted with an instability 
     
    160169                        ENDIF 
    161170                        ! 
    162                         IF( jiter == 1 )   inpcc = inpcc + 1  
     171                        IF( jiter == 1 )   nnpcc = nnpcc + 1 
    163172                        ! 
    164173                        IF( lp_monitor_point )   WRITE(numout, *) 'Negative N2 at ikp =',ikp,' for layer #', ilayer 
     
    185194                        zsum_beta = 0._wp 
    186195                        zsum_z    = 0._wp 
    187                                                   
     196 
    188197                        DO jk = ikup, ikbot      ! Inside the instable (and overlying neutral) portion of the column 
    189198                           ! 
     
    194203                           zsum_beta = zsum_beta + zvab(jk,jp_sal)*zdz 
    195204                           zsum_z    = zsum_z    + zdz 
    196                            !                               
     205                           ! 
    197206                           IF( jk == ikbot ) EXIT ! avoid array-index overshoot in case ikbot = jpk, cause we're calling jk+1 next line 
    198207                           !! EXIT when we have reached the last layer that is instable (N2<0) or neutral (N2=0): 
    199208                           IF( zvn2(jk+1) > zn2_zero ) EXIT 
    200209                        END DO 
    201                         
     210 
    202211                        ikdown = jk ! for the current unstable layer, ikdown is the deepest point with a negative or neutral N2 
    203212                        IF( ikup == ikdown )   CALL ctl_stop( 'tra_npc :  PROBLEM #2') 
     
    225234                           zvab(jk,jp_sal) = zbeta 
    226235                        END DO 
    227                          
    228                          
     236 
     237 
    229238                        !! Updating N2 in the relvant portion of the water column 
    230239                        !! Temperature, Salinity, Alpha and Beta have been homogenized in the unstable portion 
    231240                        !! => Need to re-compute N2! will use Alpha and Beta! 
    232                          
     241 
    233242                        ikup   = MAX(2,ikup)         ! ikup can never be 1 ! 
    234243                        ik_low = MIN(ikdown+1,ikbot) ! we must go 1 point deeper than ikdown! 
    235                          
     244 
    236245                        DO jk = ikup, ik_low              ! we must go 1 point deeper than ikdown! 
    237246 
     
    253262 
    254263                        END DO 
    255                       
     264 
    256265                        ikp = MIN(ikdown+1,ikbot) 
    257                          
     266 
    258267 
    259268                     ENDIF  !IF( zvn2(ikp) < 0. ) 
     
    265274 
    266275                  IF( ikp /= ikbot )   CALL ctl_stop( 'tra_npc :  PROBLEM #3') 
    267                   
     276 
    268277                  ! ******* At this stage ikp == ikbot ! ******* 
    269                   
     278 
    270279                  IF( ilayer > 0 ) THEN      !! least an unstable layer has been found 
    271280                     ! 
     
    310319         ENDIF 
    311320         ! 
    312          CALL lbc_lnk_multi( 'tranpc', pts(:,:,:,jp_tem,Kaa), 'T', 1.0_wp, pts(:,:,:,jp_sal,Kaa), 'T', 1.0_wp ) 
    313          ! 
    314          IF( lwp .AND. l_LB_debug ) THEN 
    315             WRITE(numout,*) 'Exiting tra_npc , kt = ',kt,', => numb. of statically instable water-columns: ', inpcc 
    316             WRITE(numout,*) 
     321         IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
     322            IF( lwp .AND. l_LB_debug ) THEN 
     323               WRITE(numout,*) 'Exiting tra_npc , kt = ',kt,', => numb. of statically instable water-columns: ', nnpcc 
     324               WRITE(numout,*) 
     325            ENDIF 
    317326         ENDIF 
    318327         ! 
Note: See TracChangeset for help on using the changeset viewer.