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

« back to all changes in this revision

Viewing changes to src/base/albase.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
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
4
!
 
5
! Copyright (C) 1998-2011 EDF S.A.
 
6
!
 
7
! This program is free software; you can redistribute it and/or modify it under
 
8
! the terms of the GNU General Public License as published by the Free Software
 
9
! Foundation; either version 2 of the License, or (at your option) any later
 
10
! version.
 
11
!
 
12
! This program is distributed in the hope that it will be useful, but WITHOUT
 
13
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
14
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
15
! details.
 
16
!
 
17
! You should have received a copy of the GNU General Public License along with
 
18
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
19
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
 
20
 
 
21
!-------------------------------------------------------------------------------
 
22
 
 
23
! Module for multigrid parameters
 
24
 
 
25
module albase
 
26
 
 
27
  !=============================================================================
 
28
 
 
29
  !  Methode ale
 
30
  !  iale   : utilisation de la methode ALE
 
31
  !         = 0 sans methode ALE
 
32
  !         = 1 avec methode ALE
 
33
  !  nalinf : nombre d'iterations d'initialisation du fluide
 
34
  !  nalimx : nombre maximal d'iterations d'implicitation du deplacement
 
35
  !           des structures
 
36
  !  iortvm : type de viscosite de maillage
 
37
  !         = 0 isotrope
 
38
  !         = 1 orthotrope
 
39
  !  epalim : precision relative d'implicitation du deplacement des
 
40
  !           structures
 
41
  !  italin : iteration d'initialisation de l'ALE
 
42
  !         = 0 non
 
43
  !         = 1 oui
 
44
 
 
45
  integer, save :: iale  , nalinf
 
46
  integer, save :: nalimx, iortvm, italin
 
47
 
 
48
  double precision, save :: epalim
 
49
 
 
50
  !  impale : indicateur de deplacement impose
 
51
  !  xyzno0 : position initiale du maillage
 
52
  !  depale : deplacement du maillage
 
53
  !  ialtyb : type de bord
 
54
 
 
55
  integer, allocatable, dimension(:) :: impale, ialtyb
 
56
 
 
57
  double precision, allocatable, dimension(:,:) :: xyzno0, depale
 
58
 
 
59
contains
 
60
 
 
61
  !=============================================================================
 
62
 
 
63
  subroutine init_ale ( ncelet , ncel , nfac , nfabor , nnod )
 
64
 
 
65
    use cplsat
 
66
 
 
67
    ! Arguments
 
68
 
 
69
    integer, intent(in) :: ncelet, ncel, nfac, nfabor, nnod
 
70
 
 
71
    if (iale.eq.1.or.imobil.eq.1) then
 
72
      allocate(xyzno0(3,nnod))
 
73
    endif
 
74
 
 
75
    if (iale.eq.1) then
 
76
      allocate(impale(nnod))
 
77
      allocate(ialtyb(nfabor))
 
78
      allocate(depale(nnod,3))
 
79
    endif
 
80
 
 
81
  end subroutine init_ale
 
82
 
 
83
  !=============================================================================
 
84
 
 
85
  subroutine finalize_ale
 
86
 
 
87
    use cplsat
 
88
 
 
89
    if (iale.eq.1.or.imobil.eq.1) then
 
90
      deallocate(xyzno0)
 
91
    endif
 
92
 
 
93
    if (iale.eq.1) then
 
94
      deallocate(impale)
 
95
      deallocate(depale)
 
96
      deallocate(ialtyb)
 
97
    endif
 
98
 
 
99
  end subroutine finalize_ale
 
100
 
 
101
  !=============================================================================
 
102
 
 
103
end module albase