~ubuntu-branches/ubuntu/precise/code-saturne/precise

« back to all changes in this revision

Viewing changes to users/base/ussatc.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-24 00:00:08 UTC
  • mfrom: (6.1.9 sid)
  • Revision ID: package-import@ubuntu.com-20111124000008-2vo99e38267942q5
Tags: 2.1.0-3
Install a missing file

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
!-------------------------------------------------------------------------------
2
 
 
3
 
!VERS
4
 
 
5
 
 
6
 
!     This file is part of the Code_Saturne Kernel, element of the
7
 
!     Code_Saturne CFD tool.
8
 
 
9
 
!     Copyright (C) 1998-2009 EDF S.A., France
10
 
 
11
 
!     contact: saturne-support@edf.fr
12
 
 
13
 
!     The Code_Saturne Kernel is free software; you can redistribute it
14
 
!     and/or modify it under the terms of the GNU General Public License
15
 
!     as published by the Free Software Foundation; either version 2 of
16
 
!     the License, or (at your option) any later version.
17
 
 
18
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
19
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
20
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
21
 
!     GNU General Public License for more details.
22
 
 
23
 
!     You should have received a copy of the GNU General Public License
24
 
!     along with the Code_Saturne Kernel; if not, write to the
25
 
!     Free Software Foundation, Inc.,
26
 
!     51 Franklin St, Fifth Floor,
27
 
!     Boston, MA  02110-1301  USA
28
 
 
29
 
!-------------------------------------------------------------------------------
30
 
 
31
 
subroutine ussatc &
32
 
!================
33
 
 
34
 
( )
35
 
 
36
 
!===============================================================================
37
 
! Purpose:
38
 
! -------
39
 
 
40
 
!    User subroutine.
41
 
 
42
 
!    Define couplings with Code_Saturne itself.
43
 
 
44
 
!-------------------------------------------------------------------------------
45
 
! Arguments
46
 
!__________________.____._____.________________________________________________.
47
 
! name             !type!mode ! role                                           !
48
 
!__________________!____!_____!________________________________________________!
49
 
!__________________!____!_____!________________________________________________!
50
 
 
51
 
!     Type: i (integer), r (real), s (string), a (array), l (logical),
52
 
!           and composite types (ex: ra real array)
53
 
!     mode: <-- input, --> output, <-> modifies data, --- work array
54
 
!===============================================================================
55
 
 
56
 
implicit none
57
 
 
58
 
!===============================================================================
59
 
! Common blocks
60
 
!===============================================================================
61
 
 
62
 
include "paramx.h"
63
 
include "entsor.h"
64
 
include "parall.h"
65
 
 
66
 
!===============================================================================
67
 
 
68
 
! Arguments
69
 
 
70
 
! Local variables
71
 
 
72
 
character*32     namsat
73
 
integer          numsat, nbcsat, ii
74
 
integer          iwarns
75
 
 
76
 
!===============================================================================
77
 
 
78
 
 
79
 
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
80
 
!===============================================================================
81
 
 
82
 
if(1.eq.1) return
83
 
 
84
 
!===============================================================================
85
 
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_END
86
 
 
87
 
numsat = -1
88
 
iwarns = 1
89
 
 
90
 
nbcsat = 2
91
 
 
92
 
! In the case of a coupling between two Code_Saturne instances, the
93
 
! 'numsat' and 'namsat' arguments of 'defsat' are ignored.
94
 
 
95
 
! In case of multiple couplings, a coupling will be matched with available
96
 
! Code_Saturne instances prioritarily based on the 'namsat' (Code_Saturne
97
 
! instance name) argument, then on the 'numsat' (Code_Saturne instance
98
 
! application number) argument.
99
 
 
100
 
! If 'namsat' is empty, matching will be based on 'numsat' only.
101
 
 
102
 
! The arguments to defsat are:
103
 
!   numsat <-- matching Code_Saturne application id, or -1
104
 
!   namsat <-- matching Code_Saturne application name
105
 
!   crtcsu <-- cell selection criteria for support
106
 
!   crtfsu <-- boundary face selection criteria for support (not functional)
107
 
!   crtccp <-- cell selection criteria for coupled cells
108
 
!   crtfcp <-- boundary face selection criteria for coupled faces
109
 
!   iwarns <-- verbosity level
110
 
 
111
 
! Loop on Code_Saturne couplings
112
 
 
113
 
do ii = 1, nbcsat
114
 
 
115
 
  ! Example: coupling  with instance number 1
116
 
  !    - coupled faces of color 3 or 4
117
 
  !    - all cells available as localization support for instance 'SATURNE_01'
118
 
 
119
 
  if (ii .eq. 1) then
120
 
 
121
 
    numsat = 1
122
 
 
123
 
    call defsat(numsat, namsat, 'all[]', ' ', ' ', '3 or 4', iwarns)
124
 
    !==========
125
 
 
126
 
  ! Example: coupling  with instance number 3
127
 
  !    - coupled faces of group 'coupled_faces'
128
 
  !    - coupled cells (every cell overlapping the distant mesh)
129
 
  !    - all cells available as localization support for instance 'SATURNE_02'
130
 
 
131
 
  else if (ii .eq. 2) then
132
 
 
133
 
    numsat = 3
134
 
 
135
 
    call defsat(numsat, namsat, 'all[]', ' ', 'all[]', 'coupled_faces', iwarns)
136
 
    !==========
137
 
 
138
 
  endif
139
 
 
140
 
enddo
141
 
 
142
 
return
143
 
end subroutine