!/*****************************************************************************/1! *2! * Elmer, A Finite Element Software for Multiphysical Problems3! *4! * Copyright 1st April 1995 - , CSC - IT Center for Science Ltd., Finland5! *6! * This library is free software; you can redistribute it and/or7! * modify it under the terms of the GNU Lesser General Public8! * License as published by the Free Software Foundation; either9! * version 2.1 of the License, or (at your option) any later version.10! *11! * This library is distributed in the hope that it will be useful,12! * but WITHOUT ANY WARRANTY; without even the implied warranty of13! * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU14! * Lesser General Public License for more details.15! *16! * You should have received a copy of the GNU Lesser General Public17! * License along with this library (in file ../LGPL-2.1); if not, write18! * to the Free Software Foundation, Inc., 51 Franklin Street,19! * Fifth Floor, Boston, MA 02110-1301 USA20! *21! *****************************************************************************/22!23!/******************************************************************************24! *25! * Authors: Juha Ruokolainen26! * Email: [email protected]27! * Web: http://www.csc.fi/elmer28! * Address: CSC - IT Center for Science Ltd.29! * Keilaranta 1430! * 02101 Espoo, Finland31! *32! * Original Date: 01 Oct 199633! *34! ****************************************************************************/3536!> \ingroup ElmerLib37!> \{3839!-----------------------------------------------------------------------------40!> Module defining coordinate systems.41!-----------------------------------------------------------------------------4243MODULE CoordinateSystems4445USE Types4647IMPLICIT NONE4849INTEGER, PARAMETER :: Cartesian = 150INTEGER, PARAMETER :: Cylindric = 2, CylindricSymmetric = 3, AxisSymmetric = 451INTEGER, PARAMETER :: Polar = 552INTEGER :: Coordinates = Cartesian5354!----------------------------------------------------------------------------55CONTAINS56!----------------------------------------------------------------------------575859!----------------------------------------------------------------------------60FUNCTION CylindricalMetric( r,z,t ) RESULT(metric)6162REAL(KIND=dp) :: r,z,t63REAL(KIND=dp), DIMENSION(3,3) :: Metric6465Metric = 0.0d066Metric(1,1) = 1.0d067Metric(2,2) = 1.0d068Metric(3,3) = 1.0d069IF ( r /= 0.0d0 ) Metric(3,3) = 1.0d0 / (r**2)70END FUNCTION CylindricalMetric71!----------------------------------------------------------------------------727374!----------------------------------------------------------------------------75FUNCTION CylindricalSqrtMetric( r,z,t ) RESULT(s)7677REAL(KIND=dp) :: r,z,t,s7879s = r80END FUNCTION CylindricalSqrtMetric81!----------------------------------------------------------------------------828384!----------------------------------------------------------------------------85FUNCTION CylindricalSymbols( r,z,t ) RESULT(symbols)86REAL(KIND=dp) :: r,z,t8788REAL(KIND=dp), DIMENSION(3,3,3) :: symbols8990Symbols = 0.0d091Symbols(3,3,1) = -r9293IF ( r /= 0.0d0 ) THEN94Symbols(1,3,3) = 1.0d0 / r95Symbols(3,1,3) = 1.0d0 / r96END IF97END FUNCTION CylindricalSymbols98!----------------------------------------------------------------------------99100101!----------------------------------------------------------------------------102FUNCTION CylindricalDerivSymbols( r,z,t ) RESULT(dsymbols)103REAL(KIND=dp) :: r,z,t104105REAL(KIND=dp), DIMENSION(3,3,3,3) :: dsymbols106107dSymbols = 0.0d0108dSymbols(3,3,1,1) = -1.0d0109110IF ( r /= 0.0 ) THEN111dSymbols(1,3,3,1) = -1.0d0 / (r**2)112dSymbols(3,1,3,1) = -1.0d0 / (r**2)113END IF114END FUNCTION CylindricalDerivSymbols115!----------------------------------------------------------------------------116117118!----------------------------------------------------------------------------119FUNCTION PolarMetric( r,p,t ) RESULT(Metric)120REAL(KIND=dp) :: r,p,t121INTEGER :: i122REAL(KIND=dp), DIMENSION(3,3) :: Metric123124Metric = 0.0d0125DO i=1,3126Metric(i,i) = 1.0d0127END DO128129IF ( r /= 0.0d0 ) THEN130Metric(2,2) = 1.0d0 / (r**2 * COS(t)**2)131IF ( CoordinateSystemDimension() == 3 ) THEN132Metric(3,3) = 1.0d0 / r**2133END IF134END IF135END FUNCTION PolarMetric136!----------------------------------------------------------------------------137138139!----------------------------------------------------------------------------140FUNCTION PolarSqrtMetric( r,p,t ) RESULT(s)141REAL(KIND=dp) :: r,p,t,s142143IF ( CoordinateSystemDimension() == 2 ) THEN144s = SQRT( r**2 * COS(t)**2 )145ELSE146s = SQRT( r**4 * COS(t)**2 )147END IF148END FUNCTION PolarSqrtMetric149!----------------------------------------------------------------------------150151152!----------------------------------------------------------------------------153FUNCTION PolarSymbols( r,p,t ) RESULT(symbols)154REAL(KIND=dp) :: r,p,t155156REAL(KIND=dp), DIMENSION(3,3,3) :: symbols157158Symbols = 0.0d0159Symbols(2,2,1) = -r * COS(t)**2160IF ( r /= 0.0d0 ) THEN161Symbols(1,2,2) = 1.0d0 / r162Symbols(2,1,2) = 1.0d0 / r163END IF164165IF ( CoordinateSystemDimension() == 3 ) THEN166Symbols(3,3,1) = -r167Symbols(2,2,3) = SIN(t)*COS(t)168169Symbols(2,3,2) = -TAN(t)170Symbols(3,2,2) = -TAN(t)171172IF ( r /= 0.0d0 ) THEN173Symbols(3,1,3) = 1.0d0 / r174Symbols(1,3,3) = 1.0d0 / r175END IF176END IF177END FUNCTION PolarSymbols178!----------------------------------------------------------------------------179180181!----------------------------------------------------------------------------182FUNCTION PolarDerivSymbols( r,p,t ) RESULT(dsymbols)183REAL(KIND=dp) :: r,p,t184185REAL(KIND=dp), DIMENSION(3,3,3,3) :: dSymbols186187dSymbols = 0.0d0188dSymbols(2,2,1,1) = -COS(t)**2189IF ( r /= 0.0d0 ) THEN190dSymbols(1,2,2,1) = -1.0d0 / r**2191dSymbols(2,1,2,1) = -1.0d0 / r**2192END IF193194IF ( CoordinateSystemDimension() == 3 ) THEN195dSymbols(2,2,1,3) = -2*r*SIN(t)*COS(t)196dSymbols(3,3,1,1) = -1197dSymbols(2,2,3,3) = COS(t)**2 - SIN(t)**2198199dSymbols(2,3,2,3) = -1.0d0 / COS(t)**2200dSymbols(3,2,2,3) = -1.0d0 / COS(t)**2201202IF ( r /= 0.0d0 ) THEN203dSymbols(1,3,3,1) = -1.0d0 / r**2204dSymbols(3,1,3,1) = -1.0d0 / r**2205END IF206END IF207END FUNCTION PolarDerivSymbols208!----------------------------------------------------------------------------209210211212!----------------------------------------------------------------------------213FUNCTION CoordinateSqrtMetric( X,Y,Z ) RESULT( SqrtMetric )214REAL(KIND=dp) :: X,Y,Z,SqrtMetric215216IF ( Coordinates == Cartesian ) THEN217SqrtMetric = 1.0d0218ELSE IF ( Coordinates >= Cylindric .AND. &219Coordinates <= AxisSymmetric ) THEN220SqrtMetric = CylindricalSqrtMetric( X,Y,Z )221ELSE IF ( Coordinates == Polar ) THEN222SqrtMetric = PolarSqrtMetric( X,Y,Z )223END IF224225END FUNCTION CoordinateSqrtMetric226!----------------------------------------------------------------------------227228229!----------------------------------------------------------------------------230FUNCTION CurrentCoordinateSystem() RESULT(Coords)231INTEGER :: Coords232233Coords = Coordinates234END FUNCTION CurrentCoordinateSystem235!----------------------------------------------------------------------------236237238!----------------------------------------------------------------------------239SUBROUTINE CoordinateSystemInfo( Metric,SqrtMetric, &240Symbols,dSymbols,X,Y,Z )241242REAL(KIND=dp) :: Metric(3,3),SqrtMetric, &243Symbols(3,3,3),dSymbols(3,3,3,3)244245INTEGER :: i246REAL(KIND=dp) :: X,Y,Z247248IF ( Coordinates == Cartesian ) THEN249250Metric = 0.0d0251DO i=1,3252Metric(i,i) = 1.0d0253END DO254255SqrtMetric = 1.0d0256Symbols = 0.0d0257dSymbols = 0.0d0258259ELSE IF ( Coordinates >= Cylindric .AND. &260Coordinates <= AxisSymmetric ) THEN261262SqrtMetric = CylindricalSqrtMetric( X,Y,Z )263Metric = CylindricalMetric( X,Y,Z )264Symbols = CylindricalSymbols( X,Y,Z )265dSymbols = CylindricalDerivSymbols( X,Y,Z )266267ELSE IF ( Coordinates == Polar ) THEN268269SqrtMetric = PolarSqrtMetric( X,Y,Z )270Metric = PolarMetric( X,Y,Z )271Symbols = PolarSymbols( X,Y,Z )272dSymbols = PolarDerivSymbols( X,Y,Z )273274END IF275276END SUBROUTINE CoordinateSystemInfo277!----------------------------------------------------------------------------278279280!----------------------------------------------------------------------------281FUNCTION CoordinateSystemDimension() RESULT( dim )282INTEGER :: dim ! ,csys283284! csys = CurrentCoordinateSystem()285dim = CurrentModel % Dimension286END FUNCTION CoordinateSystemDimension287!----------------------------------------------------------------------------288289!----------------------------------------------------------------------------290END MODULE CoordinateSystems291!----------------------------------------------------------------------------292293!> \} ElmerLib294295296