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 7571 for branches/UKMO/dev_r5518_MEDUSA_optim_MG_MS_RH/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90 – NEMO

Ignore:
Timestamp:
2017-01-17T11:33:49+01:00 (7 years ago)
Author:
frrh
Message:

Commit first phase of changes - these work OK in a UKESM vn0.5
suite employing the GO6 package branch at:

branches/UKMO/dev_r5518_GO6_package@7206

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_MEDUSA_optim_MG_MS_RH/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90

    r7570 r7571  
    9393      !                                                         ! =-1 not cyclic 
    9494      LOGICAL                                 ::   cyclic       ! east-west cyclic or not 
    95       INTEGER,  DIMENSION(:,:,:), POINTER    ::   data_jpi     ! array of source integers 
    96       INTEGER,  DIMENSION(:,:,:), POINTER    ::   data_jpj     ! array of source integers 
    97       REAL(wp), DIMENSION(:,:,:), POINTER    ::   data_wgt     ! array of weights on model grid 
    98       REAL(wp), DIMENSION(:,:,:), POINTER    ::   fly_dta      ! array of values on input grid 
    99       REAL(wp), DIMENSION(:,:,:), POINTER    ::   col          ! temporary array for reading in columns 
     95      INTEGER,  DIMENSION(:,:,:), ALLOCATABLE ::   data_jpi     ! array of source integers 
     96      INTEGER,  DIMENSION(:,:,:), ALLOCATABLE ::   data_jpj     ! array of source integers 
     97      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   data_wgt     ! array of weights on model grid 
     98      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   fly_dta      ! array of values on input grid 
     99      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   col          ! temporary array for reading in columns 
    100100   END TYPE WGT 
    101101 
     
    688688      REAL(wp), POINTER, DIMENSION(:,:,:)     ::   dta_read  ! work space for global data 
    689689      !!--------------------------------------------------------------------- 
    690              
     690 
    691691      ipi = SIZE( dta, 1 ) 
    692692      ipj = 1 
     
    745745      INTEGER                           ::   ill          ! character length 
    746746      INTEGER                           ::   iv           ! indice of V component 
    747       REAL(wp), POINTER, DIMENSION(:,:) ::   utmp, vtmp   ! temporary arrays for vector rotation 
     747      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   utmp, vtmp   ! temporary arrays for vector rotation 
    748748      CHARACTER (LEN=100)               ::   clcomp       ! dummy weight name 
    749749      !!--------------------------------------------------------------------- 
    750750 
    751       CALL wrk_alloc( jpi,jpj, utmp, vtmp ) 
     751      ALLOCATE( utmp (1:jpi, 1:jpj) ) 
     752      ALLOCATE( vtmp (1:jpi, 1:jpj) ) 
    752753 
    753754      !! (sga: following code should be modified so that pairs arent searched for each time 
     
    786787       END DO 
    787788      ! 
    788       CALL wrk_dealloc( jpi,jpj, utmp, vtmp ) 
     789      DEALLOCATE (utmp, vtmp) 
    789790      ! 
    790791   END SUBROUTINE fld_rot 
     
    935936         END DO 
    936937      ENDIF 
    937        
     938 
    938939   END SUBROUTINE fld_fill 
    939940 
     
    10051006            WRITE(numout,*) '       not cyclical' 
    10061007         ENDIF 
    1007          IF( ASSOCIATED(ref_wgts(kw)%data_wgt) )  WRITE(numout,*) '       allocated' 
     1008         IF( ALLOCATED(ref_wgts(kw)%data_wgt) )  WRITE(numout,*) '       allocated' 
    10081009      END DO 
    10091010      ! 
     
    10261027      CHARACTER (len=5)                 ::   aname 
    10271028      INTEGER , DIMENSION(:), ALLOCATABLE ::   ddims 
    1028       INTEGER , POINTER, DIMENSION(:,:) ::   data_src 
    1029       REAL(wp), POINTER, DIMENSION(:,:) ::   data_tmp 
     1029      INTEGER , ALLOCATABLE, DIMENSION(:,:) ::   data_src 
     1030      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   data_tmp 
    10301031      LOGICAL                           ::   cyclical 
    10311032      INTEGER                           ::   zwrap      ! local integer 
    10321033      !!---------------------------------------------------------------------- 
    10331034      ! 
    1034       CALL wrk_alloc( jpi,jpj, data_src )   ! integer 
    1035       CALL wrk_alloc( jpi,jpj, data_tmp ) 
     1035      ALLOCATE(data_src(1:jpi, 1:jpj)) 
     1036      ALLOCATE(data_tmp(1:jpi, 1:jpj)) 
     1037 
    10361038      ! 
    10371039      IF( nxt_wgt > tot_wgts ) THEN 
     
    11521154      DEALLOCATE (ddims ) 
    11531155 
    1154       CALL wrk_dealloc( jpi,jpj, data_src )   ! integer 
    1155       CALL wrk_dealloc( jpi,jpj, data_tmp ) 
     1156      DEALLOCATE( data_src )   ! integer 
     1157      DEALLOCATE( data_tmp ) 
    11561158      ! 
    11571159   END SUBROUTINE fld_weight 
     
    12941296      INTEGER                                   ::   jpi1_lsm,jpi2_lsm,jpj1_lsm,jpj2_lsm   ! temporary indices 
    12951297      INTEGER                                   ::   itmpi,itmpj,itmpz                     ! lengths 
    1296        
     1298 
    12971299      !!---------------------------------------------------------------------- 
    12981300      ! 
Note: See TracChangeset for help on using the changeset viewer.