source: LMDZ6/trunk/libf/dyn3d_common/iniconst.f90 @ 5272

Last change on this file since 5272 was 5272, checked in by abarral, 23 hours ago

Turn paramet.h into a module

  • 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.1 KB
Line 
1!
2! $Id: iniconst.f90 5272 2024-10-24 15:53:15Z abarral $
3!
4SUBROUTINE iniconst
5
6  USE control_mod
7  use IOIPSL
8
9  USE comconst_mod, ONLY: im, imp1, jm, jmp1, lllm, lllmm1, lllmp1, &
10                          unsim, pi, r, kappa, cpp, dtvr, dtphys
11  USE comvert_mod, ONLY: disvert_type, pressure_exner
12 
13  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
14USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
15          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
16IMPLICIT NONE
17  !
18  !      P. Le Van
19  !
20  !   Declarations:
21  !   -------------
22  !
23
24
25  include "iniprint.h"
26
27  character(len=*),parameter :: modname="iniconst"
28  character(len=80) :: abort_message
29  !
30  !
31  !
32  !-----------------------------------------------------------------------
33  !   dimension des boucles:
34  !   ----------------------
35
36  im      = iim
37  jm      = jjm
38  lllm    = llm
39  imp1    = iim
40  jmp1    = jjm + 1
41  lllmm1  = llm - 1
42  lllmp1  = llm + 1
43
44  !-----------------------------------------------------------------------
45
46  dtphys  = iphysiq * dtvr
47  unsim   = 1./iim
48  pi      = 2.*ASIN( 1. )
49
50  !-----------------------------------------------------------------------
51  !
52
53  r       = cpp * kappa
54
55  write(lunout,*) trim(modname),': R  CP  Kappa ',r,cpp,kappa
56  !
57  !-----------------------------------------------------------------------
58
59  ! vertical discretization: default behavior depends on planet_type flag
60  if (planet_type=="earth") then
61     disvert_type=1
62  else
63     disvert_type=2
64  endif
65  ! but user can also specify using one or the other in run.def:
66  call getin('disvert_type',disvert_type)
67  write(lunout,*) trim(modname),': disvert_type=',disvert_type
68
69  pressure_exner = disvert_type == 1 ! default value
70  call getin('pressure_exner', pressure_exner)
71
72  if (disvert_type==1) then
73     ! standard case for Earth (automatic generation of levels)
74     call disvert()
75  else if (disvert_type==2) then
76     ! standard case for planets (levels generated using z2sig.def file)
77     call disvert_noterre
78  else
79     write(abort_message,*) "Wrong value for disvert_type: ", disvert_type
80     call abort_gcm(modname,abort_message,0)
81  endif
82
83END SUBROUTINE iniconst
Note: See TracBrowser for help on using the repository browser.