source: codes/icosagcm/trunk/src/icosa_gcm.f90 @ 176

Last change on this file since 176 was 171, checked in by ymipsl, 11 years ago
  • XIOS integration -

Compiling with "-with_xios" option. Adapt path to find XIOS library (arch.path)
Retro-compatible with the old output. If xios is not present, dynamico will use the standard writefield function.
Need to have the iodef.xml configuration file in the exec directory

YM

File size: 1.5 KB
RevLine 
[12]1PROGRAM ICOSA_GCM
[19]2  USE icosa
[12]3  USE timeloop_gcm_mod
4  USE disvert_mod
5  USE etat0_mod
[15]6  USE wind_mod
[26]7  USE mpipara
[151]8  USE omp_para
[97]9  USE vertical_interp_mod
[151]10  USE trace
[171]11  USE output_field_mod
12  USE xios_mod
13  USE write_field
[12]14  IMPLICIT NONE
15 
16  TYPE(t_field),POINTER :: sum_ne(:)
[26]17  TYPE(t_field),POINTER :: sum_ne_glo(:)
[12]18  REAL(rstd),POINTER :: pt_sum_ne(:)
19 
20  INTEGER :: ind,i,j,k,n
21  REAL(rstd) :: tot_sum=0
[15]22  REAL(rstd) :: vect(3,6)
23  REAL(rstd) :: centr(3),dist
[12]24 
[26]25  CALL init_mpipara
[171]26  CALL xios_init
[32]27  CALL init_earth_const 
[15]28  CALL init_grid_param
[151]29  CALL init_omp_para
[12]30  CALL compute_metric
31  CALL compute_domain
[15]32  CALL init_transfert
[82]33  CALL init_writefield
[151]34  CALL init_trace
[149]35
[26]36 
[12]37  CALL compute_geometry
38  CALL init_disvert 
[97]39  CALL init_vertical_interp
40
[12]41  CALL allocate_field(sum_ne,field_T,type_real)
42 
43
44  DO ind=1,ndomain
45     
46    pt_sum_ne=sum_ne(ind)
47     
48    CALL swap_dimensions(ind)
49    CALL swap_geometry(ind)
50   
51    DO j=jj_begin,jj_end
52      DO i=ii_begin,ii_end
53        n=(j-1)*iim+i
54        pt_sum_ne(n)=0
55        DO k=1,6
56          pt_sum_ne(n)=pt_sum_ne(n)+ne(n,k)
57        ENDDO
58        IF (domain(ind)%own(i,j)) tot_sum=tot_sum+Ai(n)
59      ENDDO
60    ENDDO
61  ENDDO
62
63
64 
[131]65  IF (is_mpi_root) PRINT *," Diff surf",1-tot_sum/(4*Pi*radius*radius)
[12]66
67 
[15]68  CALL WriteField("Ai",geom%Ai)
[151]69
[131]70  IF (is_mpi_root) CALL write_apbp
[97]71  CALL init_time
[151]72
[171]73  CALL output_field_init
[151]74  CALL init_timeloop
75
76!$OMP PARALLEL
[12]77  CALL timeloop
[151]78!$OMP END PARALLEL
[26]79
[171]80  CALL output_field_finalize
[26]81  CALL close_files
[82]82  CALL close_time_counter
[26]83  CALL finalize_mpipara
[12]84 
85END PROGRAM ICOSA_gcm 
Note: See TracBrowser for help on using the repository browser.