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 7911 for branches/2017/dev_r7881_no_wrk_alloc – NEMO

Ignore:
Timestamp:
2017-04-13T17:13:42+02:00 (7 years ago)
Author:
timgraham
Message:

Minor bug fixes with pointers in bdy and also remove wrk_alloc calls in test cases

Location:
branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/CONFIG/TEST_CASES/SAS_BIPER/MY_SRC/usrdef_sbc.F90

    r7377 r7911  
    9999      !! ** Purpose :   provide the surface boundary (flux) condition over sea-ice 
    100100      !!--------------------------------------------------------------------- 
    101       REAL(wp), DIMENSION(:,:), POINTER ::   zsnw       ! snw distribution after wind blowing 
     101      REAL(wp), DIMENSION(jpi,jpj) ::   zsnw       ! snw distribution after wind blowing 
    102102      INTEGER, INTENT(in) ::   kt   ! ocean time step 
    103103      !!--------------------------------------------------------------------- 
    104       CALL wrk_alloc( jpi,jpj, zsnw ) 
    105104      ! 
    106105      IF( kt==nit000 .AND. lwp)   WRITE(numout,*)' usrdef_sbc_ice : SAS_BIPER case: NO flux forcing' 
     
    140139      fr2_i0(:,:) = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice ) 
    141140 
    142       CALL wrk_dealloc( jpi,jpj, zsnw ) 
    143  
    144141   END SUBROUTINE usrdef_sbc_ice_flx 
    145142 
  • branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/CONFIG/TEST_CASES/WAD/MY_SRC/bdyini.F90

    r7610 r7911  
    151151      INTEGER :: com_east_b, com_west_b, com_south_b, com_north_b  ! Flags for boundaries receiving 
    152152      INTEGER :: iw_b(4), ie_b(4), is_b(4), in_b(4)                ! Arrays for neighbours coordinates 
    153       REAL(wp), POINTER, DIMENSION(:,:)       ::   zfmask  ! temporary fmask array excluding coastal boundary condition (shlat) 
     153      REAL(wp), DIMENSION(jpi,jpj)            ::   zfmask  ! temporary fmask array excluding coastal boundary condition (shlat) 
    154154      !! 
    155155      CHARACTER(LEN=1)                     ::   ctypebdy   !     -        -  
     
    12171217      ! For the flagu/flagv calculation below we require a version of fmask without 
    12181218      ! the land boundary condition (shlat) included: 
    1219       CALL wrk_alloc(jpi,jpj,  zfmask )  
    12201219      DO ij = 2, jpjm1 
    12211220         DO ii = 2, jpim1 
     
    13451344      !-------- 
    13461345      IF( nb_bdy>0 )   DEALLOCATE( nbidta, nbjdta, nbrdta ) 
    1347       ! 
    1348       CALL wrk_dealloc(jpi,jpj,   zfmask )  
    13491346      ! 
    13501347      IF( nn_timing == 1 )   CALL timing_stop('bdy_segs') 
  • branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r7910 r7911  
    140140      INTEGER , POINTER  ::  nbi, nbj, nbr                 ! short cuts 
    141141      REAL(wp), POINTER  ::  flagu, flagv                  !    -   - 
    142       REAL(wp), POINTER, DIMENSION(:,:)       ::   pmask    ! pointer to 2D mask fields 
     142      REAL(wp), DIMENSION(jpi,jpj)       ::   pmask        ! 2D mask fields 
    143143      REAL(wp) ::   zefl, zwfl, znfl, zsfl                 ! local scalars 
    144144      INTEGER, DIMENSION (2)                  ::   kdimsz 
     
    12411241         DO igrd = 1,jpbgrd  
    12421242            SELECT CASE( igrd ) 
    1243                CASE( 1 )   ;   pmask => umask   (:,:,1)   ;   i_offset = 0 
    1244                CASE( 2 )   ;   pmask => bdytmask(:,:)     ;   i_offset = 1 
    1245                CASE( 3 )   ;   pmask => zfmask  (:,:)     ;   i_offset = 0 
     1243               CASE( 1 )   ;   pmask = umask   (:,:,1)   ;   i_offset = 0 
     1244               CASE( 2 )   ;   pmask = bdytmask(:,:)     ;   i_offset = 1 
     1245               CASE( 3 )   ;   pmask = zfmask  (:,:)     ;   i_offset = 0 
    12461246            END SELECT  
    12471247            icount = 0 
     
    12761276         DO igrd = 1, jpbgrd  
    12771277            SELECT CASE( igrd ) 
    1278                CASE( 1 )   ;   pmask => vmask (:,:,1)   ;   j_offset = 0 
    1279                CASE( 2 )   ;   pmask => zfmask(:,:)     ;   j_offset = 0 
    1280                CASE( 3 )   ;   pmask => bdytmask        ;   j_offset = 1 
     1278               CASE( 1 )   ;   pmask = vmask (:,:,1)   ;   j_offset = 0 
     1279               CASE( 2 )   ;   pmask = zfmask(:,:)     ;   j_offset = 0 
     1280               CASE( 3 )   ;   pmask = bdytmask        ;   j_offset = 1 
    12811281            END SELECT  
    12821282            icount = 0 
  • branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r7910 r7911  
    547547      REAL(wp), DIMENSION(jpi,jpj) ::   zgphi1        ! Model latitudes for prof variable 1 
    548548      REAL(wp), DIMENSION(jpi,jpj) ::   zgphi2        ! Model latitudes for prof variable 2 
    549 #if ! defined key_lim2 ! defined key_lim3 
     549#if ! defined key_lim2 && ! defined key_lim3 
    550550      REAL(wp), DIMENSION(jpi,jpj) :: frld 
    551551#endif 
Note: See TracChangeset for help on using the changeset viewer.