source: codes/icosagcm/trunk/src/icosa_sw.f90 @ 19

Last change on this file since 19 was 19, checked in by ymipsl, 12 years ago

Simplify the management of the module.

YM

File size: 950 bytes
Line 
1PROGRAM ICOSA_SW
2  USE icosa
3  USE timeloop_sw_mod
4  USE transfert_mod
5  USE dissip_sw_mod
6  USE disvert_mod
7  IMPLICIT NONE
8 
9
10  TYPE(t_field),POINTER :: sum_ne(:)
11  REAL(rstd),POINTER :: pt_sum_ne(:)
12 
13  INTEGER :: ind,i,j,k,n
14  REAL(rstd) :: tot_sum=0
15 
16  CALL compute_metric
17  CALL compute_domain
18  CALL compute_geometry
19  CALL init_transfert
20 
21  CALL allocate_field(sum_ne,field_T,type_real)
22 
23
24  DO ind=1,ndomain
25     
26    pt_sum_ne=sum_ne(ind)
27     
28    CALL swap_dimensions(ind)
29    CALL swap_geometry(ind)
30   
31    DO j=jj_begin,jj_end
32      DO i=ii_begin,ii_end
33        n=(j-1)*iim+i
34        pt_sum_ne(n)=0
35        DO k=1,6
36          pt_sum_ne(n)=pt_sum_ne(n)+ne(n,k)
37        ENDDO
38        IF (domain(ind)%own(i,j)) tot_sum=tot_sum+Ai(n)
39      ENDDO
40    ENDDO
41  ENDDO
42
43  PRINT *," Diff surf",1-tot_sum/(4*Pi*radius*radius)
44
45 
46!  CALL WriteField("Ai",geom%Ai)
47!  CALL WriteField("sum_ne",sum_ne)
48 CALL timeloop
49 
50END PROGRAM ICOSA_SW 
Note: See TracBrowser for help on using the repository browser.