Ignore:
Timestamp:
Oct 29, 2013 1:21:31 PM (10 years ago)
Author:
heinze
Message:

Undoing commit 1239

File:
1 edited

Legend:

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

    r1239 r1240  
    2020! Currrent revisions:
    2121! ------------------
    22 ! Generalize calc_mean_profile for wider use: use additional steering
    23 ! character loc
    2422!
    2523!
     
    346344
    347345
    348     SUBROUTINE calc_mean_profile( var, pr, loc )
     346    SUBROUTINE calc_mean_profile( var, pr )
    349347
    350348!------------------------------------------------------------------------------!
     
    365363
    366364       INTEGER ::  i, j, k, omp_get_thread_num, pr, tn
    367        CHARACTER (LEN=*) ::  loc
    368365#if defined( __nopointer )
    369366       REAL, DIMENSION(:,:,:) ::  var
     
    417414       ENDIF
    418415
    419        SELECT CASE ( loc )
    420 
    421           CASE ( 'time_int' )
    422 
    423              ref_state(:)  = hom(:,1,pr,0)   ! this is used in the buoyancy term
    424 
    425 
    426           CASE ( 'nudging' )
    427              !nothing to be done
    428 
    429 
    430           CASE DEFAULT
    431              message_string = 'unknown location "' // loc // '"'
    432              CALL message( 'calc_mean_profile', 'PA0379', 1, 2, 0, 6, 0 )
    433 
    434        END SELECT
    435 
    436 
     416       ref_state(:)  = hom(:,1,pr,0)   ! this is used in the buoyancy term
    437417
    438418    END SUBROUTINE calc_mean_profile
Note: See TracChangeset for help on using the changeset viewer.