source: codes/icosagcm/trunk/src/vertical/disvert_plugin.f90

Last change on this file was 1057, checked in by millour, 3 years ago

Add a "plugin" option to disvert. Only the interface to the plugin is present inthe realted disvert_plugin.f90; a placeholder for a user-provided routine set byan external driver.
EM

File size: 1.1 KB
Line 
1MODULE disvert_plugin_mod
2  USE prec, ONLY: rstd
3  IMPLICIT NONE
4  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:)
5!$OMP THREADPRIVATE(ap)
6  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: bp(:)
7!$OMP THREADPRIVATE(bp)
8  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: presnivs(:)
9!$OMP THREADPRIVATE(presnivs)
10
11  INTERFACE
12    SUBROUTINE plugin_disvert(ap,bp,presnivs)
13      REAL,INTENT(OUT) :: ap(:)
14      REAL,INTENT(OUT) :: bp(:)
15      REAL,INTENT(OUT) :: presnivs(:)
16    END SUBROUTINE
17  END INTERFACE
18 
19  PROCEDURE(plugin_disvert), POINTER :: disvert_plugin => NULL()
20
21CONTAINS
22
23  SUBROUTINE init_disvert
24
25  USE grid_param, ONLY: llm
26  USE abort_mod, ONLY: dynamico_abort
27
28  IMPLICIT NONE
29 
30    ALLOCATE(ap(llm+1))
31    ALLOCATE(bp(llm+1))
32    ALLOCATE(presnivs(llm))
33
34    IF(.NOT.ASSOCIATED(disvert_plugin)) THEN
35      WRITE(*,*) "Fatal Error: option disvert=plugin is selected ",&
36                 "but disvert_plugin not set by driver"
37       CALL dynamico_abort("init_disvert : disvert_plugin not set")
38    ENDIF
39
40    CALL disvert_plugin(ap,bp,presnivs)   
41
42  END SUBROUTINE init_disvert 
43
44END MODULE disvert_plugin_mod
Note: See TracBrowser for help on using the repository browser.