Ignore:
Timestamp:
01/09/14 09:56:11 (10 years ago)
Author:
ymipsl
Message:

Add new openMP parallelism based on distribution of domains on threads. There is no more limitation of number of threads by MPI process.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/etat0_academic.f90

    r19 r186  
    1010  USE kinetic_mod 
    1111  IMPLICIT NONE 
    12     TYPE(t_field),POINTER :: f_ps(:) 
    13     TYPE(t_field),POINTER :: f_phis(:) 
    14     TYPE(t_field),POINTER :: f_theta_rhodz(:) 
    15     TYPE(t_field),POINTER :: f_u(:) 
    16     TYPE(t_field),POINTER :: f_q(:) 
    17     TYPE(t_field),POINTER :: f_Ki(:) 
    18     TYPE(t_field),POINTER :: f_temp(:) 
     12    TYPE(t_field),POINTER,SAVE :: f_ps(:) 
     13    TYPE(t_field),POINTER,SAVE :: f_phis(:) 
     14    TYPE(t_field),POINTER,SAVE :: f_theta_rhodz(:) 
     15    TYPE(t_field),POINTER,SAVE :: f_u(:) 
     16    TYPE(t_field),POINTER,SAVE :: f_q(:) 
     17    TYPE(t_field),POINTER,SAVE :: f_Ki(:) 
     18    TYPE(t_field),POINTER,SAVE :: f_temp(:) 
    1919   
    2020    REAL(rstd),POINTER :: Ki(:,:) 
     
    5858     
    5959    DO ind=1,ndomain 
     60      IF (.NOT. assigned_domain(ind)) CYCLE 
    6061      CALL swap_dimensions(ind) 
    6162      CALL swap_geometry(ind) 
Note: See TracChangeset for help on using the changeset viewer.