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 6442 for branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

Ignore:
Timestamp:
2016-04-07T16:38:54+02:00 (8 years ago)
Author:
dancopsey
Message:

Merged in v3_6_extra_CMIP6_diagnostics up to revision 6433.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/NEMO/OPA_SRC/DIA/diaptr.F90

    r6439 r6442  
    3838   PUBLIC   dia_ptr_init   ! call in step module 
    3939   PUBLIC   dia_ptr        ! call in step module 
     40   PUBLIC   dia_ptr_ohst_components        ! called from tra_ldf/tra_adv routines 
    4041 
    4142   !                                  !!** namelist  namptr  ** 
    42    REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:) ::   htr_adv, htr_ldf   !: Heat TRansports (adv, diff, overturn.) 
    43    REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:) ::   str_adv, str_ldf   !: Salt TRansports (adv, diff, overturn.) 
     43   REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) ::   htr_adv, htr_ldf   !: Heat TRansports (adv, diff, overturn.) 
     44   REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) ::   str_adv, str_ldf   !: Salt TRansports (adv, diff, overturn.) 
    4445    
    4546 
    4647   LOGICAL, PUBLIC ::   ln_diaptr   !  Poleward transport flag (T) or not (F) 
    4748   LOGICAL, PUBLIC ::   ln_subbas   !  Atlantic/Pacific/Indian basins calculation 
    48    INTEGER        ::   nptr        ! = 1 (l_subbas=F) or = 5 (glo, atl, pac, ind, ipc) (l_subbas=T)  
     49   INTEGER, PUBLIC ::   nptr        ! = 1 (l_subbas=F) or = 5 (glo, atl, pac, ind, ipc) (l_subbas=T)  
    4950 
    5051   REAL(wp) ::   rc_sv    = 1.e-6_wp   ! conversion from m3/s to Sverdrup 
     
    8283      REAL(wp), DIMENSION(jpi,jpj,jpk) ::  zmask   ! 3D workspace 
    8384      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts) ::  zts   ! 3D workspace 
    84       CHARACTER( len = 10 )  :: cl1 
     85      CHARACTER( len = 12 )  :: cl1 
    8586      !!---------------------------------------------------------------------- 
    8687      ! 
     
    150151         !                                ! Advective and diffusive heat and salt transport 
    151152         IF( iom_use("sophtadv") .OR. iom_use("sopstadv") ) THEN    
    152             z2d(1,:) = htr_adv(:) * rc_pwatt        !  (conversion in PW) 
     153            z2d(1,:) = htr_adv(:,1) * rc_pwatt        !  (conversion in PW) 
    153154            DO ji = 1, jpi 
    154155               z2d(ji,:) = z2d(1,:) 
     
    156157            cl1 = 'sophtadv'                  
    157158            CALL iom_put( TRIM(cl1), z2d ) 
    158             z2d(1,:) = str_adv(:) * rc_ggram        ! (conversion in Gg) 
     159            z2d(1,:) = str_adv(:,1) * rc_ggram        ! (conversion in Gg) 
    159160            DO ji = 1, jpi 
    160161               z2d(ji,:) = z2d(1,:) 
     
    162163            cl1 = 'sopstadv' 
    163164            CALL iom_put( TRIM(cl1), z2d ) 
     165            IF( ln_subbas ) THEN 
     166              DO jn=2,nptr 
     167               z2d(1,:) = htr_adv(:,jn) * rc_pwatt        !  (conversion in PW) 
     168               DO ji = 1, jpi 
     169                 z2d(ji,:) = z2d(1,:) 
     170               ENDDO 
     171               cl1 = TRIM('sophtadv_'//clsubb(jn))                  
     172               CALL iom_put( cl1, z2d ) 
     173               z2d(1,:) = str_adv(:,jn) * rc_ggram        ! (conversion in Gg) 
     174               DO ji = 1, jpi 
     175                  z2d(ji,:) = z2d(1,:) 
     176               ENDDO 
     177               cl1 = TRIM('sopstadv_'//clsubb(jn))                  
     178               CALL iom_put( cl1, z2d )               
     179              ENDDO 
     180            ENDIF 
    164181         ENDIF 
    165182         ! 
    166183         IF( iom_use("sophtldf") .OR. iom_use("sopstldf") ) THEN    
    167             z2d(1,:) = htr_ldf(:) * rc_pwatt        !  (conversion in PW)  
     184            z2d(1,:) = htr_ldf(:,1) * rc_pwatt        !  (conversion in PW)  
    168185            DO ji = 1, jpi 
    169186               z2d(ji,:) = z2d(1,:) 
     
    171188            cl1 = 'sophtldf' 
    172189            CALL iom_put( TRIM(cl1), z2d ) 
    173             z2d(1,:) = str_ldf(:) * rc_ggram        !  (conversion in Gg) 
     190            z2d(1,:) = str_ldf(:,1) * rc_ggram        !  (conversion in Gg) 
    174191            DO ji = 1, jpi 
    175192               z2d(ji,:) = z2d(1,:) 
     
    177194            cl1 = 'sopstldf' 
    178195            CALL iom_put( TRIM(cl1), z2d ) 
     196            IF( ln_subbas ) THEN 
     197              DO jn=2,nptr 
     198               z2d(1,:) = htr_ldf(:,jn) * rc_pwatt        !  (conversion in PW) 
     199               DO ji = 1, jpi 
     200                 z2d(ji,:) = z2d(1,:) 
     201               ENDDO 
     202               cl1 = TRIM('sophtldf_'//clsubb(jn))                  
     203               CALL iom_put( cl1, z2d ) 
     204               z2d(1,:) = str_ldf(:,jn) * rc_ggram        ! (conversion in Gg) 
     205               DO ji = 1, jpi 
     206                  z2d(ji,:) = z2d(1,:) 
     207               ENDDO 
     208               cl1 = TRIM('sopstldf_'//clsubb(jn))                  
     209               CALL iom_put( cl1, z2d )               
     210              ENDDO 
     211            ENDIF 
     212 
    179213         ENDIF 
    180214         ! 
     
    256290         ! Initialise arrays to zero because diatpr is called before they are first calculated 
    257291         ! Note that this means diagnostics will not be exactly correct when model run is restarted. 
    258          htr_adv(:) = 0._wp  ;  str_adv(:) =  0._wp   
    259          htr_ldf(:) = 0._wp  ;  str_ldf(:) =  0._wp  
     292         htr_adv(:,:) = 0._wp  ;  str_adv(:,:) =  0._wp   
     293         htr_ldf(:,:) = 0._wp  ;  str_ldf(:,:) =  0._wp  
    260294         ! 
    261295      ENDIF  
     
    263297   END SUBROUTINE dia_ptr_init 
    264298 
     299   SUBROUTINE dia_ptr_ohst_components( ktra, cptr, pva )  
     300      !!---------------------------------------------------------------------- 
     301      !!                    ***  ROUTINE dia_ptr_ohst_components  *** 
     302      !!---------------------------------------------------------------------- 
     303      !! Wrapper for heat and salt transport calculations to calculate them for each basin 
     304      !! Called from all advection and/or diffusion routines 
     305      !!---------------------------------------------------------------------- 
     306      INTEGER                         , INTENT(in )  :: ktra  ! tracer index 
     307      CHARACTER(len=3)                , INTENT(in)   :: cptr  ! transport type  'adv'/'ldf' 
     308      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in)   :: pva   ! 3D input array of advection/diffusion 
     309      INTEGER                                        :: jn    ! 
     310 
     311       
     312      IF( cptr == 'adv' ) THEN 
     313         IF( ktra == jp_tem )  htr_adv(:,1) = ptr_sj( pva(:,:,:) ) 
     314         IF( ktra == jp_sal )  str_adv(:,1) = ptr_sj( pva(:,:,:) ) 
     315      ENDIF 
     316      IF( cptr == 'ldf' ) THEN 
     317         IF( ktra == jp_tem )  htr_ldf(:,1) = ptr_sj( pva(:,:,:) ) 
     318         IF( ktra == jp_sal )  str_ldf(:,1) = ptr_sj( pva(:,:,:) ) 
     319      ENDIF 
     320      ! 
     321      IF( ln_subbas ) THEN 
     322         ! 
     323         IF( cptr == 'adv' ) THEN 
     324             IF( ktra == jp_tem ) THEN  
     325                DO jn = 2, nptr 
     326                   htr_adv(:,jn) = ptr_sj( pva(:,:,:), btmsk(:,:,jn) ) 
     327                END DO 
     328             ENDIF 
     329             IF( ktra == jp_sal ) THEN  
     330                DO jn = 2, nptr 
     331                   str_adv(:,jn) = ptr_sj( pva(:,:,:), btmsk(:,:,jn) ) 
     332                END DO 
     333             ENDIF 
     334         ENDIF 
     335         IF( cptr == 'ldf' ) THEN 
     336             IF( ktra == jp_tem ) THEN  
     337                DO jn = 2, nptr 
     338                    htr_ldf(:,jn) = ptr_sj( pva(:,:,:), btmsk(:,:,jn) ) 
     339                 END DO 
     340             ENDIF 
     341             IF( ktra == jp_sal ) THEN  
     342                DO jn = 2, nptr 
     343                   str_ldf(:,jn) = ptr_sj( pva(:,:,:), btmsk(:,:,jn) ) 
     344                END DO 
     345             ENDIF 
     346         ENDIF 
     347         ! 
     348      ENDIF 
     349 
     350   END SUBROUTINE 
     351 
    265352 
    266353   FUNCTION dia_ptr_alloc() 
     
    274361      ! 
    275362      ALLOCATE( btmsk(jpi,jpj,nptr) ,           & 
    276          &      htr_adv(jpj) , str_adv(jpj) ,   & 
    277          &      htr_ldf(jpj) , str_ldf(jpj) , STAT=ierr(1)  ) 
     363         &      htr_adv(jpj,nptr) , str_adv(jpj,nptr) ,   & 
     364         &      htr_ldf(jpj,nptr) , str_ldf(jpj,nptr) , STAT=ierr(1)  ) 
    278365         ! 
    279366      ALLOCATE( p_fval1d(jpj), p_fval2d(jpj,jpk), Stat=ierr(2)) 
Note: See TracChangeset for help on using the changeset viewer.