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 2590 for branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

Ignore:
Timestamp:
2011-02-18T13:49:27+01:00 (13 years ago)
Author:
trackstand2
Message:

Merge branch 'dynamic_memory' into master-svn-dyn

Location:
branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD/trdicp.F90

    r2528 r2590  
    344344      !! ** Purpose :  write dynamic trends in ocean.output  
    345345      !!---------------------------------------------------------------------- 
     346      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     347      USE wrk_nemo, ONLY: zkepe => wrk_3d_1, zkx => wrk_3d_2, & 
     348                          zky => wrk_3d_3, zkz => wrk_3d_4 
    346349      INTEGER, INTENT(in) ::   kt                                  ! ocean time-step index 
    347350      !! 
    348351      INTEGER  ::   ji, jj, jk 
    349352      REAL(wp) ::   ze1e2w, zcof, zbe1ru, zbe2rv, zbtr, ztz, zth   !    "      scalars 
    350       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zkepe, zkx, zky, zkz   ! temporary arrays 
    351       !!---------------------------------------------------------------------- 
     353      !!---------------------------------------------------------------------- 
     354 
     355      IF(.NOT. wrk_use(3, 1,2,3,4))THEN 
     356         CALL ctl_stop('trd_dwr : requested workspace arrays unavailable.') 
     357         RETURN 
     358      END IF 
    352359 
    353360      ! I. Momentum trends 
     
    542549         ! 
    543550      ENDIF 
     551      ! 
     552      IF(.NOT. wrk_release(3, 1,2,3,4))THEN 
     553         CALL ctl_stop('trd_dwr : failed to release workspace arrays.') 
     554      END IF 
    544555      ! 
    545556   END SUBROUTINE trd_dwr 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld.F90

    r2528 r2590  
    4444   PUBLIC   trd_mld_init   ! routine called by opa.F90 
    4545   PUBLIC   trd_mld_zint   ! routine called by tracers routines 
     46   PUBLIC   trd_mld_alloc  ! routine called by nemogcm.F90 
    4647 
    4748   CHARACTER (LEN=40) ::  clhstnam         ! name of the trends NetCDF file 
    4849   INTEGER ::   nh_t, nmoymltrd 
    49    INTEGER ::   nidtrd, ndextrd1(jpi*jpj) 
     50   INTEGER ::   nidtrd 
     51   INTEGER, ALLOCATABLE, SAVE, DIMENSION(:) ::   ndextrd1 
    5052   INTEGER ::   ndimtrd1                         
    5153   INTEGER ::   ionce, icount                    
     
    6264 
    6365CONTAINS 
     66 
     67   FUNCTION trd_mld_alloc() 
     68      !!---------------------------------------------------------------------- 
     69      !!                  ***  ROUTINE trd_mld_alloc  *** 
     70      !!---------------------------------------------------------------------- 
     71      IMPLICIT none 
     72      INTEGER :: trd_mld_alloc 
     73      !!---------------------------------------------------------------------- 
     74 
     75      ALLOCATE(ndextrd1(jpi*jpj), Stat=trd_mld_alloc) 
     76 
     77      IF(trd_mld_alloc /= 0)THEN 
     78         CALL ctl_warn('trd_mld_alloc: failed to allocate array ndextrd1.') 
     79      END IF 
     80 
     81   END FUNCTION trd_mld_alloc 
    6482 
    6583   SUBROUTINE trd_mld_zint( pttrdmld, pstrdmld, ktrd, ctype ) 
     
    8199      !!            surface and the control surface is called "mixed-layer" 
    82100      !!---------------------------------------------------------------------- 
     101      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     102      USE wrk_nemo, ONLY: zvlmsk => wrk_2d_1 
     103      !! 
    83104      INTEGER, INTENT( in ) ::   ktrd                             ! ocean trend index 
    84105      CHARACTER(len=2), INTENT( in ) :: ctype                     ! surface/bottom (2D arrays) or 
     
    87108      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) ::  pstrdmld ! salinity trend  
    88109      INTEGER ::   ji, jj, jk, isum 
    89       REAL(wp), DIMENSION(jpi,jpj) ::  zvlmsk 
    90       !!---------------------------------------------------------------------- 
     110      !!---------------------------------------------------------------------- 
     111 
     112      IF(.NOT. wrk_use(2, 1))THEN 
     113         CALL ctl_stop('trd_mld_zint : requested workspace arrays unavailable.') 
     114         RETURN 
     115      END IF 
    91116 
    92117      ! I. Definition of control surface and associated fields 
     
    176201         smltrd(:,:,ktrd) = smltrd(:,:,ktrd) + pstrdmld(:,:,1) * wkx(:,:,1)             
    177202      END SELECT 
     203      ! 
     204      IF(.NOT. wrk_release(2, 1))THEN 
     205         CALL ctl_stop('trd_mld_zint : failed to release workspace arrays.') 
     206      END IF 
    178207      ! 
    179208   END SUBROUTINE trd_mld_zint 
     
    227256      !!       - See NEMO documentation (in preparation) 
    228257      !!---------------------------------------------------------------------- 
     258      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     259      USE wrk_nemo, ONLY: ztmltot => wrk_2d_1,  zsmltot => wrk_2d_2 ! dT/dt over the anlysis window (including Asselin) 
     260      USE wrk_nemo, ONLY: ztmlres => wrk_2d_3,  zsmlres => wrk_2d_4 ! residual = dh/dt entrainment term 
     261      USE wrk_nemo, ONLY: ztmlatf => wrk_2d_5,  zsmlatf => wrk_2d_6 ! needed for storage only 
     262      USE wrk_nemo, ONLY: ztmltot2 => wrk_2d_7, ztmlres2 => wrk_2d_8, ztmltrdm2 => wrk_2d_9    ! \  working arrays to diagnose the trends 
     263      USE wrk_nemo, ONLY: zsmltot2 => wrk_2d_10, zsmlres2 => wrk_2d_11, zsmltrdm2 => wrk_2d_12 !  > associated with the time meaned ML T & S 
     264      USE wrk_nemo, ONLY: ztmlatf2 => wrk_2d_13, zsmlatf2 => wrk_2d_14                         ! / 
     265      !! 
    229266      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    230267      !! 
     
    232269      LOGICAL :: lldebug = .TRUE. 
    233270      REAL(wp) :: zavt, zfn, zfn2 
    234       REAL(wp) ,DIMENSION(jpi,jpj) ::     & 
    235            ztmltot,  zsmltot,             & ! dT/dt over the anlysis window (including Asselin) 
    236            ztmlres,  zsmlres,             & ! residual = dh/dt entrainment term 
    237            ztmlatf,  zsmlatf,             & ! needed for storage only 
    238            ztmltot2, ztmlres2, ztmltrdm2, & ! \  working arrays to diagnose the trends 
    239            zsmltot2, zsmlres2, zsmltrdm2, & !  > associated with the time meaned ML T & S 
    240            ztmlatf2, zsmlatf2               ! / 
    241       REAL(wp), DIMENSION(jpi,jpj,jpltrd) ::  & 
     271      REAL(wp), POINTER, DIMENSION(:,:,:) ::  & 
    242272           ztmltrd2, zsmltrd2               ! only needed for mean diagnostics 
    243273#if defined key_dimgout 
     
    247277      !!---------------------------------------------------------------------- 
    248278       
     279      ! Check that the workspace arrays are all OK to be used 
     280      IF( (.NOT. wrk_use(2, 1,2,3,4,5,6,7,8,9,10,11,12,13,14)) .OR. & 
     281          (.NOT. wrk_use(3, 1,2)) )THEN 
     282         CALL ctl_stop('trd_mld : requested workspace arrays unavailable.') 
     283         RETURN 
     284      ELSE IF(jpltrd > jpk) 
     285         ! ARPDBG, is this reasonable or will this cause trouble in the future? 
     286         CALL ctl_stop('trd_mld : no. of mixed-layer trends (jpltrd) exceeds no. of model levels so cannot use 3D workspaces.') 
     287         RETURN          
     288      END IF 
     289      ! Set-up pointers into sub-arrays of 3d-workspaces 
     290      ztmltrd2 => wrk_3d_1(:,:,1:jpltrd) 
     291      zsmltrd2 => wrk_3d_2(:,:,1:jpltrd) 
    249292 
    250293      ! ====================================================================== 
     
    707750      IF( lrst_oce )   CALL trd_mld_rst_write( kt )  
    708751 
     752      IF( (.NOT. wrk_release(2, 1,2,3,4,5,6,7,8,9,10,11,12,13,14)) .OR. & 
     753          (.NOT. wrk_release(3, 1,2)) )THEN 
     754         CALL ctl_stop('trd_mld : failed to release workspace arrays.') 
     755      END IF 
     756 
    709757   END SUBROUTINE trd_mld 
    710758 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_oce.F90

    r2528 r2590  
    1111   PRIVATE 
    1212 
     13   ! Routine accessibility 
     14   PUBLIC trdmld_oce_alloc    ! Called in nemogcm.F90 
     15 
    1316#if defined key_trdmld 
    1417   LOGICAL, PUBLIC, PARAMETER ::   lk_trdmld = .TRUE.    !: ML trend flag 
     
    1821   !!* mixed layer trends indices 
    1922   INTEGER, PARAMETER, PUBLIC ::   jpltrd = 11    !: number of mixed-layer trends arrays 
    20    INTEGER, PUBLIC   &  
    21 #if !defined key_agrif 
    22       , PARAMETER  & 
    23 #endif 
    24 ::   jpktrd = jpk   !: max level for mixed-layer trends diag. 
     23   INTEGER, PUBLIC            ::   jpktrd         !: max level for mixed-layer trends diag. 
    2524   ! 
    2625   INTEGER, PUBLIC, PARAMETER ::   jpmld_xad =  1   !:  zonal       
     
    4645   CHARACTER(LEN=80) , PUBLIC :: clname, ctrd(jpltrd+1,2) 
    4746 
    48    INTEGER , PUBLIC, DIMENSION(jpi,jpj)     ::   nmld   !: mixed layer depth indexes  
    49    INTEGER , PUBLIC, DIMENSION(jpi,jpj)     ::   nbol   !: mixed-layer depth indexes when read from file 
     47   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   nmld   !: mixed layer depth indexes  
     48   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   nbol   !: mixed-layer depth indexes when read from file 
    5049 
    51    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   wkx    !: 
     50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wkx    !: 
    5251 
    53    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
     52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  & 
    5453      rmld   ,                      & !: mld depth (m) corresponding to nmld 
    5554      tml    , sml  ,               & !: \ "now" mixed layer temperature/salinity 
     
    6665      rmld_sum, rmldbn                !: needed to compute the leap-frog time mean of the ML depth 
    6766 
    68    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::  & 
     67   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  & 
    6968      tmlatfb, tmlatfn ,            & !: "before" Asselin contribution at begining of the averaging 
    7069      smlatfb, smlatfn,             & !: period (i.e. last contrib. from previous such period) and  
     
    7271      tmlatfm, smlatfm                !: accumulator for Asselin trends (needed for storage only) 
    7372 
    74    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpltrd) ::  & 
     73   REAL(wp), PUBLIC, DIMENSION(:,:,:) ::  & 
    7574      tmltrd,                       & !: \ physical contributions to the total trend (for T/S), 
    7675      smltrd,                       & !: / cumulated over the current analysis window 
     
    8786   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    8887   !!====================================================================== 
     88CONTAINS 
     89 
     90  FUNCTION trdmld_oce_alloc() 
     91     !!---------------------------------------------------------------------- 
     92     !!---------------------------------------------------------------------- 
     93     USE in_out_manager, ONLY: ctl_warn 
     94     IMPLICIT none 
     95     INTEGER :: trdmld_oce_alloc 
     96     INTEGER :: ierr(5) 
     97     !!---------------------------------------------------------------------- 
     98 
     99     ! Initialise jpktrd here as can no longer do it in MODULE body since 
     100     ! jpk is now a variable. 
     101     jpktrd = jpk   !: max level for mixed-layer trends diag. 
     102 
     103     ierr(:) = 0 
     104 
     105#if   defined  key_trdmld   ||   defined key_esopa 
     106     ALLOCATE(nmld(jpi,jpj), nbol(jpi,jpj),       & 
     107              wkx(jpi,jpj,jpk), rmld(jpi,jpj),    &  
     108              tml(jpi,jpj)    , sml(jpi,jpj),     &  
     109              tmlb(jpi,jpj)   , smlb(jpi,jpj) ,   & 
     110              tmlbb(jpi,jpj)  , smlbb(jpi,jpj),   & 
     111              Stat = ierr(1)) 
     112 
     113     ALLOCATE(tmlbn(jpi,jpj)  , smlbn(jpi,jpj),   & 
     114              tmltrdm(jpi,jpj), smltrdm(jpi,jpj), & 
     115              tml_sum(jpi,jpj), tml_sumb(jpi,jpj),& 
     116              tmltrd_atf_sumb(jpi,jpj), Stat=ierr(2)) 
     117 
     118     ALLOCATE(sml_sum(jpi,jpj), sml_sumb(jpi,jpj), & 
     119              smltrd_atf_sumb(jpi,jpj),            & 
     120              rmld_sum(jpi,jpj), rmldbn(jpi,jpj),  & 
     121              tmlatfb(jpi,jpj), tmlatfn(jpi,jpj),  &  
     122              Stat = ierr(3)) 
     123 
     124     ALLOCATE(smlatfb(jpi,jpj), smlatfn(jpi,jpj), &  
     125              tmlatfm(jpi,jpj), smlatfm(jpi,jpj), & 
     126              tmltrd(jpi,jpj,jpltrd),   smltrd(jpi,jpj,jpltrd), & 
     127              Stat=ierr(4)) 
     128 
     129     ALLOCATE(tmltrd_sum(jpi,jpj,jpltrd),tmltrd_csum_ln(jpi,jpj,jpltrd),      & 
     130              tmltrd_csum_ub(jpi,jpj,jpltrd), smltrd_sum(jpi,jpj,jpltrd),     & 
     131              smltrd_csum_ln(jpi,jpj,jpltrd), smltrd_csum_ub(jpi,jpj,jpltrd), & 
     132              Stat=ierr(5)) 
     133#endif 
     134 
     135     trdmld_oce_alloc = MAXVAL(ierr) 
     136 
     137    IF(trdmld_oce_alloc /= 0)THEN 
     138       CALL ctl_warn('trdmld_oce_alloc: failed to allocate arrays.') 
     139    END IF 
     140 
     141  END FUNCTION trdmld_oce_alloc 
     142 
    89143END MODULE trdmld_oce 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD/trdmod.F90

    r2528 r2590  
    5151      !!              integral constraints 
    5252      !!---------------------------------------------------------------------- 
     53      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     54      USE wrk_nemo, ONLY: ztswu => wrk_2d_1,  & 
     55                          ztswv => wrk_2d_2,  & 
     56                          ztbfu => wrk_2d_3,  & 
     57                          ztbfv => wrk_2d_4,  & 
     58                          z2dx  => wrk_2d_5,  & 
     59                          z2dy  => wrk_2d_6 
     60      IMPLICIT none 
    5361      INTEGER, INTENT( in ) ::   kt                                ! time step 
    5462      INTEGER, INTENT( in ) ::   ktrd                              ! tracer trend index 
    5563      CHARACTER(len=3), INTENT( in ) ::   ctype                    ! momentum or tracers trends type 'DYN'/'TRA' 
    56       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdx ! Temperature or U trend  
    57       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   ptrdy ! Salinity    or V trend 
     64      REAL(wp), DIMENSION(:,:,:), INTENT( inout ) ::   ptrdx ! Temperature or U trend  
     65      REAL(wp), DIMENSION(:,:,:), INTENT( inout ) ::   ptrdy ! Salinity    or V trend 
    5866      !! 
    5967      INTEGER ::   ji, jj 
    60       REAL(wp), DIMENSION(jpi,jpj) ::   ztswu, ztswv               ! 2D workspace 
    61       REAL(wp), DIMENSION(jpi,jpj) ::   ztbfu, ztbfv               ! 2D workspace 
    62       REAL(wp), DIMENSION(jpi,jpj) ::   z2dx, z2dy                 ! workspace arrays 
    63       !!---------------------------------------------------------------------- 
     68      !!---------------------------------------------------------------------- 
     69 
     70      IF(.not. wrk_use(2, 1,2,3,4,5,6))THEN 
     71         CALL ctl_error('trd_mod: Requested workspace arrays already in use.') 
     72         RETURN 
     73      END IF 
    6474 
    6575      z2dx(:,:)   = 0.e0   ;   z2dy(:,:)   = 0.e0                  ! initialization of workspace arrays 
     
    218228      ENDIF 
    219229      ! 
     230      IF(.not. wrk_release(2, 1,2,3,4,5,6))THEN 
     231         CALL ctl_error('trd_mod: Failed to release workspace arrays.') 
     232      END IF 
     233      ! 
    220234   END SUBROUTINE trd_mod 
    221235 
     
    231245CONTAINS 
    232246   SUBROUTINE trd_mod(ptrd3dx, ptrd3dy, ktrd , ctype, kt )   ! Empty routine 
    233       REAL    ::   ptrd3dx(:,:,:), ptrd3dy(:,:,:) 
    234       INTEGER ::   ktrd, kt                             
     247      REAL(wp) ::   ptrd3dx(:,:,:), ptrd3dy(:,:,:) 
     248      INTEGER  ::   ktrd, kt                             
    235249      CHARACTER(len=3) ::  ctype                   
    236250      WRITE(*,*) 'trd_3d: You should not have seen this print! error ?', ptrd3dx(1,1,1), ptrd3dy(1,1,1) 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD/trdtra.F90

    r2528 r2590  
    2121 
    2222   PUBLIC trd_tra          ! called by all  traXX modules 
     23   PUBLIC trd_tra_alloc    ! called by nemogcm.F90 
    2324  
    2425   !! * Module declaration 
    25    REAL(wp), DIMENSION(jpi,jpj,jpk), SAVE :: trdtx, trdty, trdt  !: 
     26   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: trdtx, trdty, trdt  !: 
    2627 
    2728   !! * Substitutions 
     
    3536 
    3637CONTAINS 
     38 
     39   FUNCTION trd_tra_alloc() 
     40      !!---------------------------------------------------------------------------- 
     41      !!                  ***  ROUTINE trd_tra_alloc  *** 
     42      !!---------------------------------------------------------------------------- 
     43      IMPLICIT none 
     44      INTEGER trd_tra_alloc 
     45      !!---------------------------------------------------------------------------- 
     46 
     47      ALLOCATE(trdtx(jpi,jpj,jpk), trdty(jpi,jpj,jpk), trdt(jpi,jpj,jpk), & 
     48               Stat=trd_tra_alloc) 
     49 
     50      IF(trd_tra_alloc /= 0)THEN 
     51         CALL ctl_warn('trd_tra_alloc: failed to allocate arrays.') 
     52      END IF 
     53 
     54    END FUNCTION trd_tra_alloc 
    3755 
    3856   SUBROUTINE trd_tra( kt, ctype, ktra, ktrd, ptrd, pun, ptra ) 
     
    5068      !!        nn_ctls > 1  : use fixed level surface jk = nn_ctls 
    5169      !!---------------------------------------------------------------------- 
     70      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     71      USE wrk_nemo, ONLY: ztrds => wrk_3d_1 
    5272      INTEGER                         , INTENT(in)           ::  kt      ! time step 
    5373      CHARACTER(len=3)                , INTENT(in)           ::  ctype   ! tracers trends type 'TRA'/'TRC' 
     
    5777      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL ::  pun     ! velocity  
    5878      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL ::  ptra    ! Tracer variable  
    59       !! 
    60       REAL(wp), DIMENSION(jpi,jpj,jpk) ::  ztrds    !   
    61       !!---------------------------------------------------------------------- 
     79      !!---------------------------------------------------------------------- 
     80 
     81      IF(.NOT. wrk_use(3, 1))THEN 
     82         CALL ctl_stop('trd_tra: requested workspace array unavailable.') 
     83         RETURN 
     84      END IF 
    6285 
    6386      ! Control of optional arguments 
     
    118141      ENDIF 
    119142      ! 
     143      IF(.NOT. wrk_release(3, 1))THEN 
     144         CALL ctl_stop('trd_tra: failed to release workspace array.') 
     145      END IF 
     146      ! 
    120147   END SUBROUTINE trd_tra 
    121148 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRD/trdvor.F90

    r2528 r2590  
    3737   PUBLIC   trd_vor_zint   ! routine called by dynamics routines 
    3838   PUBLIC   trd_vor_init   ! routine called by opa.F90 
    39  
    40    INTEGER ::   nh_t, nmoydpvor, nidvor, nhoridvor, ndexvor1(jpi*jpj), ndimvor1, icount   ! needs for IOIPSL output 
     39   PUBLIC   trd_vor_alloc  ! routine called by nemogcm.F90 
     40 
     41   INTEGER ::   nh_t, nmoydpvor, nidvor, nhoridvor, ndimvor1, icount   ! needs for IOIPSL output 
     42   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: ndexvor1 ! needed for IOIPSL output 
    4143   INTEGER ::   ndebug     ! (0/1) set it to 1 in case of problem to have more print 
    4244 
    43    REAL(wp), DIMENSION(jpi,jpj) ::   vor_avr      ! average 
    44    REAL(wp), DIMENSION(jpi,jpj) ::   vor_avrb     ! before vorticity (kt-1) 
    45    REAL(wp), DIMENSION(jpi,jpj) ::   vor_avrbb    ! vorticity at begining of the nwrite-1 timestep averaging period 
    46    REAL(wp), DIMENSION(jpi,jpj) ::   vor_avrbn    ! after vorticity at time step after the 
    47    REAL(wp), DIMENSION(jpi,jpj) ::   rotot        ! begining of the NWRITE-1 timesteps 
    48    REAL(wp), DIMENSION(jpi,jpj) ::   vor_avrtot   ! 
    49    REAL(wp), DIMENSION(jpi,jpj) ::   vor_avrres   ! 
    50  
    51    REAL(wp), DIMENSION(jpi,jpj,jpltot_vor) ::   vortrd  ! curl of trends 
     45   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,  :) ::   vor_avr      ! average 
     46   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,  :) ::   vor_avrb     ! before vorticity (kt-1) 
     47   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,  :) ::   vor_avrbb    ! vorticity at begining of the nwrite-1 timestep averaging period 
     48   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,  :) ::   vor_avrbn    ! after vorticity at time step after the 
     49   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,  :) ::   rotot        ! begining of the NWRITE-1 timesteps 
     50   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,  :) ::   vor_avrtot   ! 
     51   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,  :) ::   vor_avrres   ! 
     52 
     53   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   vortrd  ! curl of trends 
    5254          
    5355   CHARACTER(len=12) ::   cvort 
     
    6365   !!---------------------------------------------------------------------- 
    6466CONTAINS 
     67 
     68   FUNCTION trd_vor_alloc() 
     69      !!---------------------------------------------------------------------------- 
     70      !!                  ***  ROUTINE trd_vor_alloc  *** 
     71      !!---------------------------------------------------------------------------- 
     72      IMPLICIT none 
     73      INTEGER trd_vor_alloc 
     74      !!---------------------------------------------------------------------------- 
     75 
     76      ALLOCATE(vor_avr(jpi,jpj),    vor_avrb(jpi,jpj), vor_avrbb(jpi,jpj),  & 
     77               vor_avrbn(jpi,jpj),  rotot(jpi,jpj),    vor_avrtot(jpi,jpj), & 
     78               vor_avrres(jpi,jpj), vortrd(jpi,jpj,jpltot_vor),             & 
     79               ndexvor1(jpi*jpj),   Stat=trd_vor_alloc) 
     80 
     81      IF(trd_vor_alloc /= 0)THEN 
     82         CALL ctl_warn('trd_vor_alloc: failed to allocate arrays') 
     83      END IF 
     84 
     85   END FUNCTION trd_vor_alloc 
    6586 
    6687   SUBROUTINE trd_vor_zint_2d( putrdvor, pvtrdvor, ktrd ) 
     
    91112      !!      trends output in netCDF format using ioipsl 
    92113      !!---------------------------------------------------------------------- 
     114      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     115      USE wrk_nemo, ONLY: zudpvor => wrk_2d_1, &   ! total cmulative trends 
     116                          zvdpvor => wrk_2d_2 
     117      !! 
    93118      INTEGER                     , INTENT(in   ) ::   ktrd       ! ocean trend index 
    94119      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   putrdvor   ! u vorticity trend  
     
    97122      INTEGER ::   ji, jj       ! dummy loop indices 
    98123      INTEGER ::   ikbu, ikbv   ! local integers 
    99       REAL(wp), DIMENSION(jpi,jpj) ::   zudpvor, zvdpvor   ! total cmulative trends 
    100       !!---------------------------------------------------------------------- 
     124      !!---------------------------------------------------------------------- 
     125 
     126      IF(.NOT. wrk_use(2, 1,2))THEN 
     127         CALL ctl_stop('trd_vor_zint_2d : requested workspace arrays unavailable.') 
     128         RETURN 
     129      END IF 
    101130 
    102131      ! Initialization 
     
    147176      ENDIF 
    148177      ! 
     178      IF(.NOT. wrk_release(2, 1,2))THEN 
     179         CALL ctl_stop('trd_vor_zint_2d : failed to release workspace arrays.') 
     180      END IF 
     181      ! 
    149182   END SUBROUTINE trd_vor_zint_2d 
    150183 
     
    177210      !!      trends output in netCDF format using ioipsl 
    178211      !!---------------------------------------------------------------------- 
     212      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     213      USE wrk_nemo, ONLY: zubet   => wrk_2d_1,   zvbet => wrk_2d_2   ! Beta.V  
     214      USE wrk_nemo, ONLY: zudpvor => wrk_2d_3, zvdpvor => wrk_2d_4   ! total cmulative trends 
     215      !! 
    179216      INTEGER                         , INTENT(in   ) ::   ktrd       ! ocean trend index 
    180217      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   putrdvor   ! u vorticity trend  
     
    182219      !! 
    183220      INTEGER ::   ji, jj, jk 
    184       REAL(wp), DIMENSION(jpi,jpj) ::   zubet  , zvbet     ! Beta.V  
    185       REAL(wp), DIMENSION(jpi,jpj) ::   zudpvor, zvdpvor   ! total cmulative trends 
    186221      !!---------------------------------------------------------------------- 
    187222      
     223      IF(.NOT. wrk_use(2, 1,2,3,4))THEN 
     224         CALL ctl_stop('trd_vor_zint_3d : requested workspace arrays unavailable.') 
     225         RETURN 
     226      END IF 
     227 
    188228      ! Initialization 
    189229      zubet  (:,:) = 0._wp 
     
    248288      ENDIF 
    249289      ! 
     290      IF(.NOT. wrk_release(2, 1,2,3,4))THEN 
     291         CALL ctl_stop('trd_vor_zint_3d : failed to release workspace arrays.') 
     292      END IF 
     293      ! 
    250294   END SUBROUTINE trd_vor_zint_3d 
    251295 
     
    258302      !!               and make outputs (NetCDF or DIMG format) 
    259303      !!---------------------------------------------------------------------- 
     304      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     305      USE wrk_nemo, ONLY: zun => wrk_2d_1, zvn => wrk_2d_2 ! 2D workspace 
     306      !! 
    260307      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    261308      !! 
     
    263310      INTEGER  ::   it, itmod        ! local integers 
    264311      REAL(wp) ::   zmean            ! local scalars 
    265       REAL(wp), DIMENSION(jpi,jpj) ::   zun, zvn   ! 2D workspace 
    266       !!---------------------------------------------------------------------- 
     312      !!---------------------------------------------------------------------- 
     313 
     314      IF(.NOT. wrk_use(2, 1,2))THEN 
     315         CALL ctl_stop('trd_vor : requested workspace arrays unavailable.') 
     316         RETURN 
     317      END IF 
    267318 
    268319      !  ================= 
     
    431482      IF( kt == nitend )   CALL histclo( nidvor ) 
    432483      ! 
     484      IF(.NOT. wrk_release(2, 1,2))THEN 
     485         CALL ctl_stop('trd_vor : failed to release workspace arrays.') 
     486      END IF 
     487      ! 
    433488   END SUBROUTINE trd_vor 
    434489 
Note: See TracChangeset for help on using the changeset viewer.