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

Diff of /trunk/dyn3d/Guide/conf_guide.f90

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

trunk/dyn3d/Guide/conf_guide.f revision 115 by guez, Fri Sep 19 17:36:20 2014 UTC trunk/dyn3d/Guide/conf_guide.f90 revision 328 by guez, Thu Jun 13 14:40:06 2019 UTC
# Line 1  Line 1 
1  module conf_guide_m  module conf_guide_m
2    
3    IMPLICIT NONE    USE dimensions, ONLY: iim, jjm
4    
5    ! Constantes de rappel, en jours :    IMPLICIT NONE
   REAL:: tau_min_u = 0.03  
   REAL:: tau_max_u = 10.  
   REAL:: tau_min_v = 0.03  
   REAL:: tau_max_v = 10.  
   REAL:: tau_min_t = 0.03  
   REAL:: tau_max_t = 10.  
   REAL:: tau_min_q = 0.03  
   REAL:: tau_max_q = 10.  
   REAL:: tau_min_p = 0.03  
   REAL:: tau_max_p = 10.  
6    
   LOGICAL:: ncep = .false. ! Coordonnee vert NCEP ou ECMWF  
7    LOGICAL:: ini_anal = .false. ! Initial = analyse    LOGICAL:: ini_anal = .false. ! Initial = analyse
8    LOGICAL:: guide_u = .false. ! guidage de u    LOGICAL:: guide_u = .false. ! guidage de u
9    LOGICAL:: guide_v = .false. ! gvidage de v    LOGICAL:: guide_v = .false. ! gvidage de v
10    LOGICAL:: guide_t = .false. ! guidage de T    LOGICAL:: guide_t = .false. ! guidage de T
11    LOGICAL:: guide_q = .false. ! guidage de q    LOGICAL:: guide_q = .false. ! guidage de q
12    
13    logical:: online = .true. ! controle du guide    logical, save:: ok_guide ! guidage
   ! hors-ligne: x=x_rea  
14    
15    ! Latitude min et max pour le rappel dans le cas ou on 'a les    ! alpha détermine la part des injections de données à chaque étape
16    ! analyses que sur une bande de latitudes.    ! alpha=0 signifie pas d'injection
17    REAL:: lat_min_guide = -90. ! Latitude minimum pour le guidage    ! alpha=1 signifie injection totale
18    real:: lat_max_guide = 90. ! Latitude maximum pour le guidage    REAL, save:: alpha_q(iim + 1, jjm + 1)
19      REAL, save:: alpha_t(iim + 1, jjm + 1)
20      REAL, save:: alpha_u(iim + 1, jjm + 1), alpha_v(iim + 1, jjm)
21    
22    logical, save:: ok_guide ! guidage    private iim, jjm
   REAL, save:: factt ! pas de temps entre deux appels au guidage, en jours  
23    
24  contains  contains
25    
# Line 39  contains Line 28  contains
28      ! From LMDZ4/libf/dyn3d/conf_guide.F, version 1.1.1.1 2004/05/19 12:53:07      ! From LMDZ4/libf/dyn3d/conf_guide.F, version 1.1.1.1 2004/05/19 12:53:07
29      !  Parametres de controle du run:      !  Parametres de controle du run:
30    
     use abort_gcm_m, only: abort_gcm  
31      use comconst, only: daysec, dtvr      use comconst, only: daysec, dtvr
32      use conf_gcm_m, only: day_step, iperiod      use conf_gcm_m, only: day_step, iperiod
33      use nr_util, only: assert      use dynetat0_m, only: rlatu, rlatv
34      use serre, only: grossismx, grossismy      use dynetat0_chosen_m, only: grossismx, grossismy
35        use init_tau2alpha_m, only: init_tau2alpha
36        use nr_util, only: assert, pi
37        use tau2alpha_m, only: tau2alpha
38      use unit_nml_m, only: unit_nml      use unit_nml_m, only: unit_nml
39        use writefield_m, only: writefield
40    
41        ! Local:
42    
43        ! Constantes de rappel, en jours :
44        REAL tau_min_u, tau_max_u, tau_min_v, tau_max_v, tau_min_t, tau_max_t
45        real tau_min_q, tau_max_q
46    
47      namelist /conf_guide_nml/ ncep, ini_anal, guide_u, guide_v, guide_t, &      REAL lat_min_guide_deg, lat_max_guide_deg ! in degrees
48           guide_q, online, tau_min_u, tau_max_u, tau_min_v, tau_max_v, &  
49           tau_min_t, tau_max_t, tau_min_q, tau_max_q, tau_min_p, tau_max_p, &      ! Dans le cas où on n'a les analyses que sur une bande de latitudes :
50           lat_min_guide, lat_max_guide      REAL lat_min_guide ! minimum latitude for nudging, in rad
51        real lat_max_guide ! maximum latitude for nudging, in rad
52    
53        REAL factt ! pas de temps entre deux appels au guidage, en jours
54        REAL dxdys(iim + 1, jjm + 1), dxdyu(iim + 1, jjm + 1), dxdyv(iim + 1, jjm)
55        integer i, j
56    
57        namelist /conf_guide_nml/ ini_anal, guide_u, guide_v, guide_t, guide_q, &
58             tau_min_u, tau_max_u, tau_min_v, tau_max_v, tau_min_t, tau_max_t, &
59             tau_min_q, tau_max_q, lat_min_guide_deg, lat_max_guide_deg
60    
61      !-----------------------------------------------------------------------      !-----------------------------------------------------------------------
62    
63      print *, "Call sequence information: conf_guide"      print *, "Call sequence information: conf_guide"
64    
65        ! Default values:
66        tau_min_u = 0.03
67        tau_max_u = 10.
68        tau_min_v = 0.03
69        tau_max_v = 10.
70        tau_min_t = 0.03
71        tau_max_t = 10.
72        tau_min_q = 0.03
73        tau_max_q = 10.
74        lat_min_guide_deg = -90.
75        lat_max_guide_deg = 90.
76    
77      print *, "Enter namelist 'conf_guide_nml'."      print *, "Enter namelist 'conf_guide_nml'."
78      read(unit=*, nml=conf_guide_nml)      read(unit=*, nml=conf_guide_nml)
79      write(unit_nml, nml=conf_guide_nml)      write(unit_nml, nml=conf_guide_nml)
80    
81      ok_guide = any((/guide_u, guide_v, guide_t, guide_q/))      ok_guide = any((/guide_u, guide_v, guide_t, guide_q/))
     if (ok_guide .and. mod(day_step, 4 * iperiod) /= 0) call &  
          abort_gcm(modname = "conf_guide", &  
          message = 'ok_guide day_step iperiod', ierr = 1)  
