source: palm/tags/release-3.8/SOURCE/init_pt_anomaly.f90 @ 716

Last change on this file since 716 was 668, checked in by suehring, 13 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 1.8 KB
Line 
1 SUBROUTINE init_pt_anomaly
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7! Former revisions:
8! -----------------
9! $Id: init_pt_anomaly.f90 668 2010-12-23 13:22:58Z raasch $
10!
11! 667 2010-12-23 12:06:00Z suehring/gryschka
12! Call of exchange_horiz are modified.
13!
14! 75 2007-03-22 09:54:05Z raasch
15! 2nd+3rd argument removed from exchange horiz
16!
17! 19 2007-02-23 04:53:48Z raasch
18! Calculation extended for gridpoint nzt
19!
20! RCS Log replace by Id keyword, revision history cleaned up
21!
22! Revision 1.7  2005/03/26 20:36:55  raasch
23! Arguments for non-cyclic boundary conditions added to argument list of
24! routine exchange_horiz
25!
26! Revision 1.1  1997/08/29 08:58:56  raasch
27! Initial revision
28!
29!
30! Description:
31! ------------
32! Impose a temperature perturbation for an advection test.
33!------------------------------------------------------------------------------!
34
35    USE arrays_3d
36    USE constants
37    USE grid_variables
38    USE indices
39    USE control_parameters
40
41    IMPLICIT NONE
42
43    INTEGER ::  i, ic, j, jc, k, kc
44    REAL    ::  betrag, radius, rc, x, y, z
45
46!
47!-- Defaults: radius rc, strength z,
48!--           position of centre: ic, jc, kc
49    rc =  10.0 * dx
50    ic =  ( nx+1 ) / 2
51    jc =  ic
52    kc = nzt / 2
53
54!
55!-- Compute the perturbation.
56    DO  i = nxl, nxr
57       DO  j = nys, nyn
58          DO  k = nzb+1, nzt
59             x = ( i - ic ) * dx
60             y = ( j - jc ) * dy
61             z = ABS( zu(k) - zu(kc) )
62             radius = SQRT( x**2 + y**2 + z**2 )
63             IF ( radius <= rc )  THEN
64                betrag = 5.0 * EXP( -( radius / 2.0 )**2 )
65             ELSE
66                betrag = 0.0
67             ENDIF
68
69             pt(k,j,i) = pt(k,j,i) + betrag
70
71          ENDDO
72       ENDDO
73    ENDDO
74
75!
76!-- Exchange of boundary values for temperature
77    CALL exchange_horiz( pt, nbgp )
78
79
80 END SUBROUTINE init_pt_anomaly
Note: See TracBrowser for help on using the repository browser.