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 3294 for trunk/NEMOGCM/NEMO/OPA_SRC/SOL – NEMO

Ignore:
Timestamp:
2012-01-28T17:44:18+01:00 (12 years ago)
Author:
rblod
Message:

Merge of 3.4beta into the trunk

Location:
trunk/NEMOGCM/NEMO/OPA_SRC/SOL
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/SOL/solmat.F90

    r2715 r3294  
    3131   USE lib_mpp         ! distributed memory computing 
    3232   USE in_out_manager  ! I/O manager 
     33   USE timing          ! timing 
    3334 
    3435   IMPLICIT NONE 
     
    6465      REAL(wp) ::   z2dt, zcoef 
    6566      !!---------------------------------------------------------------------- 
    66  
     67      ! 
     68      IF( nn_timing == 1 )  CALL timing_start('sol_mat') 
     69      ! 
    6770       
    6871      ! 1. Construction of the matrix 
     
    297300      gccd (:,:) = 0.e0 
    298301      !  
     302      IF( nn_timing == 1 )  CALL timing_stop('sol_mat') 
     303      ! 
    299304   END SUBROUTINE sol_mat 
    300305 
  • trunk/NEMOGCM/NEMO/OPA_SRC/SOL/solpcg.F90

    r2715 r3294  
    1414   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    1515   USE in_out_manager  ! I/O manager 
    16    USE lib_fortran 
     16   USE lib_fortran     ! Fortran routines library 
     17   USE wrk_nemo        ! Memory allocation 
     18   USE timing          ! Timing 
    1719 
    1820   IMPLICIT NONE 
     
    8385      !!        !  08-01  (R. Benshila) mpp optimization 
    8486      !!---------------------------------------------------------------------- 
    85       USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released 
    86       USE wrk_nemo, ONLY:   zgcr => wrk_2d_1 
    8787      !! 
    8888      INTEGER, INTENT(inout) ::   kindic   ! solver indicator, < 0 if the conver- 
     
    9393      REAL(wp) ::   zgcad        ! temporary scalars 
    9494      REAL(wp), DIMENSION(2) ::   zsum 
     95      REAL(wp), POINTER, DIMENSION(:,:) ::   zgcr 
    9596      !!---------------------------------------------------------------------- 
    96        
    97       IF( wrk_in_use(2, 1) )THEN 
    98          CALL ctl_stop('sol_pcg: requested workspace array is unavailable')   ;   RETURN 
    99       ENDIF 
    100  
     97      ! 
     98      IF( nn_timing == 1 )  CALL timing_start('sol_pcg') 
     99      ! 
     100      CALL wrk_alloc( jpi, jpj, zgcr ) 
     101      ! 
    101102      ! Initialization of the algorithm with standard PCG 
    102103      ! ------------------------------------------------- 
     
    209210      CALL lbc_lnk( gcx, c_solver_pt, 1. )      ! Output in gcx with lateral b.c. applied 
    210211      !  
    211       IF( wrk_not_released(2, 1) )   CALL ctl_stop('sol_pcg: failed to release workspace array') 
     212      CALL wrk_dealloc( jpi, jpj, zgcr ) 
     213      ! 
     214      IF( nn_timing == 1 )  CALL timing_stop('sol_pcg') 
    212215      ! 
    213216   END SUBROUTINE sol_pcg 
  • trunk/NEMOGCM/NEMO/OPA_SRC/SOL/solsor.F90

    r2715 r3294  
    2222   USE lib_mpp         ! distributed memory computing 
    2323   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    24    USE lib_fortran 
     24   USE lib_fortran     ! Fortran routines library 
     25   USE wrk_nemo        ! Memory allocation 
     26   USE timing          ! Timing 
    2527 
    2628   IMPLICIT NONE 
     
    5759      !!                Beare and Stevens 1997 Ann. Geophysicae 15, 1369-1377 
    5860      !!---------------------------------------------------------------------- 
    59       USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released 
    60       USE wrk_nemo, ONLY:   ztab => wrk_2d_1    ! 2D workspace 
    6161      !! 
    6262      INTEGER, INTENT(inout) ::   kindic   ! solver indicator, < 0 if the convergence is not reached: 
     
    6666      INTEGER  ::   ishift, icount, ijmppodd, ijmppeven, ijpr2d   ! local integers 
    6767      REAL(wp) ::   ztmp, zres, zres2                             ! local scalars 
     68      REAL(wp), POINTER, DIMENSION(:,:) ::   ztab                 ! 2D workspace 
    6869      !!---------------------------------------------------------------------- 
    69        
    70       IF( wrk_in_use(2, 1) )THEN 
    71          CALL ctl_stop('sol_sor: requested workspace array is unavailable')   ;   RETURN 
    72       ENDIF 
    73  
     70      ! 
     71      IF( nn_timing == 1 )  CALL timing_start('sol_sor') 
     72      ! 
     73      CALL wrk_alloc( jpi, jpj, ztab ) 
     74      ! 
    7475      ijmppeven = MOD( nimpp+njmpp+jpr2di+jpr2dj   , 2 ) 
    7576      ijmppodd  = MOD( nimpp+njmpp+jpr2di+jpr2dj+1 , 2 ) 
     
    167168      !  ------------- 
    168169      CALL lbc_lnk_e( gcx, c_solver_pt, 1. )    ! boundary conditions 
    169       !  
    170       IF( wrk_not_released(2, 1) )   CALL ctl_stop('sol_sor: failed to release workspace array') 
     170      ! 
     171      CALL wrk_dealloc( jpi, jpj, ztab ) 
     172      ! 
     173      IF( nn_timing == 1 )  CALL timing_stop('sol_sor') 
    171174      ! 
    172175   END SUBROUTINE sol_sor 
  • trunk/NEMOGCM/NEMO/OPA_SRC/SOL/solver.F90

    r2715 r3294  
    2323   USE dynspg_oce      ! choice/control of key cpp for surface pressure gradient 
    2424   USE solmat          ! matrix of the solver 
    25    USE obc_oce         ! Lateral open boundary condition 
    2625   USE in_out_manager  ! I/O manager 
    2726   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2827   USE lib_mpp         ! MPP library 
     28   USE timing          ! timing 
    2929 
    3030   IMPLICIT NONE 
     
    5454      NAMELIST/namsol/ nn_solv, nn_sol_arp, nn_nmin, nn_nmax, nn_nmod, rn_eps, rn_resmax, rn_sor 
    5555      !!---------------------------------------------------------------------- 
     56      ! 
     57      IF( nn_timing == 1 )  CALL timing_start('solver_init') 
     58      ! 
    5659 
    5760      IF(lwp) THEN                  !* open elliptic solver statistics file (only on the printing processors) 
     
    111114      CALL sol_mat( kt )            !* Construction of the elliptic system matrix 
    112115      ! 
     116      IF( nn_timing == 1 )  CALL timing_stop('solver_init') 
     117      ! 
    113118   END SUBROUTINE solver_init 
    114119#endif 
Note: See TracChangeset for help on using the changeset viewer.