source: LMDZ6/trunk/libf/dyn3dmem/vlspltgen_mod.f90 @ 5308

Last change on this file since 5308 was 5285, checked in by abarral, 4 days 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: 1.3 KB
RevLine 
[1632]1MODULE vlspltgen_mod
2
3  REAL,POINTER,SAVE :: qsat(:,:)
[2270]4  REAL,POINTER,SAVE :: mu(:,:) ! CRisi: on ajoute une dimension
[1632]5  REAL,POINTER,SAVE :: mv(:,:)
[2270]6  REAL,POINTER,SAVE :: mw(:,:,:)
[1632]7  REAL,POINTER,SAVE :: zm(:,:,:)
8  REAL,POINTER,SAVE :: zq(:,:,:)
9 
10CONTAINS
11
12  SUBROUTINE vlspltgen_allocate
13  USE bands
[1810]14  USE allocate_field_mod
[1823]15  USE parallel_lmdz
[1632]16  USE infotrac
17  USE vlz_mod,ONLY : vlz_allocate
[5271]18  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]19USE paramet_mod_h
[5271]20IMPLICIT NONE
21
[5272]22
[1632]23  TYPE(distrib),POINTER :: d
24   
25    d=>distrib_vanleer
26    CALL allocate_u(qsat,llm,d)
27    CALL allocate_u(mu,llm,d)
28    CALL allocate_v(mv,llm,d)
[2270]29    CALL allocate_u(mw,llm+1,nqtot,d)
[1632]30    CALL allocate_u(zm,llm,nqtot,d)
31    CALL allocate_u(zq,llm,nqtot,d)
32
33    CALL vlz_allocate
34
35  END SUBROUTINE vlspltgen_allocate
36 
37  SUBROUTINE vlspltgen_switch_vanleer(dist)
[1810]38  USE allocate_field_mod
[1632]39  USE bands
[1823]40  USE parallel_lmdz
[1632]41  USE vlz_mod,ONLY : vlz_switch_vanleer
42  IMPLICIT NONE
43    TYPE(distrib),INTENT(IN) :: dist
44 
45    CALL switch_u(qsat,distrib_vanleer,dist)
46    CALL switch_u(mu,distrib_vanleer,dist)
47    CALL switch_u(mv,distrib_vanleer,dist)
48    CALL switch_u(mw,distrib_vanleer,dist)
49    CALL switch_u(zm,distrib_vanleer,dist)
50    CALL switch_u(zq,distrib_vanleer,dist)
51
52    CALL vlz_switch_vanleer(dist)
53
54  END SUBROUTINE vlspltgen_switch_vanleer 
55 
56END MODULE vlspltgen_mod 
Note: See TracBrowser for help on using the repository browser.