Changeset 7593
- Timestamp:
- 2017-01-20T17:32:39+01:00 (8 years ago)
- Location:
- branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90
r7572 r7593 48 48 USE timing ! preformance summary 49 49 USE wrk_nemo ! working arrays 50 50 51 51 52 IMPLICIT NONE … … 66 67 !! * Shared module variables 67 68 LOGICAL, PUBLIC, PARAMETER :: lk_diadct = .TRUE. !: model-data diagnostics flag 69 LOGICAL, PUBLIC :: ln_dct_calc_noos_25h !: Calcuate noos 25 h means 70 LOGICAL, PUBLIC :: ln_dct_calc_noos_hr !: Calcuate noos hourly means 68 71 69 72 !! * Module variables … … 150 153 !! 151 154 !!--------------------------------------------------------------------- 152 NAMELIST/namdct/nn_dct,nn_dctwri,nn_secdebug 155 NAMELIST/namdct/nn_dct,nn_dctwri,nn_secdebug,ln_dct_calc_noos_25h,ln_dct_calc_noos_hr 153 156 INTEGER :: ios ! Local integer output status for namelist read 154 157 … … 175 178 nn_dct=3600./rdt ! hard coded for NOOS transects, to give 25 hour means 176 179 nn_dctwri=86400./rdt 180 177 181 nn_dct_h=1 ! hard coded for NOOS transects, to give hourly data 178 182 nn_dctwri_h=3600./rdt … … 184 188 WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~" 185 189 IF( ln_NOOS ) THEN 190 WRITE(numout,*) " Calculate NOOS hourly output: ln_dct_calc_noos_hr = ",ln_dct_calc_noos_hr 191 WRITE(numout,*) " Calculate NOOS 25 hour mean output: ln_dct_calc_noos_hr = ",ln_dct_calc_noos_25h 186 192 WRITE(numout,*) " Frequency of computation hard coded to be every hour: nn_dct = ",nn_dct 187 193 WRITE(numout,*) " Frequency of write hard coded to average 25 instantaneous hour values: nn_dctwri = ",nn_dctwri … … 213 219 IF( lwp ) THEN 214 220 IF( ln_NOOS ) THEN 215 CALL ctl_opn( numdct_NOOS ,'NOOS_transport' , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )216 CALL ctl_opn( numdct_NOOS_h,'NOOS_transport_h', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )221 if ( ln_dct_calc_noos_25h ) CALL ctl_opn( numdct_NOOS ,'NOOS_transport' , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 222 if ( ln_dct_calc_noos_hr ) CALL ctl_opn( numdct_NOOS_h,'NOOS_transport_h', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 217 223 ELSE 218 224 CALL ctl_opn( numdct_vol , 'volume_transport', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) … … 264 270 REAL(wp), POINTER, DIMENSION(:) :: zwork ! " 265 271 REAL(wp), POINTER, DIMENSION(:,:,:):: zsum ! " 266 267 268 269 272 !!--------------------------------------------------------------------- 270 273 271 274 275 276 !i_steps = 1 277 272 278 273 279 … … 296 302 WRITE(numout,*) "nb_class_max = ",nb_class_max 297 303 ENDIF 298 299 300 ! Compute transport and write only at nn_dctwri 301 IF ( MOD(kt,nn_dct)==0 .or. & ! compute transport every nn_dct time steps 302 (ln_NOOS .and. kt==nn_it000 ) ) THEN ! also include first time step when calculating NOOS 25 hour averages 303 304 DO jsec=1,nb_sec 305 306 lldebug=.FALSE. 307 IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND. kt==nit000+nn_dct-1 .AND. lwp ) lldebug=.TRUE. 308 309 !Compute transport through section 310 CALL transport(secs(jsec),lldebug,jsec) 311 312 313 ENDDO 314 315 IF( MOD(kt,nn_dctwri)==0 )THEN 316 317 IF( lwp .AND. kt==nit000+nn_dctwri-1 )WRITE(numout,*)" diadct: average and write at kt = ",kt 318 319 !! divide arrays by nn_dctwri/nn_dct to obtain average 320 transports_3d(:,:,:,:)=transports_3d(:,:,:,:)/(nn_dctwri/nn_dct) 321 transports_2d(:,:,:) =transports_2d(:,:,:) /(nn_dctwri/nn_dct) 322 323 ! Sum over each class 324 DO jsec=1,nb_sec 325 CALL dia_dct_sum(secs(jsec),jsec) 326 ENDDO 327 328 !Sum on all procs 329 IF( lk_mpp )THEN 330 zsum(:,:,:)=0.0_wp 331 ish(1) = nb_sec_max*nb_type*nb_class_max 332 ish2 = (/nb_sec_max,nb_type,nb_class_max/) 333 DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport(:,:) ; ENDDO 334 zwork(:)= RESHAPE(zsum(:,:,:), ish ) 335 CALL mpp_sum(zwork, ish(1)) 336 zsum(:,:,:)= RESHAPE(zwork,ish2) 337 DO jsec=1,nb_sec ; secs(jsec)%transport(:,:) = zsum(jsec,:,:) ; ENDDO 338 ENDIF 339 340 !Write the transport 341 DO jsec=1,nb_sec 342 343 IF( lwp .and. .not. ln_NOOS )CALL dia_dct_wri(kt,jsec,secs(jsec)) 344 IF( lwp .and. ln_NOOS )CALL dia_dct_wri_NOOS(kt,jsec,secs(jsec)) ! use NOOS specific formatting 304 305 306 IF ( ln_dct_calc_noos_25h ) THEN 307 308 ! Compute transport and write only at nn_dctwri 309 IF ( MOD(kt,nn_dct)==0 .or. & ! compute transport every nn_dct time steps 310 (ln_NOOS .and. kt==nn_it000 ) ) THEN ! also include first time step when calculating NOOS 25 hour averages 345 311 346 312 347 !nullify transports values after writing 348 transports_3d(:,jsec,:,:)=0.0 349 transports_2d(:,jsec,: )=0.0 350 secs(jsec)%transport(:,:)=0. 351 IF ( ln_NOOS ) CALL transport(secs(jsec),lldebug,jsec) ! reinitialise for next 25 hour instantaneous average (overlapping values) 352 353 ENDDO 354 355 ENDIF 356 313 314 DO jsec=1,nb_sec 315 316 lldebug=.FALSE. 317 IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND. kt==nit000+nn_dct-1 .AND. lwp ) lldebug=.TRUE. 318 319 !Compute transport through section 320 CALL transport(secs(jsec),lldebug,jsec) 321 322 323 ENDDO 324 325 IF( MOD(kt,nn_dctwri)==0 )THEN 326 327 328 329 IF( lwp .AND. kt==nit000+nn_dctwri-1 )WRITE(numout,*)" diadct: average and write at kt = ",kt 330 331 !! divide arrays by nn_dctwri/nn_dct to obtain average 332 transports_3d(:,:,:,:)=transports_3d(:,:,:,:)/(nn_dctwri/nn_dct) 333 transports_2d(:,:,:) =transports_2d(:,:,:) /(nn_dctwri/nn_dct) 334 335 ! Sum over each class 336 DO jsec=1,nb_sec 337 CALL dia_dct_sum(secs(jsec),jsec) 338 ENDDO 339 340 !Sum on all procs 341 IF( lk_mpp )THEN 342 zsum(:,:,:)=0.0_wp 343 ish(1) = nb_sec_max*nb_type*nb_class_max 344 ish2 = (/nb_sec_max,nb_type,nb_class_max/) 345 DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport(:,:) ; ENDDO 346 zwork(:)= RESHAPE(zsum(:,:,:), ish ) 347 CALL mpp_sum(zwork, ish(1)) 348 zsum(:,:,:)= RESHAPE(zwork,ish2) 349 DO jsec=1,nb_sec ; secs(jsec)%transport(:,:) = zsum(jsec,:,:) ; ENDDO 350 ENDIF 351 352 !Write the transport 353 DO jsec=1,nb_sec 354 355 IF( lwp .and. .not. ln_NOOS )CALL dia_dct_wri(kt,jsec,secs(jsec)) 356 !IF( lwp .and. ln_NOOS )CALL dia_dct_wri_NOOS(kt,jsec,secs(jsec)) ! use NOOS specific formatting 357 IF( ln_NOOS )CALL dia_dct_wri_NOOS(kt,jsec,secs(jsec)) ! use NOOS specific formatting 358 359 360 !nullify transports values after writing 361 transports_3d(:,jsec,:,:)=0.0 362 transports_2d(:,jsec,: )=0.0 363 secs(jsec)%transport(:,:)=0. 364 365 366 IF ( ln_NOOS ) CALL transport(secs(jsec),lldebug,jsec) ! reinitialise for next 25 hour instantaneous average (overlapping values) 367 368 369 370 ENDDO 371 372 ENDIF 373 374 ENDIF 375 376 ENDIF 377 IF ( ln_dct_calc_noos_hr ) THEN 378 IF ( MOD(kt,nn_dct_h)==0 ) THEN ! compute transport every nn_dct_h time steps 379 380 DO jsec=1,nb_sec 381 382 lldebug=.FALSE. 383 IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND. kt==nit000+nn_dct_h-1 .AND. lwp ) lldebug=.TRUE. 384 385 !Compute transport through section 386 CALL transport_h(secs(jsec),lldebug,jsec) 387 388 ENDDO 389 390 IF( MOD(kt,nn_dctwri_h)==0 )THEN 391 392 IF( lwp .AND. kt==nit000+nn_dctwri_h-1 )WRITE(numout,*)" diadct: average and write hourly files at kt = ",kt 393 394 !! divide arrays by nn_dctwri/nn_dct to obtain average 395 transports_3d_h(:,:,:,:)=transports_3d_h(:,:,:,:)/(nn_dctwri_h/nn_dct_h) 396 transports_2d_h(:,:,:) =transports_2d_h(:,:,:) /(nn_dctwri_h/nn_dct_h) 397 398 ! Sum over each class 399 DO jsec=1,nb_sec 400 CALL dia_dct_sum_h(secs(jsec),jsec) 401 ENDDO 402 403 !Sum on all procs 404 IF( lk_mpp )THEN 405 ish(1) = nb_sec_max*nb_type*nb_class_max 406 ish2 = (/nb_sec_max,nb_type,nb_class_max/) 407 DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport_h(:,:) ; ENDDO 408 zwork(:)= RESHAPE(zsum(:,:,:), ish ) 409 CALL mpp_sum(zwork, ish(1)) 410 zsum(:,:,:)= RESHAPE(zwork,ish2) 411 DO jsec=1,nb_sec ; secs(jsec)%transport_h(:,:) = zsum(jsec,:,:) ; ENDDO 412 ENDIF 413 414 !Write the transport 415 DO jsec=1,nb_sec 416 417 IF( lwp .and. ln_NOOS ) THEN 418 CALL dia_dct_wri_NOOS_h(kt/nn_dctwri_h,jsec,secs(jsec)) ! use NOOS specific formatting 419 endif 420 !nullify transports values after writing 421 transports_3d_h(:,jsec,:,:)=0.0 422 transports_2d_h(:,jsec,:)=0.0 423 secs(jsec)%transport_h(:,:)=0. 424 IF ( ln_NOOS ) CALL transport_h(secs(jsec),lldebug,jsec) ! reinitialise for next 25 hour instantaneous average (overlapping values) 425 426 ENDDO 427 428 ENDIF 429 430 ENDIF 431 357 432 ENDIF 358 IF ( MOD(kt,nn_dct_h)==0 ) THEN ! compute transport every nn_dct_h time steps359 360 DO jsec=1,nb_sec361 362 lldebug=.FALSE.363 IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND. kt==nit000+nn_dct_h-1 .AND. lwp ) lldebug=.TRUE.364 365 !Compute transport through section366 CALL transport_h(secs(jsec),lldebug,jsec)367 368 ENDDO369 370 IF( MOD(kt,nn_dctwri_h)==0 )THEN371 372 IF( lwp .AND. kt==nit000+nn_dctwri_h-1 )WRITE(numout,*)" diadct: average and write hourly files at kt = ",kt373 374 !! divide arrays by nn_dctwri/nn_dct to obtain average375 transports_3d_h(:,:,:,:)=transports_3d_h(:,:,:,:)/(nn_dctwri_h/nn_dct_h)376 transports_2d_h(:,:,:) =transports_2d_h(:,:,:) /(nn_dctwri_h/nn_dct_h)377 378 ! Sum over each class379 DO jsec=1,nb_sec380 CALL dia_dct_sum_h(secs(jsec),jsec)381 ENDDO382 383 !Sum on all procs384 IF( lk_mpp )THEN385 ish(1) = nb_sec_max*nb_type*nb_class_max386 ish2 = (/nb_sec_max,nb_type,nb_class_max/)387 DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport_h(:,:) ; ENDDO388 zwork(:)= RESHAPE(zsum(:,:,:), ish )389 CALL mpp_sum(zwork, ish(1))390 zsum(:,:,:)= RESHAPE(zwork,ish2)391 DO jsec=1,nb_sec ; secs(jsec)%transport_h(:,:) = zsum(jsec,:,:) ; ENDDO392 ENDIF393 394 !Write the transport395 DO jsec=1,nb_sec396 397 IF( lwp .and. ln_NOOS ) THEN398 CALL dia_dct_wri_NOOS_h(kt/nn_dctwri_h,jsec,secs(jsec)) ! use NOOS specific formatting399 endif400 !nullify transports values after writing401 transports_3d_h(:,jsec,:,:)=0.0402 transports_2d_h(:,jsec,:)=0.0403 secs(jsec)%transport_h(:,:)=0.404 IF ( ln_NOOS ) CALL transport_h(secs(jsec),lldebug,jsec) ! reinitialise for next 25 hour instantaneous average (overlapping values)405 406 ENDDO407 408 ENDIF409 410 ENDIF411 433 412 434 IF( lk_mpp )THEN … … 476 498 477 499 IF ( lwp .AND. ( jsec==nn_secdebug .OR. nn_secdebug==-1 ) ) & 478 & WRITE(numout,*)'debug ing for section number: ',jsec500 & WRITE(numout,*)'debugging for section number: ',jsec 479 501 480 502 !initialization … … 1622 1644 REAL(wp), POINTER, DIMENSION(:):: zsumclasses ! 1D workspace 1623 1645 CHARACTER(len=3) :: noos_sect_name ! Classname 1646 CHARACTER(len=25) :: noos_var_sect_name 1624 1647 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: noos_iom_dummy 1625 1648 INTEGER :: IERR … … 1639 1662 zslope = sec%slopeSection 1640 1663 1641 WRITE(numdct_NOOS,'(I4,a1,I2,a1,I2,a12,i3,a17,i3,a10,a25)') nyear,'.',nmonth,'.',nday,' Transect:',ksec-1,' No. of layers:',sec%nb_class-1,' Name: ',sec%name 1642 1664 IF( lwp ) THEN 1665 WRITE(numdct_NOOS,'(I4,a1,I2,a1,I2,a12,i3,a17,i3,a10,a25)') nyear,'.',nmonth,'.',nday,' Transect:',ksec-1,' No. of layers:',sec%nb_class-1,' Name: ',sec%name 1666 ENDIF 1643 1667 DO jclass=1,MAX(1,sec%nb_class-1) 1644 1668 zsumclasses(1:nb_type)=zsumclasses(1:nb_type)+sec%transport(1:nb_type,jclass) … … 1653 1677 write (noos_sect_name, "(I0.3)") ksec 1654 1678 1655 !ALLOCATE( noos_iom_dummy(jpi,jpj,1), STAT= ierr )1656 ! IF( ierr /= 0 ) CALL ctl_stop( 'dia_dct_wri_NOOS: failed to allocate noos_iom_dummy array' )1657 1658 1659 ! ALLOCATE( noos_iom_dummy(jpi,jpj,9), STAT= ierr )1660 ! IF( ierr /= 0 ) CALL ctl_stop( 'dia_dct_wri_NOOS: failed to allocate noos_iom_dummy array' )1661 1662 1679 ALLOCATE( noos_iom_dummy(jpi,jpj,3), STAT= ierr ) 1663 1680 IF( ierr /= 0 ) CALL ctl_stop( 'dia_dct_wri_NOOS: failed to allocate noos_iom_dummy array' ) … … 1665 1682 1666 1683 1667 !IF( lwp ) THEN1668 !1669 ! WRITE(numout,*) "dia_dct_wri_NOOS: kt, jpi,jpj,3", kt, jpi,jpj,31670 !1671 !ENDIF1672 1684 IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 1685 1686 IF( lwp ) THEN 1673 1687 WRITE(numdct_NOOS,'(9e12.4E2)') -(zsumclasses( 1)+zsumclasses( 2)), -zsumclasses( 2),-zsumclasses( 1), & 1674 1688 -(zsumclasses( 7)+zsumclasses( 8)), -zsumclasses( 8),-zsumclasses( 7), & 1675 1689 -(zsumclasses( 9)+zsumclasses(10)), -zsumclasses(10),-zsumclasses( 9) 1676 ! 1677 ! noos_iom_dummy(:,:,:) = 0. 1678 ! 1679 ! noos_iom_dummy(:,:,1) = -(zsumclasses( 1)+zsumclasses( 2)) 1680 ! noos_iom_dummy(:,:,2) = -zsumclasses( 2) 1681 ! noos_iom_dummy(:,:,3) = -zsumclasses( 1) 1682 ! noos_iom_dummy(:,:,4) = -(zsumclasses( 7)+zsumclasses( 8)) 1683 ! noos_iom_dummy(:,:,5) = -zsumclasses( 8) 1684 ! noos_iom_dummy(:,:,6) = -zsumclasses( 7) 1685 ! noos_iom_dummy(:,:,7) = -(zsumclasses( 9)+zsumclasses( 10)) 1686 ! noos_iom_dummy(:,:,8) = -zsumclasses( 10) 1687 ! noos_iom_dummy(:,:,9) = -zsumclasses( 9) 1688 ! 1689 ! CALL iom_put( "noos_" // trim(noos_sect_name), noos_iom_dummy ) 1690 ! noos_iom_dummy(:,:,:) = 0. 1691 ! 1692 1693 1690 endif 1691 1694 1692 1695 1693 noos_iom_dummy(:,:,:) = 0. … … 1698 1696 noos_iom_dummy(:,:,2) = -zsumclasses( 2) 1699 1697 noos_iom_dummy(:,:,3) = -zsumclasses( 1) 1700 !IF( lwp ) WRITE(numout,*) "dia_dct_wri_NOOS +ve : kt, trans", kt, & 1701 ! & noos_iom_dummy(10,10,1), noos_iom_dummy(10,10,2), noos_iom_dummy(10,10,3) 1702 !CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans', noos_iom_dummy ) 1698 1699 noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_trans' 1700 if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 1701 CALL iom_put( noos_var_sect_name, noos_iom_dummy ) 1703 1702 noos_iom_dummy(:,:,:) = 0. 1704 1703 … … 1706 1705 noos_iom_dummy(:,:,2) = -zsumclasses( 8) 1707 1706 noos_iom_dummy(:,:,3) = -zsumclasses( 7) 1708 !IF( lwp ) WRITE(numout,*) "dia_dct_wri_NOOS +ve : kt, heat", kt, & 1709 ! & noos_iom_dummy(10,10,1), noos_iom_dummy(10,10,2), noos_iom_dummy(10,10,3) 1710 !CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat', noos_iom_dummy ) 1707 1708 noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_heat' 1709 if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 1710 CALL iom_put( noos_var_sect_name, noos_iom_dummy ) 1711 1711 noos_iom_dummy(:,:,:) = 0. 1712 1712 … … 1714 1714 noos_iom_dummy(:,:,2) = -zsumclasses( 10) 1715 1715 noos_iom_dummy(:,:,3) = -zsumclasses( 9) 1716 !IF( lwp ) WRITE(numout,*) "dia_dct_wri_NOOS +ve : kt, salt", kt, & 1717 ! & noos_iom_dummy(10,10,1), noos_iom_dummy(10,10,2), noos_iom_dummy(10,10,3) 1718 !CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt', noos_iom_dummy ) 1716 1717 noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_salt' 1718 if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 1719 CALL iom_put( noos_var_sect_name, noos_iom_dummy ) 1719 1720 noos_iom_dummy(:,:,:) = 0. 1720 1721 1722 !1723 ! noos_iom_dummy(:,:,:) = 0.1724 !1725 ! noos_iom_dummy(:,:,1) = -(zsumclasses( 1)+zsumclasses( 2))1726 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans_tot', noos_iom_dummy )1727 ! noos_iom_dummy(:,:,:) = 0.1728 !1729 ! noos_iom_dummy(:,:,1) = -zsumclasses( 2)1730 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans_pos', noos_iom_dummy )1731 ! noos_iom_dummy(:,:,:) = 0.1732 !1733 ! noos_iom_dummy(:,:,1) = -zsumclasses( 1)1734 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans_neg', noos_iom_dummy )1735 ! noos_iom_dummy(:,:,:) = 0.1736 !1737 ! noos_iom_dummy(:,:,1) = -(zsumclasses( 7)+zsumclasses( 8))1738 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat_tot', noos_iom_dummy )1739 ! noos_iom_dummy(:,:,:) = 0.1740 !1741 ! noos_iom_dummy(:,:,1) = -zsumclasses( 8)1742 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat_pos', noos_iom_dummy )1743 ! noos_iom_dummy(:,:,:) = 0.1744 !1745 ! noos_iom_dummy(:,:,1) = -zsumclasses( 7)1746 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat_neg', noos_iom_dummy )1747 ! noos_iom_dummy(:,:,:) = 0.1748 !1749 ! noos_iom_dummy(:,:,1) = -(zsumclasses( 9)+zsumclasses( 10))1750 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt_tot', noos_iom_dummy )1751 ! noos_iom_dummy(:,:,:) = 0.1752 !1753 ! noos_iom_dummy(:,:,1) = -zsumclasses( 10)1754 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt_pos', noos_iom_dummy )1755 ! noos_iom_dummy(:,:,:) = 0.1756 !1757 ! noos_iom_dummy(:,:,1) = -zsumclasses( 9)1758 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt_neg', noos_iom_dummy )1759 ! noos_iom_dummy(:,:,:) = 0.1760 !1761 1762 1763 1721 ELSE 1764 WRITE(numdct_NOOS,'(9e12.4E2)') zsumclasses( 1)+zsumclasses( 2) , zsumclasses( 1), zsumclasses( 2), & 1765 zsumclasses( 7)+zsumclasses( 8) , zsumclasses( 7), zsumclasses( 8), & 1766 zsumclasses( 9)+zsumclasses(10) , zsumclasses( 9), zsumclasses(10) 1722 IF( lwp ) THEN 1723 WRITE(numdct_NOOS,'(9e12.4E2)') zsumclasses( 1)+zsumclasses( 2) , zsumclasses( 1), zsumclasses( 2), & 1724 zsumclasses( 7)+zsumclasses( 8) , zsumclasses( 7), zsumclasses( 8), & 1725 zsumclasses( 9)+zsumclasses(10) , zsumclasses( 9), zsumclasses(10) 1726 endif 1767 1727 1768 1769 1770 !1771 ! noos_iom_dummy(:,:,:) = 0.1772 !1773 ! noos_iom_dummy(:,:,1) = (zsumclasses( 1)+zsumclasses( 2))1774 ! noos_iom_dummy(:,:,2) = zsumclasses( 1)1775 ! noos_iom_dummy(:,:,3) = zsumclasses( 2)1776 ! noos_iom_dummy(:,:,4) = (zsumclasses( 7)+zsumclasses( 8))1777 ! noos_iom_dummy(:,:,5) = zsumclasses( 7)1778 ! noos_iom_dummy(:,:,6) = zsumclasses( 8)1779 ! noos_iom_dummy(:,:,7) = (zsumclasses( 9)+zsumclasses( 10))1780 ! noos_iom_dummy(:,:,8) = zsumclasses( 9)1781 ! noos_iom_dummy(:,:,9) = zsumclasses( 10)1782 !1783 ! CALL iom_put( "noos_" // trim(noos_sect_name), noos_iom_dummy )1784 1785 1786 1787 1728 1788 1729 noos_iom_dummy(:,:,1) = (zsumclasses( 1)+zsumclasses( 2)) 1789 1730 noos_iom_dummy(:,:,2) = zsumclasses( 1) 1790 1731 noos_iom_dummy(:,:,3) = zsumclasses( 2) 1791 !IF( lwp ) WRITE(numout,*) "dia_dct_wri_NOOS -ve : kt, trans", kt, & 1792 ! & noos_iom_dummy(10,10,1), noos_iom_dummy(10,10,2), noos_iom_dummy(10,10,3) 1793 !CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans', noos_iom_dummy ) 1732 1733 noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_trans' 1734 if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 1735 CALL iom_put( noos_var_sect_name, noos_iom_dummy ) 1794 1736 noos_iom_dummy(:,:,:) = 0. 1795 1737 … … 1797 1739 noos_iom_dummy(:,:,2) = zsumclasses( 7) 1798 1740 noos_iom_dummy(:,:,3) = zsumclasses( 8) 1799 !IF( lwp ) WRITE(numout,*) "dia_dct_wri_NOOS -ve : kt, heat", kt, & 1800 ! & noos_iom_dummy(10,10,1), noos_iom_dummy(10,10,2), noos_iom_dummy(10,10,3) 1801 !CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat', noos_iom_dummy ) 1741 1742 noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_heat' 1743 if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 1744 CALL iom_put(noos_var_sect_name, noos_iom_dummy ) 1802 1745 noos_iom_dummy(:,:,:) = 0. 1803 1746 … … 1805 1748 noos_iom_dummy(:,:,2) = zsumclasses( 9) 1806 1749 noos_iom_dummy(:,:,3) = zsumclasses( 10) 1807 !IF( lwp ) WRITE(numout,*) "dia_dct_wri_NOOS -ve : kt, salt", kt, & 1808 ! & noos_iom_dummy(10,10,1), noos_iom_dummy(10,10,2), noos_iom_dummy(10,10,3) 1809 !CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt', noos_iom_dummy ) 1750 1751 noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_salt' 1752 if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 1753 CALL iom_put(noos_var_sect_name, noos_iom_dummy ) 1810 1754 noos_iom_dummy(:,:,:) = 0. 1811 1755 1812 !1813 !1814 !1815 ! noos_iom_dummy(:,:,1) = (zsumclasses( 1)+zsumclasses( 2))1816 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans_tot', noos_iom_dummy )1817 ! noos_iom_dummy(:,:,:) = 0.1818 !1819 ! noos_iom_dummy(:,:,1) = zsumclasses( 1)1820 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans_pos', noos_iom_dummy )1821 ! noos_iom_dummy(:,:,:) = 0.1822 !1823 ! noos_iom_dummy(:,:,1) = zsumclasses( 2)1824 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_trans_neg', noos_iom_dummy )1825 ! noos_iom_dummy(:,:,:) = 0.1826 !1827 ! noos_iom_dummy(:,:,1) = (zsumclasses( 7)+zsumclasses( 8))1828 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat_tot', noos_iom_dummy )1829 ! noos_iom_dummy(:,:,:) = 0.1830 !1831 ! noos_iom_dummy(:,:,1) = zsumclasses( 7)1832 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat_pos', noos_iom_dummy )1833 ! noos_iom_dummy(:,:,:) = 0.1834 !1835 ! noos_iom_dummy(:,:,1) = zsumclasses( 8)1836 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_heat_neg', noos_iom_dummy )1837 ! noos_iom_dummy(:,:,:) = 0.1838 !1839 ! noos_iom_dummy(:,:,1) = (zsumclasses( 9)+zsumclasses( 10))1840 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt_tot', noos_iom_dummy )1841 ! noos_iom_dummy(:,:,:) = 0.1842 !1843 ! noos_iom_dummy(:,:,1) = zsumclasses( 9)1844 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt_pos', noos_iom_dummy )1845 ! noos_iom_dummy(:,:,:) = 0.1846 !1847 ! noos_iom_dummy(:,:,1) = zsumclasses( 10)1848 ! CALL iom_put( "noos_" // trim(noos_sect_name) // '_salt_neg', noos_iom_dummy )1849 ! noos_iom_dummy(:,:,:) = 0.1850 1851 1756 ENDIF 1852 1757 1853 1758 1854 1759 DEALLOCATE(noos_iom_dummy) 1855 1760 1856 1761 DO jclass=1,MAX(1,sec%nb_class-1) … … 1897 1802 1898 1803 !write volume transport per class 1899 IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 1900 WRITE(numdct_NOOS,'(9e12.4E2)') -(sec%transport( 1,jclass)+sec%transport( 2,jclass)),-sec%transport( 2,jclass),-sec%transport( 1,jclass), & 1901 -(sec%transport( 7,jclass)+sec%transport( 8,jclass)),-sec%transport( 8,jclass),-sec%transport( 7,jclass), & 1902 -(sec%transport( 9,jclass)+sec%transport(10,jclass)),-sec%transport(10,jclass),-sec%transport( 9,jclass) 1903 ELSE 1904 WRITE(numdct_NOOS,'(9e12.4E2)') sec%transport( 1,jclass)+sec%transport( 2,jclass) , sec%transport( 1,jclass), sec%transport( 2,jclass), & 1905 sec%transport( 7,jclass)+sec%transport( 8,jclass) , sec%transport( 7,jclass), sec%transport( 8,jclass), & 1906 sec%transport( 9,jclass)+sec%transport(10,jclass) , sec%transport( 9,jclass), sec%transport(10,jclass) 1804 1805 IF( lwp ) THEN 1806 IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 1807 WRITE(numdct_NOOS,'(9e12.4E2)') -(sec%transport( 1,jclass)+sec%transport( 2,jclass)),-sec%transport( 2,jclass),-sec%transport( 1,jclass), & 1808 -(sec%transport( 7,jclass)+sec%transport( 8,jclass)),-sec%transport( 8,jclass),-sec%transport( 7,jclass), & 1809 -(sec%transport( 9,jclass)+sec%transport(10,jclass)),-sec%transport(10,jclass),-sec%transport( 9,jclass) 1810 ELSE 1811 WRITE(numdct_NOOS,'(9e12.4E2)') sec%transport( 1,jclass)+sec%transport( 2,jclass) , sec%transport( 1,jclass), sec%transport( 2,jclass), & 1812 sec%transport( 7,jclass)+sec%transport( 8,jclass) , sec%transport( 7,jclass), sec%transport( 8,jclass), & 1813 sec%transport( 9,jclass)+sec%transport(10,jclass) , sec%transport( 9,jclass), sec%transport(10,jclass) 1814 ENDIF 1907 1815 ENDIF 1908 1816 1909 1817 ENDDO 1910 1818 1911 CALL FLUSH(numdct_NOOS)1819 if ( lwp ) CALL FLUSH(numdct_NOOS) 1912 1820 1913 1821 CALL wrk_dealloc(nb_type , zsumclasses ) … … 1929 1837 !!------------------------------------------------------------- 1930 1838 !!arguments 1931 INTEGER, INTENT(IN) :: hr ! hour 1839 INTEGER, INTENT(IN) :: hr ! hour => effectively kt/12 1932 1840 TYPE(SECTION), INTENT(INOUT) :: sec ! section to write 1933 1841 INTEGER ,INTENT(IN) :: ksec ! section number … … 1941 1849 REAL(wp), POINTER, DIMENSION(:):: zsumclasses ! 1D workspace 1942 1850 CHARACTER(len=3) :: noos_sect_name ! Classname 1943 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: noos_iom_dummy 1851 CHARACTER(len=25) :: noos_var_sect_name 1852 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: noos_iom_dummy 1944 1853 INTEGER :: IERR 1945 1854 … … 1957 1866 write (noos_sect_name, "(I03)") ksec 1958 1867 1959 ALLOCATE( noos_iom_dummy(jpi,jpj ), STAT= ierr )1868 ALLOCATE( noos_iom_dummy(jpi,jpj,3), STAT= ierr ) 1960 1869 IF( ierr /= 0 ) CALL ctl_stop( 'dia_dct_wri_NOOS_h: failed to allocate noos_iom_dummy array' ) 1961 1870 -
branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/DIA/diaregmean.F90
r7572 r7593 24 24 PUBLIC dia_regmean_init ! routine called by nemogcm.F90 25 25 PUBLIC dia_regmean ! routine called by diawri.F90 26 !PUBLIC dia_wri_region_mean27 !PUBLIC dia_calctmb_region_mean28 26 29 27 … … 45 43 46 44 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tmp_field_mat !: temporary region_mask 47 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tmp_field_karamld_mat !: temporary region_mask48 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tmp_field_pea_mat !: temporary region_mask49 45 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tmp_field_AR5_mat !: temporary region_mask 50 46 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tmp_field_SBC_mat !: temporary region_mask 51 47 INTEGER :: tmp_field_cnt ! tmp_field_cnt integer 52 INTEGER :: num_reg_vars ! number of vars in regions mean53 48 !!---------------------------------------------------------------------- 54 49 !! NEMO/OPA 3.6 , NEMO Consortium (2014) … … 111 106 ENDIF 112 107 113 num_reg_vars = 7114 115 ALLOCATE( tmp_field_mat(jpi,jpj, num_reg_vars), STAT= ierr ) !SS/NB/DT T/S, SSH, MLD, PEA, PEAT, PEAS108 109 !ALLOCATE( tmp_field_mat(jpi,jpj,7), STAT= ierr ) !SS/NB/DT T/S, SSH, MLD, PEA, PEAT, PEAS 110 ALLOCATE( tmp_field_mat(jpi,jpj,11), STAT= ierr ) !SS/NB/DT T/S, SSH, MLD, PEA, PEAT, PEAS 116 111 IF( ierr /= 0 ) CALL ctl_stop( 'tmp_field_mat: failed to allocate tmp_region_mask_real array' ) 117 112 tmp_field_mat(:,:,:) = 0. 118 113 tmp_field_cnt = 0 119 120 IF(ln_diaregmean_karamld) THEN121 ALLOCATE( tmp_field_karamld_mat(jpi,jpj,1), STAT= ierr ) !SS/NB/DT T/S, SSH, MLD, PEA, PEAT, PEAS122 IF( ierr /= 0 ) CALL ctl_stop( 'tmp_field_karamld_mat: failed to allocate tmp_region_mask_real array' )123 tmp_field_karamld_mat(:,:,:) = 0.124 ENDIF125 126 IF(ln_diaregmean_pea) THEN127 ALLOCATE( tmp_field_pea_mat(jpi,jpj,3), STAT= ierr ) !SS/NB/DT T/S, SSH, MLD, PEA, PEAT, PEAS128 IF( ierr /= 0 ) CALL ctl_stop( 'tmp_field_pea_mat: failed to allocate tmp_region_mask_real array' )129 tmp_field_pea_mat(:,:,:) = 0.130 ENDIF131 114 132 115 IF(ln_diaregmean_diaar5) THEN … … 142 125 ENDIF 143 126 144 145 146 147 148 127 IF (ln_diaregmean) THEN 149 128 150 151 152 129 ! Open region mask for region means, and retrieve the size of the mask (number of levels) 153 130 CALL iom_open ( 'region_mask.nc', inum ) … … 284 261 INTEGER :: i_steps, ierr ! no of timesteps per hour, allocation error index 285 262 INTEGER :: maskno,jj,ji,jm,nreg ! indices of mask, i and j, and number of regions 286 REAL(wp) :: start_reg_mean_sub,finish_reg_mean_sub287 263 288 264 zmdi=1.e+20 !missing data indicator for maskin 289 265 290 266 IF (ln_diaregmean) THEN 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 tmp_field_mat(:,:,1) = tmp_field_mat(:,:,1) + zwtmbT(:,:,1)313 tmp_field_mat(:,:,2) = tmp_field_mat(:,:,2) + zwtmbT(:,:,2)314 tmp_field_mat(:,:,3) = tmp_field_mat(:,:,3) + zwtmbT(:,:,3)315 tmp_field_mat(:,:,4) = tmp_field_mat(:,:,4) + zwtmbS(:,:,1)316 tmp_field_mat(:,:,5) = tmp_field_mat(:,:,5) + zwtmbS(:,:,2)317 tmp_field_mat(:,:,6) = tmp_field_mat(:,:,6) + zwtmbS(:,:,3)318 tmp_field_mat(:,:,7) = tmp_field_mat(:,:,7) + sshn(:,:)319 320 IF( ln_diaregmean_karamld ) THEN321 tmp_field_karamld_mat(:,:,1) = tmp_field_karamld_mat(:,:,1) + hmld_kara(:,:)!hmlp(:,:)322 ENDIF323 324 325 tmp_field_pea_mat(:,:,1) = tmp_field_pea_mat(:,:,1) + pea(:,:)326 tmp_field_pea_mat(:,:,2) = tmp_field_pea_mat(:,:,2) + peat(:,:)327 tmp_field_pea_mat(:,:,3) = tmp_field_pea_mat(:,:,3) + peas(:,:)328 329 330 331 IF( ln_diaregmean_diaar5 ) THEN332 tmp_field_AR5_mat(:,:, 1) = tmp_field_AR5_mat(:,:,1) + sshsteric_mat(:,:)333 tmp_field_AR5_mat(:,:, 2) = tmp_field_AR5_mat(:,:,2) + sshthster_mat(:,:)334 tmp_field_AR5_mat(:,:, 3) = tmp_field_AR5_mat(:,:,3) + sshhlster_mat(:,:)335 tmp_field_AR5_mat(:,:,4) = tmp_field_AR5_mat(:,:,4) + zbotpres_mat(:,:) 336 337 338 339 267 ! If regional mean calculations required by namelist 268 ! ----------------- 269 ! identify hourly time steps (not used) 270 zdt = rdt 271 IF( nacc == 1 ) zdt = rdtmin 272 273 IF( MOD( 3600,INT(zdt) ) == 0 ) THEN 274 i_steps = 3600/INT(zdt) 275 ELSE 276 CALL ctl_stop('STOP', 'dia_regmean: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible') 277 ENDIF 278 279 !i_steps = 1 280 281 !Extract 2d fields from 3d T and S with dia_calctmb_region_mean 282 CALL wrk_alloc( jpi , jpj, 3 , zwtmbT ) 283 CALL wrk_alloc( jpi , jpj, 3 , zwtmbS ) 284 285 CALL dia_calctmb_region_mean( tsn(:,:,:,jp_tem),zwtmbT) 286 CALL dia_calctmb_region_mean( tsn(:,:,:,jp_sal),zwtmbS) 287 288 tmp_field_mat(:,:,1) = tmp_field_mat(:,:,1) + (zwtmbT(:,:,1)*tmask(:,:,1)) 289 tmp_field_mat(:,:,2) = tmp_field_mat(:,:,2) + (zwtmbT(:,:,2)*tmask(:,:,1)) 290 tmp_field_mat(:,:,3) = tmp_field_mat(:,:,3) + (zwtmbT(:,:,3)*tmask(:,:,1)) 291 tmp_field_mat(:,:,4) = tmp_field_mat(:,:,4) + (zwtmbS(:,:,1)*tmask(:,:,1)) 292 tmp_field_mat(:,:,5) = tmp_field_mat(:,:,5) + (zwtmbS(:,:,2)*tmask(:,:,1)) 293 tmp_field_mat(:,:,6) = tmp_field_mat(:,:,6) + (zwtmbS(:,:,3)*tmask(:,:,1)) 294 tmp_field_mat(:,:,7) = tmp_field_mat(:,:,7) + (sshn(:,:)*tmask(:,:,1)) 295 296 297 IF( ln_diaregmean_karamld ) THEN 298 tmp_field_mat(:,:,8) = tmp_field_mat(:,:,8) + (hmld_kara(:,:)*tmask(:,:,1)) !hmlp(:,:) 299 ENDIF 300 IF( ln_diaregmean_pea ) THEN 301 tmp_field_mat(:,:,9) = tmp_field_mat(:,:,9) + (pea(:,:)*tmask(:,:,1)) 302 tmp_field_mat(:,:,10) = tmp_field_mat(:,:,10) + (peat(:,:)*tmask(:,:,1)) 303 tmp_field_mat(:,:,11) = tmp_field_mat(:,:,11) + (peas(:,:)*tmask(:,:,1)) 304 ENDIF 305 306 IF( ln_diaregmean_diaar5 ) THEN 307 tmp_field_AR5_mat(:,:,1) = tmp_field_AR5_mat(:,:,1) + (sshsteric_mat(:,:)*tmask(:,:,1)) 308 tmp_field_AR5_mat(:,:,2) = tmp_field_AR5_mat(:,:,2) + (sshthster_mat(:,:)*tmask(:,:,1)) 309 tmp_field_AR5_mat(:,:,3) = tmp_field_AR5_mat(:,:,3) + (sshhlster_mat(:,:)*tmask(:,:,1)) 310 tmp_field_AR5_mat(:,:,4) = tmp_field_AR5_mat(:,:,4) + (zbotpres_mat(:,:)*tmask(:,:,1)) 311 312 ENDIF 313 314 IF( ln_diaregmean_diasbc ) THEN 315 340 316 tmp_field_SBC_mat(:,:,1) = tmp_field_SBC_mat(:,:,1) + ((qsr + qns)*tmask(:,:,1)) 341 317 tmp_field_SBC_mat(:,:,2) = tmp_field_SBC_mat(:,:,2) + (qsr*tmask(:,:,1)) … … 345 321 tmp_field_SBC_mat(:,:,6) = tmp_field_SBC_mat(:,:,6) + (pressnow*tmask(:,:,1)) 346 322 tmp_field_SBC_mat(:,:,7) = tmp_field_SBC_mat(:,:,7) + (rnf*tmask(:,:,1)) 323 324 325 ENDIF 326 327 tmp_field_cnt = tmp_field_cnt + 1 328 329 IF( MOD( kt, i_steps ) == 0 .and. kt .ne. nn_it000 ) THEN 330 331 332 CALL dia_wri_region_mean(kt, "sst" , tmp_field_mat(:,:,1)/real(tmp_field_cnt,wp)) 333 CALL dia_wri_region_mean(kt, "nbt" , tmp_field_mat(:,:,2)/real(tmp_field_cnt,wp)) 334 CALL dia_wri_region_mean(kt, "dft" , tmp_field_mat(:,:,3)/real(tmp_field_cnt,wp)) 335 336 CALL dia_wri_region_mean(kt, "sss" , tmp_field_mat(:,:,4)/real(tmp_field_cnt,wp)) 337 CALL dia_wri_region_mean(kt, "nbs" , tmp_field_mat(:,:,5)/real(tmp_field_cnt,wp)) 338 CALL dia_wri_region_mean(kt, "dfs" , tmp_field_mat(:,:,6)/real(tmp_field_cnt,wp)) 339 340 CALL dia_wri_region_mean(kt, "ssh" , tmp_field_mat(:,:,7)/real(tmp_field_cnt,wp)) 341 342 343 IF( ln_diaregmean_karamld ) THEN 344 345 CALL dia_wri_region_mean(kt, "mldkara" , tmp_field_mat(:,:,8)/real(tmp_field_cnt,wp)) ! tm 346 ENDIF 347 IF( ln_diaregmean_pea ) THEN 348 349 CALL dia_wri_region_mean(kt, "pea" , tmp_field_mat(:,:,9)/real(tmp_field_cnt,wp)) 350 CALL dia_wri_region_mean(kt, "peat" , tmp_field_mat(:,:,10)/real(tmp_field_cnt,wp)) 351 CALL dia_wri_region_mean(kt, "peas" , tmp_field_mat(:,:,11)/real(tmp_field_cnt,wp)) ! tmb 352 ENDIF 353 354 tmp_field_mat(:,:,:) = 0. 355 356 IF( ln_diaregmean_diaar5 ) THEN 357 358 CALL dia_wri_region_mean(kt, "ssh_steric" , tmp_field_AR5_mat(:,:,1)/real(tmp_field_cnt,wp)) 359 CALL dia_wri_region_mean(kt, "ssh_thermosteric", tmp_field_AR5_mat(:,:,2)/real(tmp_field_cnt,wp)) 360 CALL dia_wri_region_mean(kt, "ssh_halosteric" , tmp_field_AR5_mat(:,:,3)/real(tmp_field_cnt,wp)) 361 CALL dia_wri_region_mean(kt, "bot_pres" , tmp_field_AR5_mat(:,:,4)/real(tmp_field_cnt,wp)) 362 tmp_field_AR5_mat(:,:,:) = 0. 363 ENDIF 364 365 IF( ln_diaregmean_diasbc ) THEN 366 367 CALL dia_wri_region_mean(kt, "qt" , tmp_field_SBC_mat(:,:,1)/real(tmp_field_cnt,wp)) 368 CALL dia_wri_region_mean(kt, "qsr" , tmp_field_SBC_mat(:,:,2)/real(tmp_field_cnt,wp)) 369 CALL dia_wri_region_mean(kt, "qns" , tmp_field_SBC_mat(:,:,3)/real(tmp_field_cnt,wp)) 370 CALL dia_wri_region_mean(kt, "emp" , tmp_field_SBC_mat(:,:,4)/real(tmp_field_cnt,wp)) 371 CALL dia_wri_region_mean(kt, "wspd" , tmp_field_SBC_mat(:,:,5)/real(tmp_field_cnt,wp)) 372 CALL dia_wri_region_mean(kt, "mslp" , tmp_field_SBC_mat(:,:,6)/real(tmp_field_cnt,wp)) 373 CALL dia_wri_region_mean(kt, "rnf" , tmp_field_SBC_mat(:,:,7)/real(tmp_field_cnt,wp)) 374 tmp_field_SBC_mat(:,:,:) = 0. 375 ENDIF 376 377 tmp_field_cnt = 0 378 379 ENDIF 380 381 382 ! If on the last time step, close binary and ascii files. 383 IF( kt == nitend ) THEN 384 IF(lwp) THEN 385 IF ( ln_diaregmean_bin ) THEN 386 !Closing binary files for regional mean time series. 387 CLOSE(73) 388 ENDIF 389 IF ( ln_diaregmean_ascii ) THEN 390 !Closing text files for regional mean time series. 391 CLOSE(37) 392 ENDIF 347 393 394 DEALLOCATE( region_mask, nreg_mat, tmp_field_mat) 395 IF( ln_diaregmean_diaar5 ) DEALLOCATE( tmp_field_AR5_mat) 396 IF( ln_diaregmean_diasbc ) DEALLOCATE( tmp_field_SBC_mat) 348 397 ENDIF 349 350 tmp_field_cnt = tmp_field_cnt + 1 351 352 IF( MOD( kt, i_steps ) == 0 .and. kt .ne. nn_it000 ) THEN 353 354 355 CALL dia_wri_region_mean(kt, "sst" , tmp_field_mat(:,:,1)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 356 CALL dia_wri_region_mean(kt, "nbt" , tmp_field_mat(:,:,2)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 357 CALL dia_wri_region_mean(kt, "dft" , tmp_field_mat(:,:,3)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 358 359 CALL dia_wri_region_mean(kt, "sss" , tmp_field_mat(:,:,4)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Salinity 360 CALL dia_wri_region_mean(kt, "nbs" , tmp_field_mat(:,:,5)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Salinity 361 CALL dia_wri_region_mean(kt, "dfs" , tmp_field_mat(:,:,6)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Salinity; 362 363 CALL dia_wri_region_mean(kt, "ssh" , tmp_field_mat(:,:,7)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 364 365 IF( ln_diaregmean_karamld ) THEN 366 367 CALL dia_wri_region_mean(kt, "mldkara" , tmp_field_karamld_mat(:,:,1)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 368 369 ENDIF 370 371 IF( ln_diaregmean_pea ) THEN 372 373 CALL dia_wri_region_mean(kt, "pea" , tmp_field_pea_mat(:,:,1)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 374 CALL dia_wri_region_mean(kt, "peat" , tmp_field_pea_mat(:,:,2)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 375 CALL dia_wri_region_mean(kt, "peas" , tmp_field_pea_mat(:,:,3)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 376 377 ENDIF 378 379 IF( ln_diaregmean_diaar5 ) THEN 380 381 CALL dia_wri_region_mean(kt, "ssh_steric" , tmp_field_AR5_mat(:,:,1)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 382 CALL dia_wri_region_mean(kt, "ssh_thermosteric", tmp_field_AR5_mat(:,:,2)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 383 CALL dia_wri_region_mean(kt, "ssh_halosteric" , tmp_field_AR5_mat(:,:,3)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 384 CALL dia_wri_region_mean(kt, "bot_pres" , tmp_field_AR5_mat(:,:,4)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 385 386 ENDIF 387 388 IF( ln_diaregmean_diasbc ) THEN 389 390 CALL dia_wri_region_mean(kt, "qt" , tmp_field_SBC_mat(:,:,1)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 391 CALL dia_wri_region_mean(kt, "qsr" , tmp_field_SBC_mat(:,:,2)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 392 CALL dia_wri_region_mean(kt, "qns" , tmp_field_SBC_mat(:,:,3)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 393 CALL dia_wri_region_mean(kt, "emp" , tmp_field_SBC_mat(:,:,4)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 394 CALL dia_wri_region_mean(kt, "wspd" , tmp_field_SBC_mat(:,:,5)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 395 CALL dia_wri_region_mean(kt, "mslp" , tmp_field_SBC_mat(:,:,6)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 396 CALL dia_wri_region_mean(kt, "rnf" , tmp_field_SBC_mat(:,:,7)/real(tmp_field_cnt,wp))!,region_mask,nreg_mat(:,:,maskno),maskno,nreg_mat(maskno) ) ! tmb Temperature 397 398 ENDIF 399 400 401 IF( ln_diaregmean_karamld ) tmp_field_karamld_mat(:,:,:) = 0. 402 IF( ln_diaregmean_pea ) tmp_field_pea_mat(:,:,:) = 0. 403 IF( ln_diaregmean_diaar5 ) tmp_field_AR5_mat(:,:,:) = 0. 404 IF( ln_diaregmean_diasbc ) tmp_field_SBC_mat(:,:,:) = 0. 405 tmp_field_mat(:,:,:) = 0. 406 407 tmp_field_cnt = 0 408 409 ENDIF 410 411 412 413 414 415 ! If on the last time step, close binary and ascii files. 416 IF( kt == nitend ) THEN 417 IF(lwp) THEN 418 IF ( ln_diaregmean_bin ) THEN 419 !Closing binary files for regional mean time series. 420 CLOSE(73) 421 ENDIF 422 IF ( ln_diaregmean_ascii ) THEN 423 !Closing text files for regional mean time series. 424 CLOSE(37) 425 ENDIF 426 DEALLOCATE( region_mask, nreg_mat, tmp_field_mat) 427 IF( ln_diaregmean_karamld ) DEALLOCATE( tmp_field_karamld_mat) 428 IF( ln_diaregmean_pea ) DEALLOCATE( tmp_field_pea_mat) 429 IF( ln_diaregmean_diaar5 ) DEALLOCATE( tmp_field_AR5_mat) 430 IF( ln_diaregmean_diasbc ) DEALLOCATE( tmp_field_SBC_mat) 431 ENDIF 432 ENDIF 433 398 ENDIF 399 434 400 435 401 ELSE 436 402 CALL ctl_warn('dia_regmean: regmean diagnostic is set to false you should not have seen this') 437 403 ENDIF 438 404 … … 466 432 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zrmet_out 467 433 REAL(wp), ALLOCATABLE, DIMENSION(:) :: ave_mat,tot_mat,num_mat,var_mat,ssq_mat,cnt_mat,reg_id_mat,mask_id_mat !: region_mask 468 !REAL(wp), ALLOCATABLE, DIMENSION(:) :: tot_mat_2 469 !REAL(wp), ALLOCATABLE, DIMENSION(:) :: !: region_mask 434 470 435 REAL(wp) :: zmdi ! set masked values 471 436 INTEGER :: maskno,nreg ! ocean time-step indexocean time step … … 477 442 CHARACTER(LEN=180) :: FormatString,nreg_string 478 443 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: dummy_zrmet 479 480 !REAL(wp) :: start_reg_mean_loop,finish_reg_mean_loop,start_reg_mean_mpp, finish_reg_mean_mpp,start_reg_mean_mpp_mat,finish_reg_mean_mpp_mat481 482 483 444 zmdi=1.e+20 !missing data indicator for maskin 484 445 … … 545 506 reg_id_mat(:) = 0. 546 507 mask_id_mat(:) = 0. 547 548 508 549 509 ! loop though the array. for each sea grid box where tmask == 1), … … 599 559 600 560 WRITE(nreg_string, "(I5)") nreg 601 FormatString = "(A1 1,"//trim(nreg_string)//"F15.3)"602 WRITE(37, FMT="(A 4,I6,I6)") name,kt,maskno561 FormatString = "(A17,"//trim(nreg_string)//"F15.3)" 562 WRITE(37, FMT="(A17,I6,I6)") name,kt,maskno 603 563 WRITE(37, FMT=trim(FormatString)) trim(name)//" "//"ave_mat:", ave_mat 604 564 WRITE(37, FMT=trim(FormatString)) trim(name)//" "//"tot_mat:", tot_mat -
branches/UKMO/CO6_shelfclimate/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90
r7572 r7593 180 180 181 181 182 WRITE(numout,*) 'IOM: n_regions_output: ',n_regions_output183 184 182 ELSE 185 183 n_regions_output = 1 … … 312 310 313 311 314 ! JT Region means.315 312 CALL iom_set_axis_attr( "region", (/ (REAL(ji,wp), ji=1,n_regions_output) /) ) 316 313 317 !JT CALL iom_set_axis_attr( "noos", (/ (REAL(ji,wp), ji=1,9) /) )318 !JT CALL iom_set_axis_attr( "noos", (/ (REAL(ji,wp), ji=1,1) /) )319 !JT CALL iom_set_axis_attr( "noos", (/ (REAL(1,wp)) /) )320 314 CALL iom_set_axis_attr( "noos", (/ (REAL(ji,wp), ji=1,3) /) ) 321 315 … … 1340 1334 REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) :: bounds 1341 1335 1342 !INTEGER :: iind_JT1343 1344 1345 !write(numout,*) 'IOM/iom.F90:iom_set_axis_attr: ',cdid1346 1347 1336 IF ( PRESENT(paxis) ) THEN 1348 1337 1349 !write(numout,*) 'IOM/iom.F90:iom_set_axis_attr paxis size for: ',cdid,SIZE(paxis)1350 !write(numout,*) 'IOM/iom.F90:iom_set_axis_attr paxis values for: ',cdid,paxis1351 !do iind_JT = 1,SIZE(paxis)1352 ! write(numout,*) 'IOM/iom.F90:iom_set_axis_attr paxis individual values for: ',cdid,iind_JT,paxis(iind_JT)1353 !end do1354 1355 1338 #if ! defined key_xios2 1356 1339 IF ( xios_is_valid_axis (cdid) ) CALL xios_set_axis_attr ( cdid, size=SIZE(paxis), value=paxis )
Note: See TracChangeset
for help on using the changeset viewer.