source: LMDZ6/trunk/libf/dyn3d_common/adaptdt.f90 @ 5319

Last change on this file since 5319 was 5285, checked in by abarral, 10 days 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: 1.0 KB
RevLine 
[524]1!
[1403]2! $Id: adaptdt.f90 5285 2024-10-28 13:33:29Z fairhead $
[524]3!
[5246]4subroutine adaptdt(nadv,dtbon,n,pbaru, &
5        masse)
[524]6
[5281]7  USE comgeom2_mod_h
[5280]8  USE comdissip_mod_h
[5246]9  USE comconst_mod, ONLY: dtvr
[5271]10  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]11USE paramet_mod_h
[5271]12IMPLICIT NONE
[524]13
[5271]14
[5272]15
[5246]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
[524]28
[5246]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
[524]44
[5246]45   return
46end subroutine adaptdt
[524]47
48
49
50
51
[5246]52
53
Note: See TracBrowser for help on using the repository browser.