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

Changeset 2941


Ignore:
Timestamp:
2011-10-17T14:17:40+02:00 (13 years ago)
Author:
cbricaud
Message:

corrections after review

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_r2802_MERCATOR10_diadct/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90

    r2927 r2941  
    7070  INTEGER            :: nb_sec  
    7171 
    72   LOGICAL            :: l_strpond ! FALSE: 0 section with heat/salt tranport 
    73                                   ! TRUE : 1 or more sections  with heat/salt tranport 
    74                                   ! Used to open/close output files for heat/salt tranport 
    75   
    7672  TYPE POINT_SECTION 
    7773     INTEGER :: I,J 
     
    9995     REAL(wp), DIMENSION(nb_type_class,nb_class_max)  :: transport     ! transport output 
    10096     REAL(wp)                                         :: slopeSection  ! slope of the section 
    101      INTEGER                                          :: nb_point      ! number of points in section 
    102      TYPE(POINT_SECTION),DIMENSION(nb_point_max)      :: listPoint     ! list point in section 
     97     INTEGER                                          :: nb_point      ! number of points in the section 
     98     TYPE(POINT_SECTION),DIMENSION(nb_point_max)      :: listPoint     ! list of points in the sections 
    10399  END TYPE SECTION 
    104100 
     
    147143     IF( lwp ) THEN 
    148144        CALL ctl_opn( numdct_vol,  'volume_transport', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    149         IF( l_strpond )THEN 
    150            CALL ctl_opn( numdct_heat, 'heat_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    151            CALL ctl_opn( numdct_salt, 'salt_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    152         ENDIF 
     145        CALL ctl_opn( numdct_heat, 'heat_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
     146        CALL ctl_opn( numdct_salt, 'salt_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    153147     ENDIF 
    154148 
     
    248242     INTEGER :: isec, iiglo, ijglo, iiloc, ijloc,iost,i1 ,i2  ! temporary  integer 
    249243     INTEGER :: jsec, jpt                                     ! dummy loop indices 
    250      INTEGER :: istrpond                                      ! count number of section for which  
    251244                                                              ! heat/salt tranport is actived 
    252245 
     
    262255                lldebug                                       !debug the section 
    263256     !!------------------------------------------------------------------------------------- 
    264      istrpond   =  0             ! init  to zero number of section for which heat/salt tranport is actived 
    265      l_strpond = .FALSE.        ! 
    266257 
    267258     !open input file 
     
    310301        READ(numdct_in)secs(jsec)%slopeSection 
    311302        READ(numdct_in)iptglo 
    312  
    313         istrpond = istrpond + COUNT((/secs(jsec)%llstrpond/))   
    314303 
    315304        !debug 
     
    422411     nb_sec = jsec-1   !number of section read in the file 
    423412 
    424      IF( istrpond .GT. 0 ) l_strpond = .TRUE.   ! output file  for heat/salt transport actived 
    425  
    426413  END SUBROUTINE readsec 
    427414 
     
    506493     !!                     ***  ROUTINE transport  *** 
    507494     !! 
    508      !!  ** Purpose : Compute the transport trough a section 
     495     !!  ** Purpose : Compute the transport through a section 
    509496     !! 
    510497     !!  ** Method  :Transport through a given section is equal to the sum of transports 
     
    515502     !!              !BE carefull :           
    516503     !!              one section is a sum of segments 
    517      !!              one segment is defined by 2 consectuives points in sec%listPoint 
     504     !!              one segment is defined by 2 consectuve points in sec%listPoint 
    518505     !!              all points of sec%listPoint are positioned on the F-point of the cell.  
    519506     !!  
     
    547534                zice_surf_pos, zice_surf_neg  !surface ice  transport     " 
    548535     REAL(wp):: ztn, zsn, zrhoi, zrhop, zsshn, zfsdep ! temperature/salinity/ssh/potential density /depth at u/v point 
    549      REAL(wp) :: aj,i0,j0,i1,j1,i,j 
    550536 
    551537     TYPE(POINT_SECTION) :: k 
     
    868854  END SUBROUTINE transport 
    869855   
    870   SUBROUTINE dia_dct_wri(kt,jsec,sec) 
     856  SUBROUTINE dia_dct_wri(kt,ksec,sec) 
    871857     !!------------------------------------------------------------- 
    872858     !! Write transport output in numdct  
     
    888874     INTEGER, INTENT(IN)          :: kt         ! time-step 
    889875     TYPE(SECTION), INTENT(INOUT) :: sec        ! section to write    
    890      INTEGER ,INTENT(IN)          :: jsec       ! section number 
     876     INTEGER ,INTENT(IN)          :: ksec       ! section number 
    891877 
    892878     !!local declarations 
     
    949935                   
    950936        !write volume transport per class 
    951         WRITE(numdct_vol,118) ndastp,kt,jsec,sec%name,zslope, & 
     937        WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope, & 
    952938                              jcl,classe,zbnd1,zbnd2,& 
    953939                              sec%transport(1,jcl),sec%transport(2,jcl), & 
     
    957943 
    958944           !write heat transport per class: 
    959            WRITE(numdct_heat,119) ndastp,kt,jsec,sec%name,zslope,  & 
     945           WRITE(numdct_heat,119) ndastp,kt,ksec,sec%name,zslope,  & 
    960946                              jcl,classe,zbnd1,zbnd2,& 
    961947                              sec%transport(7,jcl)*1000._wp*rcp/1.e15,sec%transport(8,jcl)*1000._wp*rcp/1.e15, & 
    962948                              ( sec%transport(7,jcl)+sec%transport(8,jcl) )*1000._wp*rcp/1.e15 
    963949           !write salt transport per class 
    964            WRITE(numdct_salt,119) ndastp,kt,jsec,sec%name,zslope,  & 
     950           WRITE(numdct_salt,119) ndastp,kt,ksec,sec%name,zslope,  & 
    965951                              jcl,classe,zbnd1,zbnd2,& 
    966952                              sec%transport(9,jcl)*1000._wp/1.e9,sec%transport(10,jcl)*1000._wp/1.e9,& 
     
    975961 
    976962     !write total volume transport 
    977      WRITE(numdct_vol,118) ndastp,kt,jsec,sec%name,zslope, & 
     963     WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope, & 
    978964                           jcl,"total",zbnd1,zbnd2,& 
    979965                           zsumclass(1),zsumclass(2),zsumclass(1)+zsumclass(2) 
     
    982968 
    983969        !write total heat transport 
    984         WRITE(numdct_heat,119) ndastp,kt,jsec,sec%name,zslope, & 
     970        WRITE(numdct_heat,119) ndastp,kt,ksec,sec%name,zslope, & 
    985971                           jcl,"total",zbnd1,zbnd2,& 
    986972                           zsumclass(7)* 1000._wp*rcp/1.e15,zsumclass(8)* 1000._wp*rcp/1.e15,& 
    987973                           (zsumclass(7)+zsumclass(8) )* 1000._wp*rcp/1.e15 
    988974        !write total salt transport 
    989         WRITE(numdct_salt,119) ndastp,kt,jsec,sec%name,zslope, & 
     975        WRITE(numdct_salt,119) ndastp,kt,ksec,sec%name,zslope, & 
    990976                           jcl,"total",zbnd1,zbnd2,& 
    991977                           zsumclass(9)*1000._wp/1.e9,zsumclass(10)*1000._wp/1.e9,& 
     
    996982     IF ( sec%ll_ice_section) THEN 
    997983        !write total ice volume transport 
    998         WRITE(numdct_vol,118) ndastp,kt,jsec,sec%name,zslope,& 
     984        WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope,& 
    999985                              jcl,"ice_vol",zbnd1,zbnd2,& 
    1000986                              sec%transport(9,1),sec%transport(10,1),& 
    1001987                              sec%transport(9,1)+sec%transport(10,1) 
    1002988        !write total ice surface transport 
    1003         WRITE(numdct_vol,118) ndastp,kt,jsec,sec%name,zslope,& 
     989        WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope,& 
    1004990                              jcl,"ice_surf",zbnd1,zbnd2,& 
    1005991                              sec%transport(11,1),sec%transport(12,1), & 
Note: See TracChangeset for help on using the changeset viewer.