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

Last change on this file since 5136 was 5136, checked in by abarral, 8 weeks ago

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