source: LMDZ6/trunk/libf/dyn3dmem/caldyn_mod.f90 @ 5407

Last change on this file since 5407 was 5285, checked in by abarral, 7 weeks ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 2.0 KB
RevLine 
[1632]1MODULE caldyn_mod
2
3  REAL,POINTER,SAVE :: vcont(:,:)
4  REAL,POINTER,SAVE :: ucont(:,:)
5  REAL,POINTER,SAVE :: ang(:,:)
6  REAL,POINTER,SAVE :: p(:,:)
7  REAL,POINTER,SAVE :: massebx(:,:)
8  REAL,POINTER,SAVE :: masseby(:,:)
9  REAL,POINTER,SAVE :: psexbarxy(:,:)
10  REAL,POINTER,SAVE :: vorpot(:,:)
11  REAL,POINTER,SAVE :: ecin(:,:)
12  REAL,POINTER,SAVE :: bern(:,:)
13  REAL,POINTER,SAVE :: massebxy(:,:)
14  REAL,POINTER,SAVE :: convm(:,:)
15
16
[5272]17
[1632]18CONTAINS
19
20  SUBROUTINE caldyn_allocate
21  USE bands
[1810]22  USE allocate_field_mod
[1823]23  USE parallel_lmdz
[5272]24  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]25  USE paramet_mod_h
[5272]26  USE advect_new_mod, ONLY : advect_new_allocate
[1632]27  IMPLICIT NONE
28  TYPE(distrib),POINTER :: d
29
30
31    d=>distrib_caldyn
32    CALL allocate_v(vcont,llm,d)
33    CALL allocate_u(ucont,llm,d)
34    CALL allocate_u(ang,llm,d)
35    CALL allocate_u(p,llmp1,d)
36    CALL allocate_u(massebx,llm,d)
37    CALL allocate_v(masseby,llm,d)
38    CALL allocate_v(psexbarxy,llm,d)
39    CALL allocate_v(vorpot,llm,d)
40    CALL allocate_u(ecin,llm,d)
41    CALL allocate_u(bern,llm,d)
42    CALL allocate_v(massebxy,llm,d)
43    CALL allocate_u(convm,llm,d)
[5272]44
[1632]45    CALL advect_new_allocate
[5272]46
[1632]47  END SUBROUTINE caldyn_allocate
[5272]48
[1632]49  SUBROUTINE caldyn_switch_caldyn(dist)
[1810]50  USE allocate_field_mod
[1632]51  USE bands
[1823]52  USE parallel_lmdz
[1632]53  USE advect_new_mod,ONLY : advect_new_switch_caldyn
54  IMPLICIT NONE
55    TYPE(distrib),INTENT(IN) :: dist
56
57    CALL switch_v(vcont,distrib_caldyn,dist)
58    CALL switch_u(ucont,distrib_caldyn,dist)
59    CALL switch_u(ang,distrib_caldyn,dist)
60    CALL switch_u(p,distrib_caldyn,dist)
61    CALL switch_u(massebx,distrib_caldyn,dist)
62    CALL switch_v(masseby,distrib_caldyn,dist)
63    CALL switch_v(psexbarxy,distrib_caldyn,dist)
64    CALL switch_v(vorpot,distrib_caldyn,dist)
65    CALL switch_u(ecin,distrib_caldyn,dist)
66    CALL switch_u(bern,distrib_caldyn,dist)
67    CALL switch_v(massebxy,distrib_caldyn,dist)
68    CALL switch_u(convm,distrib_caldyn,dist)
[5272]69
[1632]70    CALL advect_new_switch_caldyn(dist)
[5272]71
[1632]72  END SUBROUTINE caldyn_switch_caldyn
73
[5272]74
75
76END MODULE caldyn_mod
Note: See TracBrowser for help on using the repository browser.