source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/adaptdt.f90 @ 5116

Last change on this file since 5116 was 5116, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

  • 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: 1.1 KB
Line 
1
2! $Id: adaptdt.f90 5116 2024-07-24 12:54:37Z abarral $
3
4SUBROUTINE adaptdt(nadv,dtbon,n,pbaru, &
5        masse)
6
7  USE comconst_mod, ONLY: dtvr
8  USE lmdz_description, ONLY: descript
9  IMPLICIT NONE
10
11  include "dimensions.h"
12  include "paramet.h"
13  include "comdissip.h"
14  include "comgeom2.h"
15
16  !----------------------------------------------------------
17  ! Arguments
18  !----------------------------------------------------------
19  INTEGER :: n,nadv
20  REAL :: dtbon
21  REAL :: pbaru(iip1,jjp1,llm)
22  REAL :: masse(iip1,jjp1,llm)
23  !----------------------------------------------------------
24  ! Local
25  !----------------------------------------------------------
26  INTEGER :: i,j,l
27  REAL :: CFLmax,aaa,bbb
28
29    CFLmax=0.
30    do l=1,llm
31     do j=2,jjm
32      do i=1,iim
33         aaa=pbaru(i,j,l)*dtvr/masse(i,j,l)
34         CFLmax=max(CFLmax,aaa)
35         bbb=-pbaru(i,j,l)*dtvr/masse(i+1,j,l)
36         CFLmax=max(CFLmax,bbb)
37      enddo
38     enddo
39    enddo
40    n=int(CFLmax)+1
41  ! pour reproduire cas VL du code qui appele x,y,z,y,x
42     ! if (nadv.eq.30) n=n/2   ! Pour Prather
43    dtbon=dtvr/n
44
45   RETURN
46END SUBROUTINE adaptdt
47
48
49
50
51
52
53
Note: See TracBrowser for help on using the repository browser.