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 7910 for branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90 – NEMO

Ignore:
Timestamp:
2017-04-13T16:21:08+02:00 (7 years ago)
Author:
timgraham
Message:

All wrk_alloc removed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90

    r7646 r7910  
    4040   USE domvvl 
    4141   USE timing          ! preformance summary 
    42    USE wrk_nemo        ! working arrays 
    4342 
    4443   IMPLICIT NONE 
     
    209208     INTEGER , DIMENSION(1)             :: ish   ! tmp array for mpp_sum 
    210209     INTEGER , DIMENSION(3)             :: ish2  !   " 
    211      REAL(wp), POINTER, DIMENSION(:)    :: zwork !   "   
    212      REAL(wp), POINTER, DIMENSION(:,:,:):: zsum  !   " 
     210     REAL(wp), DIMENSION(itotal)    :: zwork !   "   
     211     REAL(wp), DIMENSION(nb_sec_max,nb_type_class,nb_class_max):: zsum  !   " 
    213212     !!---------------------------------------------------------------------     
    214213     ! 
     
    217216     IF( lk_mpp )THEN 
    218217        itotal = nb_sec_max*nb_type_class*nb_class_max 
    219         CALL wrk_alloc( itotal                                , zwork )  
    220         CALL wrk_alloc( nb_sec_max,nb_type_class,nb_class_max , zsum  ) 
    221218     ENDIF     
    222219  
     
    289286     IF( lk_mpp )THEN 
    290287        itotal = nb_sec_max*nb_type_class*nb_class_max 
    291         CALL wrk_dealloc( itotal                                , zwork )  
    292         CALL wrk_dealloc( nb_sec_max,nb_type_class,nb_class_max , zsum  ) 
    293288     ENDIF     
    294289 
     
    318313     TYPE(POINT_SECTION),DIMENSION(nb_point_max)  ::coordtemp !contains listpoints coordinates  
    319314                                                              !read in the file 
    320      INTEGER, POINTER, DIMENSION(:) :: directemp              !contains listpoints directions 
     315     INTEGER, DIMENSION(nb_point_max) :: directemp              !contains listpoints directions 
    321316                                                              !read in the files 
    322317     LOGICAL :: llbon                                       ,&!local logical 
    323318                lldebug                                       !debug the section 
    324319     !!------------------------------------------------------------------------------------- 
    325      CALL wrk_alloc( nb_point_max, directemp ) 
    326320 
    327321     !open input file 
     
    495489     nb_sec = jsec-1   !number of section read in the file 
    496490 
    497      CALL wrk_dealloc( nb_point_max, directemp ) 
    498491     ! 
    499492  END SUBROUTINE readsec 
     
    521514                istart,iend      !first and last points selected in listpoint 
    522515     INTEGER :: jpoint           !loop on list points 
    523      INTEGER, POINTER, DIMENSION(:)   :: idirec !contains temporary sec%direction 
    524      INTEGER, POINTER, DIMENSION(:,:) :: icoord !contains temporary sec%listpoint 
     516     INTEGER, DIMENSION(nb_point_max)   :: idirec !contains temporary sec%direction 
     517     INTEGER, DIMENSION(2,nb_point_max) :: icoord !contains temporary sec%listpoint 
    525518     !---------------------------------------------------------------------------- 
    526      CALL wrk_alloc(    nb_point_max, idirec ) 
    527      CALL wrk_alloc( 2, nb_point_max, icoord ) 
    528519 
    529520     IF( ld_debug )WRITE(numout,*)'      -------------------------' 
     
    575566     ENDIF 
    576567 
    577      CALL wrk_dealloc(    nb_point_max, idirec ) 
    578      CALL wrk_dealloc( 2, nb_point_max, icoord ) 
    579568  END SUBROUTINE removepoints 
    580569 
     
    10191008     REAL(wp)              :: zslope             ! section's slope coeff 
    10201009     ! 
    1021      REAL(wp), POINTER, DIMENSION(:):: zsumclasses ! 1D workspace  
     1010     REAL(wp), DIMENSION(nb_type_class):: zsumclasses ! 1D workspace  
    10221011     !!-------------------------------------------------------------  
    1023      CALL wrk_alloc(nb_type_class , zsumclasses )   
    10241012 
    10251013     zsumclasses(:)=0._wp 
     
    11331121119   FORMAT(I8,1X,I8,1X,I4,1X,A30,1X,f9.2,1X,I4,3X,A8,1X,2F12.4,5X,3E15.6) 
    11341122 
    1135       CALL wrk_dealloc(nb_type_class , zsumclasses )   
    11361123      ! 
    11371124   END SUBROUTINE dia_dct_wri 
Note: See TracChangeset for help on using the changeset viewer.