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

Changeset 2927


Ignore:
Timestamp:
2011-10-14T19:01:57+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

    r2919 r2927  
    4141  USE ice 
    4242#endif 
     43  USE domvvl 
    4344 
    4445  IMPLICIT NONE 
     
    6869  INTEGER, PARAMETER :: nb_type_class = 14 
    6970  INTEGER            :: nb_sec  
     71 
     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 
    7075  
    7176  TYPE POINT_SECTION 
     
    8186     LOGICAL                                      :: llstrpond         ! true if you want the computation of salt and 
    8287                                                                       ! heat transports 
    83      LOGICAL                                      :: ll_ice_section    ! icesurf and icevol computation 
     88     LOGICAL                                      :: ll_ice_section    ! ice surface and ice volume computation 
    8489     LOGICAL                                      :: ll_date_line      ! = T if the section crosses the date-line 
    8590     TYPE(COORD_SECTION), DIMENSION(2)            :: coordSec          ! longitude and latitude of the extremities of the sec 
     
    9398                                                     zlay              ! level classes      (99 if you don't want) 
    9499     REAL(wp), DIMENSION(nb_type_class,nb_class_max)  :: transport     ! transport output 
    95      REAL(wp)                                         :: slopeSection  ! section's slopesection  
    96      INTEGER                                          :: nb_point      ! section's number of points 
    97      TYPE(POINT_SECTION),DIMENSION(nb_point_max)      :: listPoint     ! section's list point 
     100     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 
    98103  END TYPE SECTION 
    99104 
     
    134139          &  CALL ctl_stop( 'diadct: nn_dct should be smaller and a multiple of nn_dctwri' ) 
    135140 
    136         !open output file 
    137         CALL ctl_opn( numdct_vol,  'volume_transport', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    138         CALL ctl_opn( numdct_heat, 'heat_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    139         CALL ctl_opn( numdct_salt, 'salt_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    140  
    141141     ENDIF 
    142142 
    143143     !Read section_ijglobal.diadct 
    144144     CALL readsec 
     145 
     146     !open output file 
     147     IF( lwp ) THEN 
     148        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 
     153     ENDIF 
     154 
    145155 
    146156  END SUBROUTINE dia_dct_init 
     
    238248     INTEGER :: isec, iiglo, ijglo, iiloc, ijloc,iost,i1 ,i2  ! temporary  integer 
    239249     INTEGER :: jsec, jpt                                     ! dummy loop indices 
     250     INTEGER :: istrpond                                      ! count number of section for which  
     251                                                              ! heat/salt tranport is actived 
    240252 
    241253     INTEGER, DIMENSION(2) :: icoord  
    242      CHARACTER(len=160)  :: clname                            !filename 
    243      CHARACTER(len=200)  :: cltmp 
     254     CHARACTER(len=160)    :: clname                          !filename 
     255     CHARACTER(len=200)    :: cltmp 
     256     CHARACTER(len=200)    :: clformat                        !automatic format 
    244257     TYPE(POINT_SECTION),DIMENSION(nb_point_max)  ::coordtemp !contains listpoints coordinates  
    245258                                                              !read in the file 
     
    249262                lldebug                                       !debug the section 
    250263     !!------------------------------------------------------------------------------------- 
     264     istrpond   =  0             ! init  to zero number of section for which heat/salt tranport is actived 
     265     l_strpond = .FALSE.        ! 
    251266 
    252267     !open input file 
     
    296311        READ(numdct_in)iptglo 
    297312 
     313        istrpond = istrpond + COUNT((/secs(jsec)%llstrpond/))   
     314 
    298315        !debug 
    299316        !----- 
     317 
    300318        IF( lwp .AND. ( jsec==nn_secdebug .OR. nn_secdebug==-1 ) )THEN 
    301             WRITE(numout,*)                  "   Section name :                       ",TRIM(secs(jsec)%name) 
    302             WRITE(numout,*)                  "      Compute heat and salt transport ? ",secs(jsec)%llstrpond 
    303             WRITE(numout,*)                  "      Compute ice transport ?           ",secs(jsec)%ll_ice_section 
    304             WRITE(numout,*)                  "      Section crosses date-line ?       ",secs(jsec)%ll_date_line 
    305             WRITE(numout,*)                  "      Slope section :                   ",secs(jsec)%slopeSection 
    306             WRITE(numout,*)                  "      Number of points in the section:  ",iptglo 
    307             WRITE(numout,*)                  "      Number of classes                 ",secs(jsec)%nb_class 
    308 !            WRITE(numout,'(A40,10(f8.3,1X))')"      Insitu density classes :          ",secs(jsec)%zsigi 
    309             WRITE(numout,'(A40,nb_class_max(f8.3,1X))')"      Insitu density classes :          ",secs(jsec)%zsigi 
    310             WRITE(numout,'(A40,10(f8.3,1X))')"      Potential density classes :       ",secs(jsec)%zsigp 
    311             WRITE(numout,'(A40,10(f8.3,1X))')"      Salinity classes :                ",secs(jsec)%zsal 
    312             WRITE(numout,'(A40,10(f8.3,1X))')"      Temperature classes :             ",secs(jsec)%ztem 
    313             WRITE(numout,'(A40,10(f8.3,1X))')"      Depth classes :                   ",secs(jsec)%zlay 
     319           
     320            WRITE(clformat,'(a,i2,a)') '(A40,', nb_class_max,'(f8.3,1X))'  
     321 
     322            WRITE(numout,*)       "   Section name :                       ",TRIM(secs(jsec)%name) 
     323            WRITE(numout,*)       "      Compute heat and salt transport ? ",secs(jsec)%llstrpond 
     324            WRITE(numout,*)       "      Compute ice transport ?           ",secs(jsec)%ll_ice_section 
     325            WRITE(numout,*)       "      Section crosses date-line ?       ",secs(jsec)%ll_date_line 
     326            WRITE(numout,*)       "      Slope section :                   ",secs(jsec)%slopeSection 
     327            WRITE(numout,*)       "      Number of points in the section:  ",iptglo 
     328            WRITE(numout,*)       "      Number of classes                 ",secs(jsec)%nb_class 
     329            WRITE(numout,clformat)"      Insitu density classes :          ",secs(jsec)%zsigi 
     330            WRITE(numout,clformat)"      Potential density classes :       ",secs(jsec)%zsigp 
     331            WRITE(numout,clformat)"      Salinity classes :                ",secs(jsec)%zsal 
     332            WRITE(numout,clformat)"      Temperature classes :             ",secs(jsec)%ztem 
     333            WRITE(numout,clformat)"      Depth classes :                   ",secs(jsec)%zlay 
    314334        ENDIF                
    315335 
     
    402422     nb_sec = jsec-1   !number of section read in the file 
    403423 
     424     IF( istrpond .GT. 0 ) l_strpond = .TRUE.   ! output file  for heat/salt transport actived 
     425 
    404426  END SUBROUTINE readsec 
    405427 
     
    426448                isgn          ,& ! isgn= 1 : scan listpoint from start to end 
    427449                                 ! isgn=-1 : scan listpoint from end to start  
    428                 ipoint        ,& !way of course in listpoint 
    429450                istart,iend      !first and last points selected in listpoint 
    430451     INTEGER :: jpoint   =0      !loop on list points 
     
    485506     !!                     ***  ROUTINE transport  *** 
    486507     !! 
    487      !!  ** Purpose : Compute the transport trough a sec  
     508     !!  ** Purpose : Compute the transport trough a section 
    488509     !! 
    489510     !!  ** Method  :Transport through a given section is equal to the sum of transports 
    490511     !!              computed on each proc. 
    491512     !!              On each proc,transport is equal to the sum of transport computed through 
    492      !!               segments linking each points of sec%listPoint  with the next one.    
     513     !!               segments linking each point of sec%listPoint  with the next one.    
    493514     !! 
    494515     !!              !BE carefull :           
    495516     !!              one section is a sum of segments 
    496517     !!              one segment is defined by 2 consectuives points in sec%listPoint 
    497      !!              all points of sec%listPoint are positionned on the F-point of the cell.  
     518     !!              all points of sec%listPoint are positioned on the F-point of the cell.  
    498519     !!  
    499520     !!              There are several loops:                  
     
    580601               
    581602           !------------------------------------------------------------------------------------------- 
    582            ! Select good coordinate to have velocity of the segment: 
     603           ! Select the appropriate coordinate for computing the velocity of the segment 
    583604           ! 
    584605           !                      CASE(0)                                    Case (2) 
     
    10981119#if defined key_vvl 
    10991120 
    1100      ze3w  = fsve3w(ii2,ij2,kk) - fsve3w(ii1,ij1,kk) 
    1101  
    1102      zfse3 = fsve3w(ii1,ij1,kk) * ( 1 + sshn(ii2,ij2) * mut(ii2,ij2,kk) ) 
    1103      zwgt1 = ( fse3w(ii2,ij2,kk) - zfse3 )/ fse3w(ii2,ij2,kk) 
    1104    
    1105      zfse3 = fsve3w(ii2,ij2,kk) * ( 1 + sshn(ii1,ij1) * mut(ii1,ij1,kk) ) 
    1106      zwgt2 = ( fse3w(ii1,ij1,kk) - zfse3 )/ fse3w(ii1,ij1,kk) 
     1121     ze3t  = fse3t_n(ii2,ij2,kk) - fse3t_n(ii1,ij1,kk)  
     1122     zwgt1 = ( fse3w_n(ii2,ij2,kk) - fse3w_n(ii1,ij1,kk) ) / fse3w_n(ii2,ij2,kk) 
     1123     zwgt2 = ( fse3w_n(ii1,ij1,kk) - fse3w_n(ii2,ij2,kk) ) / fse3w_n(ii1,ij1,kk) 
    11071124 
    11081125#else 
    11091126 
    1110      ze3t  = fse3t(ii2,ij2,kk)-fse3t(ii1,ij1,kk)  
     1127     ze3t  = fse3t(ii2,ij2,kk)   - fse3t(ii1,ij1,kk)  
    11111128     zwgt1 = ( fse3w(ii2,ij2,kk) - fse3w(ii1,ij1,kk) ) / fse3w(ii2,ij2,kk) 
    11121129     zwgt2 = ( fse3w(ii1,ij1,kk) - fse3w(ii2,ij2,kk) ) / fse3w(ii1,ij1,kk) 
Note: See TracChangeset for help on using the changeset viewer.