82    
83      if (ok_guide .and. online) then      if (ok_guide) then
84           call assert(mod(day_step, 4 * iperiod) == 0, &
85                "conf_guide ok_guide day_step iperiod")
86           lat_min_guide = lat_min_guide_deg / 180. * pi
87           lat_max_guide = lat_max_guide_deg / 180. * pi
88         factt = dtvr * iperiod / daysec         factt = dtvr * iperiod / daysec
89         print *, "factt = ", factt         print *, "factt = ", factt
90         if (abs(grossismx - 1.) >= 0.1 .and. abs(grossismy - 1.) >= 0.1) then  
91            if (guide_u) call assert(factt / tau_min_u < 1, &         IF (abs(grossismx - 1.) < 0.1 .OR. abs(grossismy - 1.) < 0.1) THEN
92                 "conf_guide tau_min_u")            ! grille regulière
93            if (guide_v) call assert(factt / tau_min_v < 1, &            if (guide_u) alpha_u = 1. - exp(- factt / tau_max_u)
94                 "conf_guide tau_min_v")            if (guide_v) alpha_v = 1. - exp(- factt / tau_max_v)
95            if (guide_t) call assert(factt / tau_min_t < 1, &            if (guide_t) alpha_t = 1. - exp(- factt / tau_max_t)
96                 "conf_guide tau_min_t")            if (guide_q) alpha_q = 1. - exp(- factt / tau_max_q)
97            if (guide_q) call assert(factt / tau_min_q < 1, &         else
98                 "conf_guide tau_min_q")            call init_tau2alpha(dxdys)
99         end if  
100              if (guide_u) then
101                 DO j = 1, jjm + 1
102                    DO i = 1, iim
103                       dxdyu(i, j) = 0.5 * (dxdys(i, j) + dxdys(i + 1, j))
104                    END DO
105                    dxdyu(iim + 1, j) = dxdyu(1, j)
106                 END DO
107    
108                 CALL tau2alpha(lat_min_guide, lat_max_guide, factt, dxdyu, rlatu, &
109                      tau_min_u, tau_max_u, alpha_u)
110                 CALL writefield("alpha_u", alpha_u)
111              end if
112    
113              if (guide_v) then
114                 DO j = 1, jjm
115                    DO i = 1, iim + 1
116                       dxdyv(i, j) = 0.5 * (dxdys(i, j) + dxdys(i, j + 1))
117                    END DO
118                 END DO
119    
120                 CALL tau2alpha(lat_min_guide, lat_max_guide, factt, dxdyv, rlatv, &
121                      tau_min_v, tau_max_v, alpha_v)
122                 CALL writefield("alpha_v", alpha_v)
123              end if
124    
125              if (guide_t) then
126                 CALL tau2alpha(lat_min_guide, lat_max_guide, factt, dxdys, rlatu, &
127                      tau_min_t, tau_max_t, alpha_t)
128                 CALL writefield("alpha_t", alpha_t)
129              end if
130    
131              if (guide_q)  then
132                 CALL tau2alpha(lat_min_guide, lat_max_guide, factt, dxdys, rlatu, &
133                      tau_min_q, tau_max_q, alpha_q)
134                 CALL writefield("alpha_q", alpha_q)
135              end if
136           end IF
137      end if      end if
138    
139    end SUBROUTINE conf_guide    end SUBROUTINE conf_guide

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

  ViewVC Help
Powered by ViewVC 1.1.21