/[lmdze]/trunk/dyn3d/disvert.f90
ViewVC logotype

Diff of /trunk/dyn3d/disvert.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/dyn3d/disvert.f revision 265 by guez, Tue Mar 20 09:35:59 2018 UTC trunk/dyn3d/disvert.f90 revision 328 by guez, Thu Jun 13 14:40:06 2019 UTC
# Line 6  module disvert_m Line 6  module disvert_m
6    
7    private llm, hybrid, funcd, y, ya, compute_ab    private llm, hybrid, funcd, y, ya, compute_ab
8    
9    real, save:: ap(llm+1), pa ! in Pa    real, save:: ap(llm+1) ! in Pa
10    real, save:: bp(llm+1)    real, save:: bp(llm+1)
11    
12    REAL s(llm+1)    REAL s(llm+1)
# Line 14  module disvert_m Line 14  module disvert_m
14    ! half-level, between layers "l" and "l-1"    ! half-level, between layers "l" and "l-1"
15    
16    real, save:: presnivs(llm)    real, save:: presnivs(llm)
17    ! pressions approximatives des milieux de couches, en Pa    ! approximate full level pressure for a reference surface pressure, in Pa
18    
19    real, parameter:: preff = 101325. ! in Pa    real, parameter:: preff = 101325. ! in Pa
20    real y, ya ! for the hybrid function    real y, ya ! for the hybrid function
# Line 30  contains Line 30  contains
30      ! variables "ap", "bp", "presnivs". "pa" should be defined before      ! variables "ap", "bp", "presnivs". "pa" should be defined before
31      ! this procedure is called.      ! this procedure is called.
32    
33        ! Libraries:
34      use jumble, only: read_column, new_unit      use jumble, only: read_column, new_unit
35      use nr_util, only: pi, assert      use nr_util, only: pi, assert
36        
37        use dynetat0_chosen_m, only: pa
38      use unit_nml_m, only: unit_nml      use unit_nml_m, only: unit_nml
39    
40      ! Local:      ! Local:
# Line 45  contains Line 48  contains
48      real zz(llm) ! in km      real zz(llm) ! in km
49    
50      character(len=20):: vert_sampling = "tropo"      character(len=20):: vert_sampling = "tropo"
51      ! Allowed values: "tropo", "param", "strato", "read_hybrid", "read_pressure"      ! Allowed values: "tropo", "strato_custom", "strato",
52        ! "read_hybrid", "read_pressure".
53    
54      ! These variables are used only in the case vert_sampling ==      ! These variables are used only in the case vert_sampling ==
55      ! "param", and all are in km:      ! "strato_custom", and all are in km:
56      real:: vert_scale = 7. ! scale height      real:: vert_scale = 7. ! scale height
57      real:: vert_dzmin = 0.02 ! width of first layer      real:: vert_dzmin = 0.017 ! width of first layer
58      real:: vert_dzlow = 1. ! dz in the low atmosphere      real:: vert_dzlow = 1. ! dz in the low atmosphere
59      real:: vert_z0low = 8. ! height at which resolution reaches dzlow      real:: vert_z0low = 8.7 ! height at which resolution reaches dzlow
60      real:: vert_dzmid = 3. ! dz in the mid atmosphere      real:: vert_dzmid = 2. ! dz in the mid atmosphere
61      real:: vert_z0mid = 70. ! height at which resolution reaches dzmid      real:: vert_z0mid = 70. ! height at which resolution reaches dzmid
62      real:: vert_h_mid = 20. ! width of the transition      real:: vert_h_mid = 20. ! width of the transition
63      real:: vert_dzhig = 11. ! dz in the high atmosphere      real:: vert_dzhig = 11. ! dz in the high atmosphere
64      real:: vert_z0hig = 80. ! height at which resolution reaches dz      real:: vert_z0hig = 75. ! height at which resolution reaches dz
65      real:: vert_h_hig = 20. ! width of the transition      real:: vert_h_hig = 20. ! width of the transition
66    
67      real, allocatable:: p(:) ! (llm + 1) pressure (in hPa)      real, allocatable:: p(:) ! (2:llm or llm + 1) pressure (in hPa)
68    
69      namelist /disvert_nml/vert_sampling, vert_scale, vert_dzmin, vert_dzlow, &      namelist /disvert_nml/vert_sampling, vert_scale, vert_dzmin, vert_dzlow, &
70           vert_z0low, vert_dzmid, vert_z0mid, vert_h_mid, vert_dzhig, &           vert_z0low, vert_dzmid, vert_z0mid, vert_h_mid, vert_dzhig, &
# Line 81  contains Line 85  contains
85      select case (vert_sampling)      select case (vert_sampling)
86    
87      case ("tropo")      case ("tropo")
88         ! with llm = 19 for CMIP 3         ! with llm = 19 and dsigmin = 1 for CMIP 3
89    
90         forall (l = 1: llm) ds(l) &         forall (l = 1: llm) ds(l) &
91              = dsigmin + 7. * SIN(pi * (REAL(l) - 0.5) / real(llm + 1))**2              = dsigmin + 7. * SIN(pi * (REAL(l) - 0.5) / real(llm + 1))**2
# Line 94  contains Line 98  contains
98         call compute_ab         call compute_ab
99    
100      case ("strato")      case ("strato")
101         ! with llm = 39 and dsigmin = 0.3 for CMIP5         ! with llm = 39 and dsigmin = 0.3 for CMIP5
102    
103         forall (l = 1: llm) x(l) = pi * (l - 0.5) / (llm + 1)         forall (l = 1: llm) x(l) = pi * (l - 0.5) / (llm + 1)
104    
# Line 107  contains Line 111  contains
111    
112         call compute_ab         call compute_ab
113    
114      case ("param")      case ("strato_custom")
115         ! with llm = 79 for CMIP 6         ! with llm = 79 for CMIP 6
116    
117         zz(1) = 0.         zz(1) = 0.
# Line 172  contains Line 176  contains
176    
177    subroutine compute_ab    subroutine compute_ab
178    
179        use dynetat0_chosen_m, only: pa
180    
181      ! Calcul de "ap" et "bp".      ! Calcul de "ap" et "bp".
182    
183      where (s >= 1. / sqrt(1. - log(tiny(0.))))      where (s >= 1. / sqrt(1. - log(tiny(0.))))

Legend:
Removed from v.265  
changed lines
  Added in v.328

  ViewVC Help
Powered by ViewVC 1.1.21