Ignore:
Timestamp:
Mar 13, 2007 3:52:49 AM (17 years ago)
Author:
raasch
Message:

preliminary changes concerning update of BC-scheme

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/prognostic_equations.f90

    r57 r63  
    44! Actual revisions:
    55! -----------------
    6 ! z0 removed from arguments in calls of diffusion_u/v/w
     6! z0 removed from arguments in calls of diffusion_u/v/w,
     7! subroutine names changed to .._noopt, .._cache, and .._vector
    78!
    89! Former revisions:
     
    6364
    6465    PRIVATE
    65     PUBLIC prognostic_equations, prognostic_equations_fast, &
    66            prognostic_equations_vec
    67 
    68     INTERFACE prognostic_equations
    69        MODULE PROCEDURE prognostic_equations
    70     END INTERFACE prognostic_equations
    71 
    72     INTERFACE prognostic_equations_fast
    73        MODULE PROCEDURE prognostic_equations_fast
    74     END INTERFACE prognostic_equations_fast
    75 
    76     INTERFACE prognostic_equations_vec
    77        MODULE PROCEDURE prognostic_equations_vec
    78     END INTERFACE prognostic_equations_vec
     66    PUBLIC prognostic_equations_noopt, prognostic_equations_cache, &
     67           prognostic_equations_vector
     68
     69    INTERFACE prognostic_equations_noopt
     70       MODULE PROCEDURE prognostic_equations_noopt
     71    END INTERFACE prognostic_equations_noopt
     72
     73    INTERFACE prognostic_equations_cache
     74       MODULE PROCEDURE prognostic_equations_cache
     75    END INTERFACE prognostic_equations_cache
     76
     77    INTERFACE prognostic_equations_vector
     78       MODULE PROCEDURE prognostic_equations_vector
     79    END INTERFACE prognostic_equations_vector
    7980
    8081
     
    8283
    8384
    84  SUBROUTINE prognostic_equations
     85 SUBROUTINE prognostic_equations_noopt
    8586
    8687!------------------------------------------------------------------------------!
     
    615616
    616617
    617  END SUBROUTINE prognostic_equations
    618 
    619 
    620  SUBROUTINE prognostic_equations_fast
     618 END SUBROUTINE prognostic_equations_noopt
     619
     620
     621 SUBROUTINE prognostic_equations_cache
    621622
    622623!------------------------------------------------------------------------------!
     
    996997
    997998
    998  END SUBROUTINE prognostic_equations_fast
    999 
    1000 
    1001  SUBROUTINE prognostic_equations_vec
     999 END SUBROUTINE prognostic_equations_cache
     1000
     1001
     1002 SUBROUTINE prognostic_equations_vector
    10021003
    10031004!------------------------------------------------------------------------------!
     
    12421243!
    12431244!-- pt-tendency terms with communication
     1245    sat = tsc(1)
     1246    sbt = tsc(2)
    12441247    IF ( scalar_advec == 'bc-scheme' )  THEN
    1245 !
    1246 !--    Bott-Chlond scheme always uses Euler time step. Thus:
    1247        sat = 1.0
    1248        sbt = 1.0
     1248
     1249       IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     1250!
     1251!--       Bott-Chlond scheme always uses Euler time step when leapfrog is
     1252!--       switched on. Thus:
     1253          sat = 1.0
     1254          sbt = 1.0
     1255       ENDIF
    12491256       tend = 0.0
    12501257       CALL advec_s_bc( pt, 'pt' )
    12511258    ELSE
    1252        sat = tsc(1)
    1253        sbt = tsc(2)
    12541259       IF ( tsc(2) /= 2.0  .AND.  scalar_advec == 'ups-scheme' )  THEN
    12551260          tend = 0.0
     
    13401345!
    13411346!--    Scalar/q-tendency terms with communication
     1347       sat = tsc(1)
     1348       sbt = tsc(2)
    13421349       IF ( scalar_advec == 'bc-scheme' )  THEN
    1343 !
    1344 !--       Bott-Chlond scheme always uses Euler time step. Thus:
    1345           sat = 1.0
    1346           sbt = 1.0
     1350
     1351          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     1352!
     1353!--          Bott-Chlond scheme always uses Euler time step when leapfrog is
     1354!--          switched on. Thus:
     1355             sat = 1.0
     1356             sbt = 1.0
     1357          ENDIF
    13471358          tend = 0.0
    13481359          CALL advec_s_bc( q, 'q' )
    13491360       ELSE
    1350           sat = tsc(1)
    1351           sbt = tsc(2)
    13521361          IF ( tsc(2) /= 2.0 )  THEN
    13531362             IF ( scalar_advec == 'ups-scheme' )  THEN
     
    14381447!--    TKE-tendency terms with communication
    14391448       CALL production_e_init
     1449
     1450       sat = tsc(1)
     1451       sbt = tsc(2)
    14401452       IF ( .NOT. use_upstream_for_tke )  THEN
    14411453          IF ( scalar_advec == 'bc-scheme' )  THEN
    1442 !
    1443 !--          Bott-Chlond scheme always uses Euler time step. Thus:
    1444              sat = 1.0
    1445              sbt = 1.0
     1454
     1455             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     1456!
     1457!--             Bott-Chlond scheme always uses Euler time step when leapfrog is
     1458!--             switched on. Thus:
     1459                sat = 1.0
     1460                sbt = 1.0
     1461             ENDIF
    14461462             tend = 0.0
    14471463             CALL advec_s_bc( e, 'e' )
    14481464          ELSE
    1449              sat = tsc(1)
    1450              sbt = tsc(2)
    14511465             IF ( tsc(2) /= 2.0 )  THEN
    14521466                IF ( scalar_advec == 'ups-scheme' )  THEN
     
    15501564
    15511565
    1552  END SUBROUTINE prognostic_equations_vec
     1566 END SUBROUTINE prognostic_equations_vector
    15531567
    15541568
Note: See TracChangeset for help on using the changeset viewer.