source: LMDZ6/trunk/libf/dyn3d/groupe.f90 @ 5401

Last change on this file since 5401 was 5285, checked in by abarral, 7 weeks ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.3 KB
RevLine 
[524]1!
2! $Header$
3!
[5246]4subroutine groupe(pext,pbaru,pbarv,pbarum,pbarvm,wm)
[524]5
[5281]6  USE comgeom2_mod_h
[5246]7  use comconst_mod, only: ngroup
[524]8
[5271]9  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]10USE paramet_mod_h
[5271]11implicit none
[524]12
[5246]13  !   sous-programme servant a fitlrer les champs de flux de masse aux
14  !   poles en "regroupant" les mailles 2 par 2 puis 4 par 4 etc. au fur
15  !   et a mesure qu'on se rapproche du pole.
16  !
17  !   en entree: pext, pbaru et pbarv
18  !
19  !   en sortie:  pbarum,pbarvm et wm.
20  !
21  !   remarque, le wm est recalcule a partir des pbaru pbarv et on n'a donc
22  !   pas besoin de w en entree.
[524]23
[5271]24
[5272]25
[524]26
[5246]27  ! integer ngroup
28  ! parameter (ngroup=3)
[524]29
30
[5246]31  real :: pbaru(iip1,jjp1,llm),pbarv(iip1,jjm,llm)
32  real :: pext(iip1,jjp1,llm)
[524]33
[5246]34  real :: pbarum(iip1,jjp1,llm),pbarvm(iip1,jjm,llm)
35  real :: wm(iip1,jjp1,llm)
[524]36
[5246]37  real :: zconvm(iip1,jjp1,llm),zconvmm(iip1,jjp1,llm)
[524]38
[5246]39  real :: uu
[524]40
[5246]41  integer :: i,j,l
[524]42
[5246]43  logical :: firstcall,groupe_ok
44  save firstcall,groupe_ok
[1674]45
[5246]46  data firstcall/.true./
47  data groupe_ok/.true./
[524]48
[5246]49  if (iim==1) then
50     groupe_ok=.false.
51  endif
[1674]52
[5246]53  if (firstcall) then
54     if (groupe_ok) then
55        if(mod(iim,2**ngroup).ne.0) &
56              CALL abort_gcm('groupe','probleme du nombre de point',1)
57     endif
58     firstcall=.false.
59  endif
[524]60
61
[5246]62  !   Champs 1D
[524]63
[5246]64  call convflu(pbaru,pbarv,llm,zconvm)
[524]65
[5246]66  call scopy(ijp1llm,zconvm,1,zconvmm,1)
67  call scopy(ijmllm,pbarv,1,pbarvm,1)
[524]68
[5246]69  if (groupe_ok) then
70  call groupeun(jjp1,llm,zconvmm)
71  call groupeun(jjm,llm,pbarvm)
[1674]72
[5246]73  !   Champs 3D
74  do l=1,llm
75     do j=2,jjm
76        uu=pbaru(iim,j,l)
77        do i=1,iim
78           uu=uu+pbarvm(i,j,l)-pbarvm(i,j-1,l)-zconvmm(i,j,l)
79           pbarum(i,j,l)=uu
80  ! zconvm(i,j,l ) =  xflu(i-1,j,l)-xflu(i,j,l)+
81  !    *                      yflu(i,j,l)-yflu(i,j-1,l)
82        enddo
83        pbarum(iip1,j,l)=pbarum(1,j,l)
84     enddo
85  enddo
86
87  else
88     pbarum(:,:,:)=pbaru(:,:,:)
89     pbarvm(:,:,:)=pbarv(:,:,:)
90  endif
91
92  !    integration de la convergence de masse de haut  en bas ......
93  do l=1,llm
94     do j=1,jjp1
95        do i=1,iip1
96           zconvmm(i,j,l)=zconvmm(i,j,l)
97        enddo
98     enddo
99  enddo
100  do  l = llm-1,1,-1
101      do j=1,jjp1
102         do i=1,iip1
103            zconvmm(i,j,l)=zconvmm(i,j,l)+zconvmm(i,j,l+1)
[524]104         enddo
105      enddo
[5246]106  enddo
[524]107
[5246]108  CALL vitvert(zconvmm,wm)
[524]109
[5246]110  return
111end subroutine groupe
[524]112
Note: See TracBrowser for help on using the repository browser.