/[lmdze]/trunk/libf/phylmd/gath_cpl.f90
ViewVC logotype

Annotation of /trunk/libf/phylmd/gath_cpl.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 32 - (hide annotations)
Tue Apr 6 17:52:58 2010 UTC (14 years, 1 month ago) by guez
File size: 1309 byte(s)
Split "stringop.f90" into single-procedure files. Gathered files in directory
"IOIPSL/Stringop".

Split "flincom.f90" into "flincom.f90" and "flinget.f90". Removed
unused procedures from module "flincom". Removed unused argument
"filename" of procedure "flinopen_nozoom".

Removed unused files.

Split "grid_change.f90" into "grid_change.f90" and
"gr_phy_write_3d.f90".

Removed unused procedures from modules "calendar", "ioipslmpp",
"grid_atob", "gath_cpl" and "getincom". Removed unused procedures in
files "ppm3d.f" and "thermcell.f".

Split "mathelp.f90" into "mathelp.f90" and "mathop.f90".

Removed unused variable "dpres" of module "comvert".

Use argument "itau" instead of local variables "iadvtr" and "first" to
control algorithm in procedure "fluxstokenc".

Removed unused arguments of procedure "integrd".

Removed useless computations at the end of procedure "leapfrog".

Merged common block "matrfil" into module "parafilt".

1 guez 3 module gath_cpl
2    
3     ! From phylmd/interface_surf.F90,v 1.8 2005/05/25 13:10:09
4    
5     implicit none
6    
7     contains
8    
9     SUBROUTINE gath2cpl(champ_in, champ_out, klon, knon, iim, jjm, knindex)
10    
11     ! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
12     ! au coupleur.
13     !
14     !
15     ! input:
16     ! champ_in champ sur la grille gathere
17     ! knon nombre de points dans le domaine a traiter
18     ! knindex index des points de la surface a traiter
19     ! klon taille de la grille
20     ! iim,jjm dimension de la grille 2D
21     !
22     ! output:
23     ! champ_out champ sur la grille 2D
24     !
25     ! input
26     integer :: klon, knon, iim, jjm
27     real, dimension(klon) :: champ_in
28     integer, dimension(klon) :: knindex
29     ! output
30     real, dimension(iim,jjm+1) :: champ_out
31     ! local
32     integer :: i, ig, j
33     real, dimension(klon) :: tamp
34    
35     tamp = 0.
36     do i = 1, knon
37     ig = knindex(i)
38     tamp(ig) = champ_in(i)
39     enddo
40     ig = 1
41     champ_out(:,1) = tamp(ig)
42     do j = 2, jjm
43     do i = 1, iim
44     ig = ig + 1
45     champ_out(i,j) = tamp(ig)
46     enddo
47     enddo
48     ig = ig + 1
49     champ_out(:,jjm+1) = tamp(ig)
50    
51     END SUBROUTINE gath2cpl
52    
53     end module gath_cpl

  ViewVC Help
Powered by ViewVC 1.1.21