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/LIM_SRC_3/limitd_me.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/LIM_SRC_3/limitd_me.F90

    r7753 r7910  
    2121   USE lbclnk           ! lateral boundary condition - MPP exchanges 
    2222   USE lib_mpp          ! MPP library 
    23    USE wrk_nemo         ! work arrays 
    2423 
    2524   USE in_out_manager   ! I/O manager 
     
    110109      REAL(wp) ::   za, zfac              ! local scalar 
    111110      CHARACTER (len = 15) ::   fieldid 
    112       REAL(wp), POINTER, DIMENSION(:,:)   ::   closing_net     ! net rate at which area is removed    (1/s) 
     111      REAL(wp), DIMENSION(jpi,jpj)   ::   closing_net     ! net rate at which area is removed    (1/s) 
    113112                                                               ! (ridging ice area - area of new ridges) / dt 
    114       REAL(wp), POINTER, DIMENSION(:,:)   ::   divu_adv        ! divu as implied by transport scheme  (1/s) 
    115       REAL(wp), POINTER, DIMENSION(:,:)   ::   opning          ! rate of opening due to divergence/shear 
    116       REAL(wp), POINTER, DIMENSION(:,:)   ::   closing_gross   ! rate at which area removed, not counting area of new ridges 
     113      REAL(wp), DIMENSION(jpi,jpj)   ::   divu_adv        ! divu as implied by transport scheme  (1/s) 
     114      REAL(wp), DIMENSION(jpi,jpj)   ::   opning          ! rate of opening due to divergence/shear 
     115      REAL(wp), DIMENSION(jpi,jpj)   ::   closing_gross   ! rate at which area removed, not counting area of new ridges 
    117116      ! 
    118117      INTEGER, PARAMETER ::   nitermax = 20     
     
    122121      IF( nn_timing == 1 )  CALL timing_start('limitd_me') 
    123122 
    124       CALL wrk_alloc( jpi,jpj, closing_net, divu_adv, opning, closing_gross ) 
    125123 
    126124      ! conservation test 
     
    289287      IF( ln_ctl )       CALL lim_prt3D( 'limitd_me' ) 
    290288 
    291       CALL wrk_dealloc( jpi, jpj, closing_net, divu_adv, opning, closing_gross ) 
    292289      ! 
    293290      IF( nn_timing == 1 )  CALL timing_stop('limitd_me') 
     
    305302      INTEGER ::   ji,jj, jl    ! dummy loop indices 
    306303      REAL(wp) ::   Gstari, astari, hrmean, zdummy   ! local scalar 
    307       REAL(wp), POINTER, DIMENSION(:,:,:) ::   Gsum      ! Gsum(n) = sum of areas in categories 0 to n 
    308       !------------------------------------------------------------------------------! 
    309  
    310       CALL wrk_alloc( jpi,jpj,jpl+2, Gsum, kkstart = -1 ) 
     304      REAL(wp), DIMENSION(jpi,jpj,-1:jpl) ::   Gsum      ! Gsum(n) = sum of areas in categories 0 to n 
     305      !------------------------------------------------------------------------------! 
     306 
    311307 
    312308      Gstari     = 1.0/rn_gstar     
     
    477473      END DO 
    478474      ! 
    479       CALL wrk_dealloc( jpi,jpj,jpl+2, Gsum, kkstart = -1 ) 
    480475      ! 
    481476   END SUBROUTINE lim_itd_me_ridgeprep 
     
    501496      REAL(wp) ::   hL, hR, farea    ! left and right limits of integration 
    502497 
    503       INTEGER , POINTER, DIMENSION(:) ::   indxi, indxj   ! compressed indices 
    504       REAL(wp), POINTER, DIMENSION(:) ::   zswitch, fvol   ! new ridge volume going to n2 
    505  
    506       REAL(wp), POINTER, DIMENSION(:) ::   afrac            ! fraction of category area ridged  
    507       REAL(wp), POINTER, DIMENSION(:) ::   ardg1 , ardg2    ! area of ice ridged & new ridges 
    508       REAL(wp), POINTER, DIMENSION(:) ::   vsrdg , esrdg    ! snow volume & energy of ridging ice 
    509       REAL(wp), POINTER, DIMENSION(:) ::   dhr   , dhr2     ! hrmax - hrmin  &  hrmax^2 - hrmin^2 
    510  
    511       REAL(wp), POINTER, DIMENSION(:) ::   vrdg1   ! volume of ice ridged 
    512       REAL(wp), POINTER, DIMENSION(:) ::   vrdg2   ! volume of new ridges 
    513       REAL(wp), POINTER, DIMENSION(:) ::   vsw     ! volume of seawater trapped into ridges 
    514       REAL(wp), POINTER, DIMENSION(:) ::   srdg1   ! sal*volume of ice ridged 
    515       REAL(wp), POINTER, DIMENSION(:) ::   srdg2   ! sal*volume of new ridges 
    516       REAL(wp), POINTER, DIMENSION(:) ::   smsw    ! sal*volume of water trapped into ridges 
    517       REAL(wp), POINTER, DIMENSION(:) ::   oirdg1, oirdg2   ! ice age of ice ridged 
    518  
    519       REAL(wp), POINTER, DIMENSION(:) ::   afrft            ! fraction of category area rafted 
    520       REAL(wp), POINTER, DIMENSION(:) ::   arft1 , arft2    ! area of ice rafted and new rafted zone 
    521       REAL(wp), POINTER, DIMENSION(:) ::   virft , vsrft    ! ice & snow volume of rafting ice 
    522       REAL(wp), POINTER, DIMENSION(:) ::   esrft , smrft    ! snow energy & salinity of rafting ice 
    523       REAL(wp), POINTER, DIMENSION(:) ::   oirft1, oirft2   ! ice age of ice rafted 
    524  
    525       REAL(wp), POINTER, DIMENSION(:,:) ::   eirft      ! ice energy of rafting ice 
    526       REAL(wp), POINTER, DIMENSION(:,:) ::   erdg1      ! enth*volume of ice ridged 
    527       REAL(wp), POINTER, DIMENSION(:,:) ::   erdg2      ! enth*volume of new ridges 
    528       REAL(wp), POINTER, DIMENSION(:,:) ::   ersw       ! enth of water trapped into ridges 
     498      INTEGER , DIMENSION(jpij) ::   indxi, indxj   ! compressed indices 
     499      REAL(wp), DIMENSION(jpij) ::   zswitch, fvol   ! new ridge volume going to n2 
     500 
     501      REAL(wp), DIMENSION(jpij) ::   afrac            ! fraction of category area ridged  
     502      REAL(wp), DIMENSION(jpij) ::   ardg1 , ardg2    ! area of ice ridged & new ridges 
     503      REAL(wp), DIMENSION(jpij) ::   vsrdg , esrdg    ! snow volume & energy of ridging ice 
     504      REAL(wp), DIMENSION(jpij) ::   dhr   , dhr2     ! hrmax - hrmin  &  hrmax^2 - hrmin^2 
     505 
     506      REAL(wp), DIMENSION(jpij) ::   vrdg1   ! volume of ice ridged 
     507      REAL(wp), DIMENSION(jpij) ::   vrdg2   ! volume of new ridges 
     508      REAL(wp), DIMENSION(jpij) ::   vsw     ! volume of seawater trapped into ridges 
     509      REAL(wp), DIMENSION(jpij) ::   srdg1   ! sal*volume of ice ridged 
     510      REAL(wp), DIMENSION(jpij) ::   srdg2   ! sal*volume of new ridges 
     511      REAL(wp), DIMENSION(jpij) ::   smsw    ! sal*volume of water trapped into ridges 
     512      REAL(wp), DIMENSION(jpij) ::   oirdg1, oirdg2   ! ice age of ice ridged 
     513 
     514      REAL(wp), DIMENSION(jpij) ::   afrft            ! fraction of category area rafted 
     515      REAL(wp), DIMENSION(jpij) ::   arft1 , arft2    ! area of ice rafted and new rafted zone 
     516      REAL(wp), DIMENSION(jpij) ::   virft , vsrft    ! ice & snow volume of rafting ice 
     517      REAL(wp), DIMENSION(jpij) ::   esrft , smrft    ! snow energy & salinity of rafting ice 
     518      REAL(wp), DIMENSION(jpij) ::   oirft1, oirft2   ! ice age of ice rafted 
     519 
     520      REAL(wp), DIMENSION(jpij,nlay_i) ::   eirft      ! ice energy of rafting ice 
     521      REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg1      ! enth*volume of ice ridged 
     522      REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg2      ! enth*volume of new ridges 
     523      REAL(wp), DIMENSION(jpij,nlay_i) ::   ersw       ! enth of water trapped into ridges 
    529524      !!---------------------------------------------------------------------- 
    530525 
    531       CALL wrk_alloc( jpij,        indxi, indxj ) 
    532       CALL wrk_alloc( jpij,        zswitch, fvol ) 
    533       CALL wrk_alloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
    534       CALL wrk_alloc( jpij,        vrdg1, vrdg2, vsw  , srdg1, srdg2, smsw, oirdg1, oirdg2 ) 
    535       CALL wrk_alloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
    536       CALL wrk_alloc( jpij,nlay_i, eirft, erdg1, erdg2, ersw ) 
    537526 
    538527      !------------------------------------------------------------------------------- 
     
    732721 
    733722      ! 
    734       CALL wrk_dealloc( jpij,        indxi, indxj ) 
    735       CALL wrk_dealloc( jpij,        zswitch, fvol ) 
    736       CALL wrk_dealloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
    737       CALL wrk_dealloc( jpij,        vrdg1, vrdg2, vsw  , srdg1, srdg2, smsw, oirdg1, oirdg2 ) 
    738       CALL wrk_dealloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
    739       CALL wrk_dealloc( jpij,nlay_i, eirft, erdg1, erdg2, ersw ) 
    740723      ! 
    741724   END SUBROUTINE lim_itd_me_ridgeshift 
     
    760743      INTEGER             ::   numts_rm    ! number of time steps for the P smoothing 
    761744      REAL(wp)            ::   zp, z1_3    ! local scalars 
    762       REAL(wp), POINTER, DIMENSION(:,:) ::   zworka           ! temporary array used here 
    763       REAL(wp), POINTER, DIMENSION(:,:) ::   zstrp1, zstrp2   ! strength at previous time steps 
     745      REAL(wp), DIMENSION(jpi,jpj) ::   zworka           ! temporary array used here 
     746      REAL(wp), DIMENSION(jpi,jpj) ::   zstrp1, zstrp2   ! strength at previous time steps 
    764747      !!---------------------------------------------------------------------- 
    765748 
    766       CALL wrk_alloc( jpi,jpj, zworka, zstrp1, zstrp2 ) 
    767749 
    768750      !------------------------------------------------------------------------------! 
     
    896878      ENDIF ! ksmooth 
    897879 
    898       CALL wrk_dealloc( jpi,jpj, zworka, zstrp1, zstrp2 ) 
    899880      ! 
    900881   END SUBROUTINE lim_itd_me_icestrength 
Note: See TracChangeset for help on using the changeset viewer.