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 8373 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limitd_me.F90 – NEMO

Ignore:
Timestamp:
2017-07-25T19:44:54+02:00 (7 years ago)
Author:
clem
Message:

remove most of wrk_alloc

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limitd_me.F90

    r8341 r8373  
    110110      REAL(wp) ::   za, zfac              ! local scalar 
    111111      CHARACTER (len = 15) ::   fieldid 
    112       REAL(wp), POINTER, DIMENSION(:,:)   ::   closing_net     ! net rate at which area is removed    (1/s) 
     112      REAL(wp), DIMENSION(jpi,jpj)   ::   closing_net     ! net rate at which area is removed    (1/s) 
    113113                                                               ! (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 
     114      REAL(wp), DIMENSION(jpi,jpj)   ::   divu_adv        ! divu as implied by transport scheme  (1/s) 
     115      REAL(wp), DIMENSION(jpi,jpj)   ::   opning          ! rate of opening due to divergence/shear 
     116      REAL(wp), DIMENSION(jpi,jpj)   ::   closing_gross   ! rate at which area removed, not counting area of new ridges 
    117117      ! 
    118118      INTEGER, PARAMETER ::   nitermax = 20     
     
    121121      !!----------------------------------------------------------------------------- 
    122122      IF( nn_timing == 1 )  CALL timing_start('limitd_me') 
    123  
    124       CALL wrk_alloc( jpi,jpj, closing_net, divu_adv, opning, closing_gross ) 
    125123 
    126124      ! conservation test 
     
    288286      ! control prints 
    289287      IF( ln_ctl )       CALL lim_prt3D( 'limitd_me' ) 
    290  
    291       CALL wrk_dealloc( jpi, jpj, closing_net, divu_adv, opning, closing_gross ) 
    292288      ! 
    293289      IF( nn_timing == 1 )  CALL timing_stop('limitd_me') 
     
    303299      !!              participating in ridging and of the resulting ridges. 
    304300      !!---------------------------------------------------------------------! 
    305       INTEGER ::   ji,jj, jl    ! dummy loop indices 
     301      INTEGER  ::   ji,jj, jl    ! dummy loop indices 
    306302      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 ) 
     303      REAL(wp), DIMENSION(jpi,jpj,-1:jpl) ::   Gsum      ! Gsum(n) = sum of areas in categories 0 to n 
     304      !------------------------------------------------------------------------------! 
    311305 
    312306      Gstari     = 1.0/rn_gstar     
     
    477471      END DO 
    478472      ! 
    479       CALL wrk_dealloc( jpi,jpj,jpl+2, Gsum, kkstart = -1 ) 
    480473      ! 
    481474   END SUBROUTINE lim_itd_me_ridgeprep 
     
    502495      REAL(wp) ::   zwfx_snw         ! snow mass flux increment 
    503496 
    504       INTEGER , POINTER, DIMENSION(:) ::   indxi, indxj   ! compressed indices 
    505       REAL(wp), POINTER, DIMENSION(:) ::   zswitch, fvol   ! new ridge volume going to n2 
    506  
    507       REAL(wp), POINTER, DIMENSION(:) ::   afrac            ! fraction of category area ridged  
    508       REAL(wp), POINTER, DIMENSION(:) ::   ardg1 , ardg2    ! area of ice ridged & new ridges 
    509       REAL(wp), POINTER, DIMENSION(:) ::   vsrdg , esrdg    ! snow volume & energy of ridging ice 
     497      INTEGER , DIMENSION(jpij) ::   indxi, indxj   ! compressed indices 
     498      REAL(wp), DIMENSION(jpij) ::   zswitch, fvol   ! new ridge volume going to n2 
     499 
     500      REAL(wp), DIMENSION(jpij) ::   afrac            ! fraction of category area ridged  
     501      REAL(wp), DIMENSION(jpij) ::   ardg1 , ardg2    ! area of ice ridged & new ridges 
     502      REAL(wp), DIMENSION(jpij) ::   vsrdg , esrdg    ! snow volume & energy of ridging ice 
    510503      ! MV MP 2016 
    511       REAL(wp), POINTER, DIMENSION(:) ::   vprdg            ! pond volume of ridging ice 
    512       REAL(wp), POINTER, DIMENSION(:) ::   aprdg1           ! pond area of ridging ice 
    513       REAL(wp), POINTER, DIMENSION(:) ::   aprdg2           ! pond area of ridging ice 
     504      REAL(wp), DIMENSION(jpij) ::   vprdg            ! pond volume of ridging ice 
     505      REAL(wp), DIMENSION(jpij) ::   aprdg1           ! pond area of ridging ice 
     506      REAL(wp), DIMENSION(jpij) ::   aprdg2           ! pond area of ridging ice 
    514507      ! END MV MP 2016 
    515       REAL(wp), POINTER, DIMENSION(:) ::   dhr   , dhr2     ! hrmax - hrmin  &  hrmax^2 - hrmin^2 
    516  
    517       REAL(wp), POINTER, DIMENSION(:) ::   vrdg1   ! volume of ice ridged 
    518       REAL(wp), POINTER, DIMENSION(:) ::   vrdg2   ! volume of new ridges 
    519       REAL(wp), POINTER, DIMENSION(:) ::   vsw     ! volume of seawater trapped into ridges 
    520       REAL(wp), POINTER, DIMENSION(:) ::   srdg1   ! sal*volume of ice ridged 
    521       REAL(wp), POINTER, DIMENSION(:) ::   srdg2   ! sal*volume of new ridges 
    522       REAL(wp), POINTER, DIMENSION(:) ::   smsw    ! sal*volume of water trapped into ridges 
    523       REAL(wp), POINTER, DIMENSION(:) ::   oirdg1, oirdg2   ! ice age of ice ridged 
    524  
    525       REAL(wp), POINTER, DIMENSION(:) ::   afrft            ! fraction of category area rafted 
    526       REAL(wp), POINTER, DIMENSION(:) ::   arft1 , arft2    ! area of ice rafted and new rafted zone 
    527       REAL(wp), POINTER, DIMENSION(:) ::   virft , vsrft    ! ice & snow volume of rafting ice 
     508      REAL(wp), DIMENSION(jpij) ::   dhr   , dhr2     ! hrmax - hrmin  &  hrmax^2 - hrmin^2 
     509 
     510      REAL(wp), DIMENSION(jpij) ::   vrdg1   ! volume of ice ridged 
     511      REAL(wp), DIMENSION(jpij) ::   vrdg2   ! volume of new ridges 
     512      REAL(wp), DIMENSION(jpij) ::   vsw     ! volume of seawater trapped into ridges 
     513      REAL(wp), DIMENSION(jpij) ::   srdg1   ! sal*volume of ice ridged 
     514      REAL(wp), DIMENSION(jpij) ::   srdg2   ! sal*volume of new ridges 
     515      REAL(wp), DIMENSION(jpij) ::   smsw    ! sal*volume of water trapped into ridges 
     516      REAL(wp), DIMENSION(jpij) ::   oirdg1, oirdg2   ! ice age of ice ridged 
     517 
     518      REAL(wp), DIMENSION(jpij) ::   afrft            ! fraction of category area rafted 
     519      REAL(wp), DIMENSION(jpij) ::   arft1 , arft2    ! area of ice rafted and new rafted zone 
     520      REAL(wp), DIMENSION(jpij) ::   virft , vsrft    ! ice & snow volume of rafting ice 
    528521      ! MV MP 2016 
    529       REAL(wp), POINTER, DIMENSION(:) ::   vprft            ! pond volume of rafting ice 
    530       REAL(wp), POINTER, DIMENSION(:) ::   aprft1           ! pond area of rafted ice 
    531       REAL(wp), POINTER, DIMENSION(:) ::   aprft2           ! pond area of new rafted ice 
     522      REAL(wp), DIMENSION(jpij) ::   vprft            ! pond volume of rafting ice 
     523      REAL(wp), DIMENSION(jpij) ::   aprft1           ! pond area of rafted ice 
     524      REAL(wp), DIMENSION(jpij) ::   aprft2           ! pond area of new rafted ice 
    532525      ! END MV MP 2016 
    533       REAL(wp), POINTER, DIMENSION(:) ::   esrft , smrft    ! snow energy & salinity of rafting ice 
    534       REAL(wp), POINTER, DIMENSION(:) ::   oirft1, oirft2   ! ice age of ice rafted 
    535  
    536       REAL(wp), POINTER, DIMENSION(:,:) ::   eirft      ! ice energy of rafting ice 
    537       REAL(wp), POINTER, DIMENSION(:,:) ::   erdg1      ! enth*volume of ice ridged 
    538       REAL(wp), POINTER, DIMENSION(:,:) ::   erdg2      ! enth*volume of new ridges 
    539       REAL(wp), POINTER, DIMENSION(:,:) ::   ersw       ! enth of water trapped into ridges 
     526      REAL(wp), DIMENSION(jpij) ::   esrft , smrft    ! snow energy & salinity of rafting ice 
     527      REAL(wp), DIMENSION(jpij) ::   oirft1, oirft2   ! ice age of ice rafted 
     528 
     529      REAL(wp), DIMENSION(jpij,nlay_i) ::   eirft      ! ice energy of rafting ice 
     530      REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg1      ! enth*volume of ice ridged 
     531      REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg2      ! enth*volume of new ridges 
     532      REAL(wp), DIMENSION(jpij,nlay_i) ::   ersw       ! enth of water trapped into ridges 
    540533      !!---------------------------------------------------------------------- 
    541  
    542       CALL wrk_alloc( jpij,        indxi, indxj ) 
    543       CALL wrk_alloc( jpij,        zswitch, fvol ) 
    544       ! MV MP 2016 
    545       !CALL wrk_alloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
    546       CALL wrk_alloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, vprdg, aprdg1, aprdg2, dhr, dhr2 ) 
    547       ! END MV MP 2016 
    548       CALL wrk_alloc( jpij,        vrdg1, vrdg2, vsw  , srdg1, srdg2, smsw, oirdg1, oirdg2 ) 
    549       ! MV MP 2016 
    550       !CALL wrk_alloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
    551       CALL wrk_alloc(  jpij,        afrft, arft1, arft2, virft, vsrft, esrft, aprft1, aprft2) 
    552       CALL wrk_alloc ( jpij,        vprft, smrft, oirft1, oirft2 ) 
    553       ! END MV MP 2016 
    554       CALL wrk_alloc( jpij,nlay_i, eirft, erdg1, erdg2, ersw ) 
    555534 
    556535      !------------------------------------------------------------------------------- 
     
    794773      ! SIMIP diagnostics 
    795774      diag_dmi_dyn(:,:) = - wfx_dyn(:,:)     + rhoic * diag_trp_vi(:,:) 
    796       diag_dms_dyn(:,:) = - wfx_snw_dyn(:,:) + rhosn * diag_trp_vs(:,:) 
    797        
    798       ! 
    799       CALL wrk_dealloc( jpij,        indxi, indxj ) 
    800       CALL wrk_dealloc( jpij,        zswitch, fvol ) 
    801       ! MV MP 2016 
    802       !CALL wrk_dealloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
    803       CALL wrk_dealloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, vprdg, aprdg1, aprdg2,  dhr, dhr2 ) 
    804       ! END MV MP 2016 
    805       CALL wrk_dealloc( jpij,        vrdg1, vrdg2, vsw  , srdg1, srdg2, smsw, oirdg1, oirdg2 ) 
    806       ! MV MP 2016 
    807       !CALL wrk_dealloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
    808       CALL wrk_dealloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, aprft1, aprft2, vprft ) 
    809       CALL wrk_dealloc( jpij,        smrft, oirft1, oirft2 ) 
    810       CALL wrk_dealloc( jpij,nlay_i, eirft, erdg1, erdg2, ersw ) 
     775      diag_dms_dyn(:,:) = - wfx_snw_dyn(:,:) + rhosn * diag_trp_vs(:,:)       
    811776      ! 
    812777   END SUBROUTINE lim_itd_me_ridgeshift 
     
    831796      INTEGER             ::   numts_rm    ! number of time steps for the P smoothing 
    832797      REAL(wp)            ::   zp, z1_3    ! local scalars 
    833       REAL(wp), POINTER, DIMENSION(:,:) ::   zworka           ! temporary array used here 
    834       REAL(wp), POINTER, DIMENSION(:,:) ::   zstrp1, zstrp2   ! strength at previous time steps 
     798      REAL(wp), DIMENSION(jpi,jpj) ::   zworka           ! temporary array used here 
     799      REAL(wp), DIMENSION(jpi,jpj) ::   zstrp1, zstrp2   ! strength at previous time steps 
    835800      !!---------------------------------------------------------------------- 
    836  
    837       CALL wrk_alloc( jpi,jpj, zworka, zstrp1, zstrp2 ) 
    838801 
    839802      !------------------------------------------------------------------------------! 
     
    966929 
    967930      ENDIF ! ksmooth 
    968  
    969       CALL wrk_dealloc( jpi,jpj, zworka, zstrp1, zstrp2 ) 
    970931      ! 
    971932   END SUBROUTINE lim_itd_me_icestrength 
Note: See TracChangeset for help on using the changeset viewer.