source: codes/icosagcm/trunk/src/pression.f90 @ 380

Last change on this file since 380 was 295, checked in by ymipsl, 10 years ago

Merging OpenMP parallisme mode : by subdomain and on vertical level.
This feature is actually experimental but may be retro-compatible with the last method based only on subdomain

YM

File size: 1.1 KB
RevLine 
[12]1MODULE pression_mod
2
3CONTAINS
4
5  SUBROUTINE pression(f_ps,f_p)
[19]6  USE icosa
[12]7  IMPLICIT NONE
8    TYPE(t_field), POINTER :: f_ps(:)
9    TYPE(t_field), POINTER :: f_p(:)
10 
11    REAL(rstd), POINTER :: ps(:)
12    REAL(rstd), POINTER :: p(:,:)
13    INTEGER :: ind
14
[295]15!$OMP BARRIER
[12]16    DO ind=1,ndomain
[186]17      IF (.NOT. assigned_domain(ind)) CYCLE
[12]18      CALL swap_dimensions(ind)
19      CALL swap_geometry(ind)
20      ps=f_ps(ind)
21      p=f_p(ind)
22      CALL compute_pression(ps, p,0)
23    ENDDO
[295]24!$OMP BARRIER
[12]25 
26  END SUBROUTINE pression
27 
28  SUBROUTINE compute_pression(ps,p,offset)
[19]29  USE icosa
[12]30  USE disvert_mod
[295]31  USE omp_para
[12]32  IMPLICIT NONE
33    REAL(rstd),INTENT(IN) :: ps(iim*jjm)
34    REAL(rstd),INTENT(OUT) :: p(iim*jjm,llm+1)
35    INTEGER,INTENT(IN) :: offset
36    INTEGER :: i,j,ij,l
37
[166]38    IF(ap_bp_present) THEN
[295]39      DO    l    = ll_begin, ll_endp1
40!      DO    l    = 1, llm + 1
41        DO j=jj_begin-offset,jj_end+offset
42          DO i=ii_begin-offset,ii_end+offset
43            ij=(j-1)*iim+i
44            p(ij,l) = ap(l) + bp(l) * ps(ij)
45          ENDDO
[12]46        ENDDO
47      ENDDO
[166]48    END IF
[295]49
[12]50  END SUBROUTINE compute_pression
51
52END MODULE pression_mod
Note: See TracBrowser for help on using the repository browser.