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 2609 for branches – NEMO

Changeset 2609 for branches


Ignore:
Timestamp:
2011-02-22T18:14:30+01:00 (13 years ago)
Author:
trackstand2
Message:

Replaced local workspace arrays with those in wrk_nemo module

Location:
branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcbio.F90

    r2528 r2609  
    6060      !!              for passive tracers are saved for futher diagnostics. 
    6161      !!--------------------------------------------------------------------- 
     62      USE wrk_nemo, ONLY: wrk_use,  wrk_release 
     63      USE wrk_nemo, ONLY: wrk_3d_2, wrk_4d_1 
     64      !! 
    6265      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index       
    6366      !! 
     
    7578#endif 
    7679#if defined key_diatrc && defined key_iomput 
    77       REAL(wp), DIMENSION(jpi,jpj,17)    :: zw2d 
    78       REAL(wp), DIMENSION(jpi,jpj,jpk,3) :: zw3d 
     80      REAL(wp), POINTER,   DIMENSION(:,:,:) :: zw2d 
     81      REAL(wp), POINTER, DIMENSION(:,:,:,:) :: zw3d 
    7982#endif 
    8083      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   ztrbio 
    8184      CHARACTER (len=25) :: charout 
    8285      !!--------------------------------------------------------------------- 
     86 
     87#if defined key_diatrc && defined key_iomput 
     88      IF( (.NOT. wrk_use(3, 2)) .OR. (.NOT. wrk_use(4, 1)) )THEN 
     89         CALL ctl_stop('trc_bio : requested workspace arrays unavailable.') 
     90         RETURN 
     91      END IF 
     92      ! Set-up pointers into sub-arrays of workspaces 
     93      zw2d => wrk_3d_2(:,:,1:17) 
     94      zw3d => wrk_4d_1(:,:,:,1:3) 
     95#endif 
    8396 
    8497      IF( kt == nit000 ) THEN 
     
    485498         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    486499      ENDIF 
    487  
     500      ! 
     501#if defined key_diatrc && defined key_iomput 
     502      IF( (.NOT. wrk_release(3, 2)) .OR. (.NOT. wrk_release(4, 1)) )THEN 
     503         CALL ctl_stop('trc_bio : failed to release workspace arrays.') 
     504      END IF 
     505#endif 
     506      ! 
    488507   END SUBROUTINE trc_bio 
    489508 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcini_lobster.F90

    r2528 r2609  
    4343      !! ** purpose :   specific initialisation for LOBSTER bio-model 
    4444      !!---------------------------------------------------------------------- 
     45      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     46      USE wrk_nemo, ONLY: zrro => wrk_2d_1, zdm0 => wrk_3d_1 
     47      !! 
    4548      INTEGER  ::   ji, jj, jk, jn 
    4649      REAL(wp) ::   ztest, zfluo, zfluu 
    47       REAL(wp), DIMENSION(jpi,jpj)     ::   zrro 
    48       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdm0 
    49       !!---------------------------------------------------------------------- 
     50      !!---------------------------------------------------------------------- 
     51 
     52      IF( (.NOT. wrk_use(2, 1)) .OR. (.NOT. wrk_use(3, 1)) )THEN 
     53         CALL ctl_stop('trc_ini_lobster : requested workspace arrays unavailable.') 
     54         RETURN 
     55      END IF 
    5056 
    5157      !  Control consitency 
     
    253259      IF(lwp) WRITE(numout,*) ' ' 
    254260 
     261      IF( (.NOT. wrk_release(2, 1)) .OR. (.NOT. wrk_release(3, 1)) )THEN 
     262         CALL ctl_stop('trc_ini_lobster : failed to release workspace arrays.') 
     263      END IF 
    255264 
    256265   END SUBROUTINE trc_ini_lobster 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcopt.F90

    r2528 r2609  
    5252      !!                xze    ??? 
    5353      !!--------------------------------------------------------------------- 
     54      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     55      USE wrk_nemo, ONLY: zpar100 => wrk_2d_1, & ! irradiance at euphotic layer depth 
     56                          zpar0m  => wrk_2d_2    ! irradiance just below the surface 
     57      USE wrk_nemo, ONLY: zparr => wrk_3d_2, &   ! red and green compound of par 
     58                          zparg => wrk_3d_3 
     59      !! 
    5460      INTEGER, INTENT( in ) ::   kt   ! index of the time stepping 
    5561      !! 
     
    5965      REAL(wp) ::   zkr, zkg            ! total absorption coefficient in red and green 
    6066      REAL(wp) ::   zcoef               ! temporary scalar 
    61       REAL(wp), DIMENSION(jpi,jpj)     ::   zpar100         ! irradiance at euphotic layer depth 
    62       REAL(wp), DIMENSION(jpi,jpj)     ::   zpar0m          ! irradiance just below the surface 
    63       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zparr, zparg    ! red and green compound of par 
    6467 
    6568      !!--------------------------------------------------------------------- 
     69 
     70      IF( (.NOT. wrk_use(2, 1,2)) .OR. (.NOT. wrk_use(3, 2,3)) )THEN 
     71         CALL ctl_stop('trc_opt : requested workspace arrays unavailable.') 
     72         RETURN 
     73      END IF 
    6674 
    6775      IF( kt == nit000 ) THEN 
     
    130138      ENDIF 
    131139      ! 
     140      IF( (.NOT. wrk_release(2, 1,2)) .OR. (.NOT. wrk_release(3, 2,3)) )THEN 
     141         CALL ctl_stop('trc_opt : failed to release workspace arrays.') 
     142      END IF 
     143      ! 
    132144   END SUBROUTINE trc_opt 
    133145 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcsed.F90

    r2528 r2609  
    5656      !!              trend of passive tracers is saved for futher diagnostics. 
    5757      !!--------------------------------------------------------------------- 
     58      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     59      USE wrk_nemo, ONLY: zwork => wrk_3d_2 
     60      USE wrk_nemo, ONLY: zw2d  => wrk_2d_1 ! only used (if defined  
     61                                            ! key_diatrc && defined key_iomput) 
     62      !! 
    5863      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index       
    5964      !! 
    6065      INTEGER  ::   ji, jj, jk, jl 
    6166      REAL(wp) ::   ztra 
    62       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwork 
    63 #if defined key_diatrc && defined key_iomput 
    64       REAL(wp), DIMENSION(jpi,jpj) ::  zw2d 
    65 #endif 
    6667      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrbio 
    6768      CHARACTER (len=25) :: charout 
    6869      !!--------------------------------------------------------------------- 
     70 
     71      IF( (.NOT. wrk_use(3,2)) .OR. (.NOT. wrk_use(2,1)) )THEN 
     72         CALL ctl_stop('trc_sed : requested workspace arrays unavailable.') 
     73         RETURN 
     74      END IF 
    6975 
    7076      IF( kt == nit000 ) THEN 
     
    144150      ENDIF 
    145151 
     152      IF( (.NOT. wrk_release(3,2)) .OR. (.NOT. wrk_release(2,1)) )THEN 
     153         CALL ctl_stop('trc_sed : failed to release workspace arrays.') 
     154      END IF 
     155 
    146156   END SUBROUTINE trc_sed 
    147157 
  • branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcsms_lobster.F90

    r2528 r2609  
    4545      !! 
    4646      !! ** Method  : - ??? 
    47       !! ------------------------------------------------------------------------------------- 
     47      !! -------------------------------------------------------------------- 
     48      USE wrk_nemo, ONLY: wrk_use, wrk_release 
     49      USE wrk_nemo, ONLY: ztrlob => wrk_3d_1   ! used for lobster sms trends 
     50      !! 
    4851      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index       
    4952      INTEGER :: jn 
    50       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrlob   ! used for lobster sms trends 
    51       !! 
     53      !! -------------------------------------------------------------------- 
     54 
     55      IF(.NOT. wrk_use(3,1))THEN 
     56         CALL ctl_stop('trc_sms_lobster : requested workspace array unavailable.') 
     57         RETURN 
     58      END IF 
    5259 
    5360      CALL trc_opt( kt )      ! optical model 
     
    6471 
    6572      IF( lk_trdmld_trc )  CALL trd_mld_bio( kt )   ! trends: Mixed-layer 
     73 
     74      IF(.NOT. wrk_release(3,1))THEN 
     75         CALL ctl_stop('trc_sms_lobster : failed to release workspace array.') 
     76      END IF 
    6677 
    6778   END SUBROUTINE trc_sms_lobster 
Note: See TracChangeset for help on using the changeset viewer.