LMDZ
leapfrog_mod.F90
Go to the documentation of this file.
2 
3  REAL,POINTER,SAVE :: ucov(:,:) ! zonal covariant wind
4  REAL,POINTER,SAVE :: vcov(:,:) ! meridional covariant wind
5  REAL,POINTER,SAVE :: teta(:,:) ! potential temperature
6  REAL,POINTER,SAVE :: ps(:) ! surface pressure
7  REAL,POINTER,SAVE :: masse(:,:) ! air mass
8  REAL,POINTER,SAVE :: phis(:) ! geopotential at the surface
9  REAL,POINTER,SAVE :: q(:,:,:) ! advected tracers
10  REAL,POINTER,SAVE :: p(:,:) ! interlayer pressure
11  REAL,POINTER,SAVE :: pks(:) ! Exner at the surface
12  REAL,POINTER,SAVE :: pk(:,:) ! Exner at mid-layer
13  REAL,POINTER,SAVE :: pkf(:,:) ! filtered Exner
14  REAL,POINTER,SAVE :: phi(:,:) ! geopotential
15  REAL,POINTER,SAVE :: w(:,:) ! vertical velocity
16  REAL,POINTER,SAVE :: pbaru(:,:)
17  REAL,POINTER,SAVE :: pbarv(:,:)
18  REAL,POINTER,SAVE :: vcovm1(:,:)
19  REAL,POINTER,SAVE :: ucovm1(:,:)
20  REAL,POINTER,SAVE :: tetam1(:,:)
21  REAL,POINTER,SAVE :: psm1(:)
22  REAL,POINTER,SAVE :: massem1(:,:)
23  REAL,POINTER,SAVE :: dv(:,:)
24  REAL,POINTER,SAVE :: du(:,:)
25  REAL,POINTER,SAVE :: dteta(:,:)
26  REAL,POINTER,SAVE :: dp(:)
27  REAL,POINTER,SAVE :: dq(:,:,:)
28  REAL,POINTER,SAVE :: finvmaold(:,:)
29  REAL,POINTER,SAVE :: flxw(:,:)
30  REAL,POINTER,SAVE :: unat(:,:)
31  REAL,POINTER,SAVE :: vnat(:,:)
32 
33 
34 
35 CONTAINS
36 
37  SUBROUTINE leapfrog_allocate
38  USE bands
40  USE parallel_lmdz
41  USE dimensions_mod
42  USE infotrac
43  USE caldyn_mod,ONLY : caldyn_allocate
44  USE integrd_mod,ONLY : integrd_allocate
48  IMPLICIT NONE
49  TYPE(distrib),POINTER :: d
50 
51 
53  CALL allocate_u(ucov,llm,d)
54  CALL allocate_v(vcov,llm,d)
55  CALL allocate_u(teta,llm,d)
56  CALL allocate_u(ps,d)
57  CALL allocate_u(masse,llm,d)
58  CALL allocate_u(phis,d)
59  CALL allocate_u(q,llm,nqtot,d)
60  CALL allocate_u(p,llmp1,d)
61  CALL allocate_u(pks,d)
62  CALL allocate_u(pk,llm,d)
63  CALL allocate_u(pkf,llm,d)
64  CALL allocate_u(phi,llm,d)
65  CALL allocate_u(w,llm,d)
66  CALL allocate_u(pbaru,llm,d)
67  CALL allocate_v(pbarv,llm,d)
68  CALL allocate_v(vcovm1,llm,d)
69  CALL allocate_u(ucovm1,llm,d)
70  CALL allocate_u(tetam1,llm,d)
71  CALL allocate_u(psm1,d)
72  CALL allocate_u(massem1,llm,d)
73  CALL allocate_v(dv,llm,d)
74  CALL allocate_u(du,llm,d)
75  CALL allocate_u(dteta,llm,d)
76  CALL allocate_u(dp,d)
77  CALL allocate_u(dq,llm,nqtot,d)
78  CALL allocate_u(finvmaold,llm,d)
79  CALL allocate_u(flxw,llm,d)
80  CALL allocate_u(unat,llm,d)
81  CALL allocate_v(vnat,llm,d)
82 
83  CALL caldyn_allocate
84  CALL integrd_allocate
88 
89  END SUBROUTINE leapfrog_allocate
90 
91  SUBROUTINE leapfrog_switch_caldyn(dist)
93  USE bands
94  USE parallel_lmdz
98  IMPLICIT NONE
99  TYPE(distrib),INTENT(IN) :: dist
100 
101  CALL switch_u(ucov,distrib_caldyn,dist)
102  CALL switch_v(vcov,distrib_caldyn,dist)
103  CALL switch_u(teta,distrib_caldyn,dist)
104  CALL switch_u(ps,distrib_caldyn,dist)
105  CALL switch_u(masse,distrib_caldyn,dist)
106  CALL switch_u(phis,distrib_caldyn,dist,up=halo_max,down=halo_max)
107  CALL switch_u(q,distrib_caldyn,dist)
108  CALL switch_u(p,distrib_caldyn,dist)
109  CALL switch_u(pks,distrib_caldyn,dist)
110  CALL switch_u(pk,distrib_caldyn,dist)
111  CALL switch_u(pkf,distrib_caldyn,dist)
112  CALL switch_u(phi,distrib_caldyn,dist)
113  CALL switch_u(w,distrib_caldyn,dist)
114  CALL switch_u(pbaru,distrib_caldyn,dist)
115  CALL switch_v(pbarv,distrib_caldyn,dist)
116  CALL switch_v(vcovm1,distrib_caldyn,dist)
117  CALL switch_u(ucovm1,distrib_caldyn,dist)
118  CALL switch_u(tetam1,distrib_caldyn,dist)
119  CALL switch_u(psm1,distrib_caldyn,dist)
120  CALL switch_u(massem1,distrib_caldyn,dist)
121  CALL switch_v(dv,distrib_caldyn,dist)
122  CALL switch_u(du,distrib_caldyn,dist)
123  CALL switch_u(dteta,distrib_caldyn,dist)
124  CALL switch_u(dp,distrib_caldyn,dist)
125  CALL switch_u(dq,distrib_caldyn,dist)
127  CALL switch_u(flxw,distrib_caldyn,dist)
128  CALL switch_u(unat,distrib_caldyn,dist)
129  CALL switch_v(vnat,distrib_caldyn,dist)
130 
131 
132  CALL caldyn_switch_caldyn(dist)
133  CALL integrd_switch_caldyn(dist)
134  CALL caladvtrac_switch_caldyn(dist)
135 
136  END SUBROUTINE leapfrog_switch_caldyn
137 
138  SUBROUTINE leapfrog_switch_dissip(dist)
140  USE bands
141  USE parallel_lmdz
143  IMPLICIT NONE
144  TYPE(distrib),INTENT(IN) :: dist
145 
146  CALL call_dissip_switch_dissip(dist)
147 
148  END SUBROUTINE leapfrog_switch_dissip
149 
150 END MODULE leapfrog_mod
151 
152 
153 
154 
155 
156 
157 
real, dimension(:,:,:), pointer, save q
Definition: leapfrog_mod.F90:9
Definition: bands.F90:4
real, dimension(:,:,:), pointer, save dq
real, dimension(:,:), pointer, save pkf
real, dimension(:,:), pointer, save pbarv
real, dimension(:,:), pointer, save dv
subroutine call_dissip_switch_dissip(dist)
!$Header llmp1
Definition: paramet.h:14
subroutine integrd_switch_caldyn(dist)
Definition: integrd_mod.F90:30
real, dimension(:,:), pointer, save unat
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
real, dimension(:,:), pointer, save vcov
Definition: leapfrog_mod.F90:4
subroutine caldyn_allocate
Definition: caldyn_mod.F90:21
integer, save nqtot
Definition: infotrac.F90:6
real, dimension(:,:), pointer, save w
real, dimension(:), pointer, save pks
subroutine leapfrog_allocate
real, dimension(:,:), pointer, save p
subroutine leapfrog_switch_caldyn(dist)
real, dimension(:,:), pointer, save vnat
real, dimension(:,:), pointer, save teta
Definition: leapfrog_mod.F90:5
real, dimension(:,:), pointer, save flxw
real, dimension(:,:), pointer, save phi
subroutine caladvtrac_allocate
real, dimension(:), pointer, save phis
Definition: leapfrog_mod.F90:8
real, dimension(:), pointer, save dp
integer, parameter halo_max
real, dimension(:,:), pointer, save pbaru
subroutine call_calfis_allocate
real, dimension(:,:), pointer, save finvmaold
real, dimension(:,:), pointer, save tetam1
subroutine call_dissip_allocate
real, dimension(:), pointer, save psm1
real, dimension(:,:), pointer, save ucovm1
real, dimension(:,:), pointer, save ucov
Definition: leapfrog_mod.F90:3
real, dimension(:), pointer, save ps
Definition: leapfrog_mod.F90:6
subroutine caldyn_switch_caldyn(dist)
Definition: caldyn_mod.F90:49
subroutine caladvtrac_switch_caldyn(dist)
subroutine integrd_allocate
Definition: integrd_mod.F90:12
real, dimension(:,:), pointer, save vcovm1
real, dimension(:,:), pointer, save dteta
type(distrib), target, save distrib_caldyn
Definition: bands.F90:17
real, dimension(:,:), pointer, save massem1
real, dimension(:,:), pointer, save du
real, dimension(:,:), pointer, save masse
Definition: leapfrog_mod.F90:7
subroutine leapfrog_switch_dissip(dist)
real, dimension(:,:), pointer, save pk