source: codes/icosagcm/trunk/src/transport/tracer.f90 @ 548

Last change on this file since 548 was 548, checked in by dubos, 7 years ago

trunk : reorganize source tree

File size: 943 bytes
Line 
1MODULE tracer_mod
2
3  INTEGER, PARAMETER   :: advect_none    = 0
4  INTEGER, PARAMETER   :: advect_vanleer = 1
5  INTEGER, ALLOCATABLE,SAVE :: advection_scheme(:)
6!$OMP THREADPRIVATE(advection_scheme)
7 
8  INTERFACE set_advection_scheme
9    MODULE PROCEDURE set_advection_scheme_1, set_advection_scheme_full
10  END INTERFACE
11
12CONTAINS
13
14  SUBROUTINE init_tracer
15  USE grid_param
16  IMPLICIT NONE
17   
18    ALLOCATE(advection_scheme(nqtot))
19    advection_scheme(:) = advect_vanleer 
20
21  END SUBROUTINE init_tracer
22
23  SUBROUTINE set_advection_scheme_1(nq,scheme)
24  IMPLICIT NONE
25    INTEGER, INTENT(IN) :: nq
26    INTEGER, INTENT(IN) :: scheme
27   
28    advection_scheme(nq)=scheme
29 
30  END SUBROUTINE set_advection_scheme_1
31
32  SUBROUTINE set_advection_scheme_full(schemes)
33  USE grid_param
34  IMPLICIT NONE
35    INTEGER, INTENT(IN) :: schemes(nqtot)
36 
37    advection_scheme(:)=schemes(:)
38 
39  END SUBROUTINE set_advection_scheme_full
40
41END MODULE tracer_mod
Note: See TracBrowser for help on using the repository browser.