Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_ModInterfacesExternal.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: set explicit interfaces to subroutines and functions.
26 !
27 ! Description: none
28 !
29 ! Notes: none.
30 !
31 !******************************************************************************
32 !
33 ! $Id: RFLO_ModInterfacesExternal.F90,v 1.9 2008/12/06 08:44:16 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2001 by the University of Illinois
36 !
37 !******************************************************************************
38 
40 
41  IMPLICIT NONE
42 
43  INTERFACE
44 
45 ! =============================================================================
46 ! Interfaces to external code
47 ! =============================================================================
48 
49  SUBROUTINE rflo_getboundaryvalues( region )
50  USE moddatastruct, ONLY : t_region
51  TYPE(t_region) :: region
52  END SUBROUTINE rflo_getboundaryvalues
53 
54  SUBROUTINE rflo_getdeformation( region,boundMoved,dNode )
55  USE moddatatypes
56  USE moddatastruct, ONLY : t_region
57  LOGICAL :: boundmoved(6)
58  REAL(RFREAL), POINTER :: dnode(:,:)
59  TYPE(t_region) :: region
60  END SUBROUTINE rflo_getdeformation
61 
62  SUBROUTINE rflo_sendboundaryvalues( region,initialize )
63  USE moddatastruct, ONLY : t_region
64  TYPE(t_region) :: region
65  LOGICAL :: initialize
66  END SUBROUTINE rflo_sendboundaryvalues
67 
68  SUBROUTINE rflo_sendboundaryvaluesalpha( region )
69  USE moddatastruct, ONLY : t_region
70  TYPE(t_region) :: region
71  LOGICAL :: initialize
72  END SUBROUTINE rflo_sendboundaryvaluesalpha
73 
74 #ifdef GENX
75  SUBROUTINE fluid_finalize( globalGenx )
76  USE modrocstar, ONLY : t_globalgenx
77  TYPE(t_globalgenx), POINTER :: globalgenx
78  END SUBROUTINE fluid_finalize
79 
80  SUBROUTINE fluid_prehdfoutput( globalGenx )
81  USE modrocstar, ONLY : t_globalgenx
82  TYPE(t_globalgenx), POINTER :: globalgenx
83  END SUBROUTINE fluid_prehdfoutput
84 
85  SUBROUTINE fluid_posthdfoutput( globalGenx )
86  USE modrocstar, ONLY : t_globalgenx
87  TYPE(t_globalgenx), POINTER :: globalgenx
88  END SUBROUTINE fluid_posthdfoutput
89 
90  SUBROUTINE rflo_flowsolverdummy( globalGenx,timeSystem,dTimeSystem, &
91  genxhandlebc,genxhandlegm )
92  USE moddatatypes
93  USE modrocstar, ONLY : t_globalgenx
94  INTEGER, INTENT(in) :: genxhandlebc, genxhandlegm
95  DOUBLE PRECISION, INTENT(in) :: timesystem, dtimesystem
96  TYPE(t_globalgenx), POINTER :: globalgenx
97  END SUBROUTINE rflo_flowsolverdummy
98 
99  SUBROUTINE rflo_initgenxinterface( regions,handle,solver,inSurf,inVol, &
101  USE moddatastruct, ONLY : t_region
102  CHARACTER(*) :: insurf, invol
103  INTEGER :: handle, solver, obtain_attribute
104  TYPE(t_region), POINTER :: regions(:)
105  END SUBROUTINE rflo_initgenxinterface
106 
107  SUBROUTINE rflo_updateinbuffgm( globalGenx,dAlpha )
108  USE moddatatypes
109  USE modrocstar, ONLY : t_globalgenx
110  DOUBLE PRECISION, INTENT(in) :: dalpha
111  TYPE(t_globalgenx), POINTER :: globalgenx
112  END SUBROUTINE rflo_updateinbuffgm
113 
114 #ifdef PEUL
115  SUBROUTINE peul_initgenxinterface( regions,wins,winv )
116  USE moddatatypes
117  USE moddatastruct, ONLY : t_region
118  TYPE(t_region), POINTER :: regions(:)
119  CHARACTER(CHRLEN) :: wins, winv
120  END SUBROUTINE peul_initgenxinterface
121 #endif
122 
123 #ifdef PLAG
124  SUBROUTINE plag_initgenxinterface( regions, wins, inPlag, obtain_attribute )
125  USE moddatatypes
126  USE moddatastruct, ONLY : t_region
127  TYPE(t_region), POINTER :: regions(:)
128  CHARACTER(CHRLEN) :: wins, inplag
129  INTEGER :: obtain_attribute
130  END SUBROUTINE plag_initgenxinterface
131 
132  SUBROUTINE plag_setsizegenx( region )
133  USE moddatatypes
134  USE moddatastruct, ONLY : t_region
135  TYPE(t_region) :: region
136  END SUBROUTINE plag_setsizegenx
137 #endif
138 
139 #ifdef RADI
140  SUBROUTINE radi_initgenxinterface( regions,wins,winv )
141  USE moddatatypes
142  USE moddatastruct, ONLY : t_region
143  TYPE(t_region), POINTER :: regions(:)
144  CHARACTER(CHRLEN) :: wins, winv
145  END SUBROUTINE radi_initgenxinterface
146 #endif
147 #ifdef TURB
148  SUBROUTINE turb_initgenxinterface( regions,wins,winv )
149  USE moddatatypes
150  USE moddatastruct, ONLY : t_region
151  TYPE(t_region), POINTER :: regions(:)
152  CHARACTER(CHRLEN) :: wins, winv
153  END SUBROUTINE turb_initgenxinterface
154 #endif
155 
156  SUBROUTINE randinitgenxinterface( regions,wins,winv )
157  USE moddatatypes
158  USE moddatastruct, ONLY : t_region
159  TYPE(t_region), POINTER :: regions(:)
160  CHARACTER(CHRLEN) :: wins, winv
161  END SUBROUTINE randinitgenxinterface
162 #endif
163 
164  END INTERFACE
165 
167 
168 !******************************************************************************
169 !
170 ! RCS Revision history:
171 !
172 ! $Log: RFLO_ModInterfacesExternal.F90,v $
173 ! Revision 1.9 2008/12/06 08:44:16 mtcampbe
174 ! Updated license.
175 !
176 ! Revision 1.8 2008/11/19 22:17:27 mtcampbe
177 ! Added Illinois Open Source License/Copyright
178 !
179 ! Revision 1.7 2005/12/08 19:57:37 wasistho
180 ! added postHdfOutput
181 !
182 ! Revision 1.6 2005/12/08 00:20:59 wasistho
183 ! added Fluid_preHdfOutput
184 !
185 ! Revision 1.5 2004/07/02 22:04:22 fnajjar
186 ! Updated and added PLAG interface calls
187 !
188 ! Revision 1.4 2004/06/29 23:58:29 wasistho
189 ! migrated to Roccom-3
190 !
191 ! Revision 1.3 2003/11/21 22:37:16 fnajjar
192 ! Added PLAG and PEUL GenX interfaces
193 !
194 ! Revision 1.2 2003/08/09 02:02:46 wasistho
195 ! added TURB and RADI_initGenxInterface
196 !
197 ! Revision 1.1 2002/12/27 22:07:14 jblazek
198 ! Splitted up RFLO_ModInterfaces and ModInterfaces.
199 !
200 !******************************************************************************
201 
202 
203 
204 
205 
206 
size_t handle(const msq_std::string &name, MsqError &err) const
Get tag index from name.
subroutine rflo_updateinbuffgm(globalGenx, dAlpha)
subroutine initialize(G_b, MAN_INIT, inSurf, inInt, INIT_0D, INIT_1D, IN_obt_attr)
Definition: rocburn_2D.f90:83
subroutine radi_initgenxinterface(regions, wins, winv)
subroutine rflo_flowsolverdummy(globalGenx, timeSystem, dTimeSystem, genxHandleBc, genxHandleGm)
subroutine fluid_posthdfoutput(globalGenx)
subroutine plag_setsizegenx(region)
subroutine turb_initgenxinterface(regions, wins, winv)
subroutine rflo_sendboundaryvaluesalpha(region)
subroutine rflo_getdeformation(region, boundMoved, dNode)
subroutine rflo_sendboundaryvalues(region, initialize)
subroutine rflo_getboundaryvalues(region)
subroutine randinitgenxinterface(regions, wins, winv)
subroutine fluid_finalize(globalGenx)
void obtain_attribute(const COM::Attribute *attribute_in, COM::Attribute *user_attribute, int *pane_id=NULL)
Fill the destination (second) attribute from files using the data corresponding to the source (first)...
Definition: Rocin.C:2431
subroutine fluid_prehdfoutput(globalGenx)
subroutine peul_initgenxinterface(regions, wins, winv)
subroutine rflo_initgenxinterface(regions, handle, solver, inSurf, inVolPlag, obtain_attribute)
subroutine plag_initgenxinterface(regions, wins, inPlag, obtain_attribute)