Changeset 1819 for trunk/LMDZ.TITAN/libf/muphytitan/mmp_gcm.f90
- Timestamp:
- Nov 8, 2017, 4:45:50 PM (7 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.TITAN/libf/muphytitan/mmp_gcm.f90
r1793 r1819 27 27 REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: c 28 28 END TYPE 29 30 !> Size distribution parameters derived type. 31 !! 32 !! It stores the parameters of the size distribution law for Titan. 33 !! 34 !! The size distribution law is represented by the minimization of a sum of 35 !! power law functions: 36 !! 37 !! $$ 38 !! \displaystyle n\left(r\right) = \frac{A_{0}}{C+\sum_{i=1}^{n} A_{i}\times 39 !! \left(\frac{r}{r_{c}}\right)^{-b_{i}}} 40 !! $$ 41 TYPE, PUBLIC :: nprm 42 !> Scaling factor. 43 REAL(kind=mm_wp) :: a0 44 !> Characterisitic radius. 45 REAL(kind=mm_wp) :: rc 46 !> Additional constant to the sum of power law. 47 REAL(kind=mm_wp) :: c 48 !> Scaling factor of each power law. 49 REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: a 50 !> Power of each power law. 51 REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: b 52 END TYPE 53 29 54 !> Inter-moment relation set of parameters for the spherical mode. 30 55 TYPE(aprm), PUBLIC, SAVE :: mmp_asp … … 32 57 TYPE(aprm), PUBLIC, SAVE :: mmp_afp 33 58 59 !> Size-distribution law parameters of the spherical mode. 60 TYPE(nprm), PUBLIC, SAVE :: mmp_pns 61 !> Size-distribution law parameters of the fractal mode. 62 TYPE(nprm), PUBLIC, SAVE :: mmp_pnf 63 34 64 !> Data set for @f$<Q>_{SF}^{M0}@f$. 35 65 TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbsf0 36 !> Extended values of [[mmp_g lobals(module):mmp_qbsf0(variable)]] dataset.66 !> Extended values of [[mmp_gcm(module):mmp_qbsf0(variable)]] dataset. 37 67 REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf0_e 38 68 !> Data set for @f$<Q>_{SF}^{M3}@f$. 39 69 TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbsf3 40 !> Extended values of [[mmp_g lobals(module):mmp_qbsf3(variable)]] dataset.70 !> Extended values of [[mmp_gcm(module):mmp_qbsf3(variable)]] dataset. 41 71 REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf3_e 42 72 !> Data set for @f$<Q>_{FF}^{M0}@f$. 43 73 TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbff0 44 !> Extended values of [[mmp_g lobals(module):mmp_qbff0(variable)]] dataset.74 !> Extended values of [[mmp_gcm(module):mmp_qbff0(variable)]] dataset. 45 75 REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbff0_e 46 76 … … 247 277 err = read_aprm(cparser,'alpha_f',mmp_afp) 248 278 IF (err /= 0) call abort_program(error("alpha_s: "//TRIM(err%msg),-1)) 279 280 ! get size-distribution laws parameters 281 IF (.NOT.cfg_has_section(cparser,'dndr_s')) call abort_program(error("Cannot find [dndr_s] section",-2)) 282 err = read_nprm(cparser,'dndr_s',mmp_pns) 283 IF (err /= 0) call abort_program(error("dndr_s: "//TRIM(err%msg),-2)) 284 IF (.NOT.cfg_has_section(cparser,'dndr_f')) call abort_program(error("Cannot find [dndr_f] section",-2)) 285 err = read_nprm(cparser,'dndr_f',mmp_pnf) 286 IF (err /= 0) call abort_program(error("dndr_f: "//TRIM(err%msg),-2)) 287 249 288 ! btk coefficients 250 289 IF (.NOT.cfg_has_section(cparser,'btks')) call abort_program(error("Cannot find [btks] section",-1)) … … 265 304 266 305 FUNCTION read_aprm(parser,sec,pp) RESULT(err) 267 !! Read and store [[mmp_g lobals(module):aprm(type)]] parameters.306 !! Read and store [[mmp_gcm(module):aprm(type)]] parameters. 268 307 TYPE(cfgparser), INTENT(in) :: parser !! Configuration parser 269 308 CHARACTER(len=*), INTENT(in) :: sec !! Name of the section that contains the parameters. 270 TYPE(aprm), INTENT(out) :: pp !! [[mmp_g lobals(module):aprm(type)]] object that stores the parameters values.309 TYPE(aprm), INTENT(out) :: pp !! [[mmp_gcm(module):aprm(type)]] object that stores the parameters values. 271 310 TYPE(error) :: err !! Error status of the function. 272 311 err = cfg_get_value(parser,TRIM(sec)//'/a',pp%a) ; IF (err /= 0) RETURN … … 278 317 END FUNCTION read_aprm 279 318 319 FUNCTION read_nprm(parser,sec,pp) RESULT(err) 320 !! Read and store [[mmp_gcm(module):nprm(type)]] parameters. 321 TYPE(cfgparser), INTENT(in) :: parser !! Configuration parser 322 CHARACTER(len=*), INTENT(in) :: sec !! Name of the section that contains the parameters. 323 TYPE(nprm), INTENT(out) :: pp !! [[mmp_gcm(module):nprm(type)]] object that stores the parameters values. 324 TYPE(error) :: err !! Error status of the function. 325 err = cfg_get_value(parser,TRIM(sec)//'/rc',pp%rc) ; IF (err /= 0) RETURN 326 err = cfg_get_value(parser,TRIM(sec)//'/a0',pp%a0) ; IF (err /= 0) RETURN 327 err = cfg_get_value(parser,TRIM(sec)//'/c',pp%c) ; IF (err /= 0) RETURN 328 err = cfg_get_value(parser,TRIM(sec)//'/a',pp%a) ; IF (err /= 0) RETURN 329 err = cfg_get_value(parser,TRIM(sec)//'/b',pp%b) ; IF (err /= 0) RETURN 330 IF (SIZE(pp%a) /= SIZE(pp%b)) & 331 err = error("Inconsistent number of coefficients (a and b must have the same size)",3) 332 RETURN 333 END FUNCTION read_nprm 334 280 335 END MODULE MMP_GCM 281 336
Note: See TracChangeset
for help on using the changeset viewer.