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

Diff of /trunk/dyn3d/disvert.f

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

trunk/libf/dyn3d/comvert.f90 revision 48 by guez, Tue Jul 19 12:54:20 2011 UTC trunk/libf/dyn3d/disvert.f90 revision 66 by guez, Thu Sep 20 13:00:41 2012 UTC
# Line 1  Line 1 
1  module comvert  module disvert_m
2    
3    use dimens_m, only: llm    use dimens_m, only: llm
4    
# Line 19  contains Line 19  contains
19    SUBROUTINE disvert    SUBROUTINE disvert
20    
21      ! From dyn3d/disvert.F, v 1.1.1.1 2004/05/19 12:53:05      ! From dyn3d/disvert.F, v 1.1.1.1 2004/05/19 12:53:05
22      ! Auteur : P. Le Van      ! Author: P. Le Van
23    
24      ! This procedure sets the vertical grid.      ! This procedure sets the vertical grid. It defines the host
25      ! It defines the host variables "ap", "bp", "presnivs", "nivsigs"      ! variables "ap", "bp", "presnivs", "nivsigs" and "nivsig". "pa"
26      ! and "nivsig".      ! should be defined before this procedure is called.
     ! "pa" should be defined before this procedure is called.  
27    
     use nr_util, only: pi  
28      use jumble, only: new_unit      use jumble, only: new_unit
29        use nr_util, only: pi
30        use unit_nml_m, only: unit_nml
31    
32        ! Local:
33    
34      REAL s(llm+1)      REAL s(llm+1)
35      ! "s(l)" is the atmospheric hybrid sigma-pressure coordinate at      ! "s(l)" is the atmospheric hybrid sigma-pressure coordinate at
# Line 37  contains Line 39  contains
39      ! "ds(l)" : épaisseur de la couche "l" dans la coordonnée "s"      ! "ds(l)" : épaisseur de la couche "l" dans la coordonnée "s"
40    
41      INTEGER l, unit      INTEGER l, unit
42      REAL alpha, x(llm), trash      REAL alpha, x(llm)
43    
44      character(len=7):: s_sampling = "LMD5"      character(len=7):: s_sampling = "tropo"
45      ! (other allowed values are "param", "strato1", "strato2" and "read")      ! (other allowed values are "param", "strato1", "strato" and "read")
46    
47      real:: h = 7. ! scale height, in km      real:: h = 7. ! scale height, in km
48      ! (used only if "s_sampling" == "param" or "strato1")      ! (used only if "s_sampling" == "param" or "strato1")
# Line 66  contains Line 68  contains
68    
69      print *, "Enter namelist 'disvert_nml'."      print *, "Enter namelist 'disvert_nml'."
70      read(unit=*, nml=disvert_nml)      read(unit=*, nml=disvert_nml)
71      write(unit=*, nml=disvert_nml)      write(unit_nml, nml=disvert_nml)
72    
73      select case (s_sampling)      select case (s_sampling)
74      case ("param")      case ("param")
# Line 77  contains Line 79  contains
79              = cosh((l - 1) / k0) **(- alpha * k0 / h) &              = cosh((l - 1) / k0) **(- alpha * k0 / h) &
80              * exp(- alpha / h * tanh((llm - k1) / k0) &              * exp(- alpha / h * tanh((llm - k1) / k0) &
81              * beta **(l - 1 - (llm - k1)) / log(beta))              * beta **(l - 1 - (llm - k1)) / log(beta))
82      case ("LMD5")      case ("tropo")
        ! Ancienne discrétisation  
83         s(1) = 1.         s(1) = 1.
84         s(llm+1) = 0.         s(llm+1) = 0.
85         forall (l = 1: llm) ds(l) &         forall (l = 1: llm) ds(l) &
86              = 1. + 7. * SIN(pi * (REAL(l)-0.5) / real(llm+1))**2              = 1. + 7. * SIN(pi * (REAL(l) - 0.5) / real(llm + 1))**2
87         ds = ds / sum(ds)         ds = ds / sum(ds)
88    
89         DO l = llm, 2, -1         DO l = llm, 2, -1
# Line 102  contains Line 103  contains
103    
104         s(2:llm) = (exp(- zz(2:llm) / h) - exp(- zz(llm + 1) / h)) &         s(2:llm) = (exp(- zz(2:llm) / h) - exp(- zz(llm + 1) / h)) &
105              / (1. - exp(- zz(llm + 1) / h))              / (1. - exp(- zz(llm + 1) / h))
106      case ("strato2")      case ("strato")
107         ! Recommended by F. Lott for a domain including the stratosphere         ! Recommended by F. Lott for a domain including the stratosphere
108         s(1) = 1.         s(1) = 1.
109         s(llm+1) = 0.         s(llm+1) = 0.
110         forall (l = 1: llm) x(l) = pi * (l - 0.5) / (llm + 1)         forall (l = 1: llm) x(l) = pi * (l - 0.5) / (llm + 1)
111    
112         ds = (1. + 7. * SIN(x)**2) * (1. - tanh(2 * x / pi - 1.))**2 / 4.         ds = (0.3 + 7. * SIN(x)**2) * (1. - tanh(2 * x / pi - 1.))**2 / 4.
113         ds = ds / sum(ds)         ds = ds / sum(ds)
114    
115         DO l = llm, 2, -1         DO l = llm, 2, -1
# Line 120  contains Line 121  contains
121              position="rewind")              position="rewind")
122         read(unit, fmt=*) ! skip title line         read(unit, fmt=*) ! skip title line
123         do l = 1, llm + 1         do l = 1, llm + 1
124            read(unit, fmt=*) trash, s(l)            read(unit, fmt=*) s(l)
125         end do         end do
126         close(unit)         close(unit)
127         ! Quick check:         ! Quick check:
# Line 143  contains Line 144  contains
144    
145    END SUBROUTINE disvert    END SUBROUTINE disvert
146    
147  end module comvert  end module disvert_m

Legend:
Removed from v.48  
changed lines
  Added in v.66

  ViewVC Help
Powered by ViewVC 1.1.21