/[lmdze]/trunk/dyn3d/Guide/tau2alpha.f90
ViewVC logotype

Annotation of /trunk/dyn3d/Guide/tau2alpha.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 178 - (hide annotations)
Fri Mar 11 18:47:26 2016 UTC (8 years, 3 months ago) by guez
Original Path: trunk/Sources/dyn3d/Guide/tau2alpha.f
File size: 1292 byte(s)
Moved variables date0, deltat, datasz_max, ncvar_ids, point, buff_pos,
buffer, regular from module histcom_var to modules where they are
defined.

Removed procedure ioipslmpp, useless for a sequential program.

Added argument datasz_max to histwrite_real (to avoid circular
dependency with histwrite).

Removed useless variables and computations everywhere.

Changed real litteral constants from default kind to double precision
in lwb, lwu, lwvn, sw1s, swtt, swtt1, swu.

Removed unused arguments: paer of sw, sw1s, sw2s, swclr; pcldsw of
sw1s, sw2s; pdsig, prayl of swr; co2_ppm of clmain, clqh; tsol of
transp_lay; nsrf of screenp; kcrit and kknu of gwstress; pstd of
orosetup.

Added output of relative humidity.

1 guez 37 module tau2alpha_m
2    
3 guez 103 IMPLICIT NONE
4 guez 37
5     contains
6    
7 guez 115 SUBROUTINE tau2alpha(dxdy, rlat, taumin, taumax, alpha)
8 guez 37
9 guez 115 use conf_guide_m, only: lat_min_guide, lat_max_guide, factt
10     use init_tau2alpha_m, only: dxdy_min, dxdy_max, gamma
11 guez 178 USE nr_util, ONLY: assert_eq
12 guez 37
13 guez 115 REAL, intent(in):: dxdy(:, :) ! (n_lon, n_lat)
14     REAL, intent(in):: rlat(:) ! (n_lat)
15     REAL, intent(in):: taumin, taumax
16     real, intent(out):: alpha(:, :) ! (n_lon, n_lat)
17 guez 103
18     ! Local:
19     REAL alphamin, alphamax, xi
20 guez 115 INTEGER i, j, n_lon, n_lat
21 guez 37
22 guez 44 !------------------------------------------------------------
23    
24 guez 115 PRINT *, 'Call sequence information: tau2alpha'
25 guez 109
26 guez 115 n_lon = assert_eq(size(alpha, 1), size(dxdy, 1), "tau2alpha n_lon")
27     n_lat = assert_eq(size(alpha, 2), size(dxdy, 2), size(rlat), &
28     "tau2alpha n_lat")
29 guez 109
30 guez 115 alphamin = factt / taumax
31     alphamax = factt / taumin
32 guez 113
33 guez 115 DO j = 1, n_lat
34 guez 140 IF (lat_min_guide <= rlat(j) .AND. rlat(j) <= lat_max_guide) THEN
35 guez 115 DO i = 1, n_lon
36     xi = min(((dxdy_max - dxdy(i, j)) &
37     / (dxdy_max - dxdy_min))**gamma, 1.)
38     alpha(i, j) = xi * alphamin + (1. - xi) * alphamax
39 guez 37 END DO
40     ELSE
41 guez 115 alpha(:, j) = 0.
42 guez 37 END IF
43     END DO
44    
45     END SUBROUTINE tau2alpha
46    
47     end module tau2alpha_m

  ViewVC Help
Powered by ViewVC 1.1.21