source: LMDZ6/branches/Amaury_dev/libf/dyn3d/fluxstokenc.F90 @ 5127

Last change on this file since 5127 was 5119, checked in by abarral, 3 months ago

enforce PRIVATE by default in several modules, expose PUBLIC as needed
move eigen.f90 to obsolete/
(lint) aslong the way

  • 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: 3.9 KB
Line 
1! $Id: fluxstokenc.F90 5119 2024-07-24 16:46:45Z snguyen $
2
3SUBROUTINE fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, &
4        time_step, itau)
5  ! This routine is designed to work with ioipsl
6
7  USE IOIPSL
8  USE lmdz_iniprint, ONLY: lunout, prt_level
9  USE lmdz_ssum_scopy, ONLY: scopy
10  !
11  ! Auteur :  F. Hourdin
12  !
13  !
14  !cc   ..   Modif. P. Le Van  ( 20/12/97 )  ...
15  !
16  IMPLICIT NONE
17  !
18  include "dimensions.h"
19  include "paramet.h"
20  include "comgeom.h"
21  include "tracstoke.h"
22
23  REAL :: time_step, t_wrt, t_ops
24  REAL :: pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
25  REAL :: masse(ip1jmp1, llm), teta(ip1jmp1, llm), phi(ip1jmp1, llm)
26  REAL :: phis(ip1jmp1)
27
28  REAL :: pbaruc(ip1jmp1, llm), pbarvc(ip1jm, llm)
29  REAL :: massem(ip1jmp1, llm), tetac(ip1jmp1, llm), phic(ip1jmp1, llm)
30
31  REAL :: pbarug(ip1jmp1, llm), pbarvg(iip1, jjm, llm), wg(ip1jmp1, llm)
32
33  REAL :: pbarvst(iip1, jjp1, llm), zistdyn
34  REAL :: dtcum
35
36  INTEGER :: iadvtr, ndex(1)
37  INTEGER :: nscal
38  REAL :: tst(1), ist(1), istp(1)
39  INTEGER :: ij, l, irec, i, j, itau
40  INTEGER, SAVE :: fluxid, fluxvid, fluxdid
41
42  SAVE iadvtr, massem, pbaruc, pbarvc, irec
43  SAVE phic, tetac
44  LOGICAL :: first
45  save first
46  data first/.TRUE./
47  DATA iadvtr/0/
48
49
50  ! AC initialisations
51  pbarug(:, :) = 0.
52  pbarvg(:, :, :) = 0.
53  wg(:, :) = 0.
54
55  IF(first) THEN
56    CALL initfluxsto('fluxstoke', &
57            time_step, istdyn * time_step, istdyn * time_step, &
58            fluxid, fluxvid, fluxdid)
59
60    ndex(1) = 0
61    CALL histwrite(fluxid, 'phis', 1, phis, iip1 * jjp1, ndex)
62    CALL histwrite(fluxid, 'aire', 1, aire, iip1 * jjp1, ndex)
63
64    ndex(1) = 0
65    nscal = 1
66    tst(1) = time_step
67    CALL histwrite(fluxdid, 'dtvr', 1, tst, nscal, ndex)
68    ist(1) = istdyn
69    CALL histwrite(fluxdid, 'istdyn', 1, ist, nscal, ndex)
70    istp(1) = istphy
71    CALL histwrite(fluxdid, 'istphy', 1, istp, nscal, ndex)
72
73    first = .FALSE.
74
75  ENDIF
76
77  IF(iadvtr==0) THEN
78    phic(:, :) = 0
79    tetac(:, :) = 0
80    pbaruc(:, :) = 0
81    pbarvc(:, :) = 0
82  ENDIF
83
84  !   accumulation des flux de masse horizontaux
85  DO l = 1, llm
86    DO ij = 1, ip1jmp1
87      pbaruc(ij, l) = pbaruc(ij, l) + pbaru(ij, l)
88      tetac(ij, l) = tetac(ij, l) + teta(ij, l)
89      phic(ij, l) = phic(ij, l) + phi(ij, l)
90    ENDDO
91    DO ij = 1, ip1jm
92      pbarvc(ij, l) = pbarvc(ij, l) + pbarv(ij, l)
93    ENDDO
94  ENDDO
95
96  !   selection de la masse instantannee des mailles avant le transport.
97  IF(iadvtr==0) THEN
98    CALL SCOPY(ip1jmp1 * llm, masse, 1, massem, 1)
99  ENDIF
100
101  iadvtr = iadvtr + 1
102
103
104  !   Test pour savoir si on advecte a ce pas de temps
105  IF (iadvtr==istdyn) THEN
106    !    normalisation
107    DO l = 1, llm
108      DO ij = 1, ip1jmp1
109        pbaruc(ij, l) = pbaruc(ij, l) / REAL(istdyn)
110        tetac(ij, l) = tetac(ij, l) / REAL(istdyn)
111        phic(ij, l) = phic(ij, l) / REAL(istdyn)
112      ENDDO
113      DO ij = 1, ip1jm
114        pbarvc(ij, l) = pbarvc(ij, l) / REAL(istdyn)
115      ENDDO
116    ENDDO
117
118    !   traitement des flux de masse avant advection.
119    ! 1. calcul de w
120    ! 2. groupement des mailles pres du pole.
121
122    CALL groupe(massem, pbaruc, pbarvc, pbarug, pbarvg, wg)
123
124    do l = 1, llm
125      do j = 1, jjm
126        do i = 1, iip1
127          pbarvst(i, j, l) = pbarvg(i, j, l)
128        enddo
129      enddo
130      do i = 1, iip1
131        pbarvst(i, jjp1, l) = 0.
132      enddo
133    enddo
134
135    iadvtr = 0
136    WRITE(lunout, *)'ITAU auquel on stoke les fluxmasses', itau
137
138    CALL histwrite(fluxid, 'masse', itau, massem, &
139            iip1 * jjp1 * llm, ndex)
140
141    CALL histwrite(fluxid, 'pbaru', itau, pbarug, &
142            iip1 * jjp1 * llm, ndex)
143
144    CALL histwrite(fluxvid, 'pbarv', itau, pbarvg, &
145            iip1 * jjm * llm, ndex)
146
147    CALL histwrite(fluxid, 'w', itau, wg, &
148            iip1 * jjp1 * llm, ndex)
149
150    CALL histwrite(fluxid, 'teta', itau, tetac, &
151            iip1 * jjp1 * llm, ndex)
152
153    CALL histwrite(fluxid, 'phi', itau, phic, &
154            iip1 * jjp1 * llm, ndex)
155
156    !
157
158  ENDIF ! if iadvtr.EQ.istdyn
159
160END SUBROUTINE fluxstokenc
Note: See TracBrowser for help on using the repository browser.