Ignore:
Timestamp:
Apr 13, 2018 11:22:08 AM (6 years ago)
Author:
raasch
Message:

bugfix: missing parallel cpp-directives added

File:
1 edited

Legend:

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

    r2951 r2967  
    2525! -----------------
    2626! $Id$
     27! bugfix: missing parallel cpp-directives added
     28!
     29! 2951 2018-04-06 09:05:08Z kanani
    2730! Add log_point_s for pmci_model_configuration
    2831!
     
    745748    INTEGER(iwp) ::  ncpl   !<  number of nest domains
    746749
     750#if defined( __parallel )
    747751    CALL location_message( 'setup the nested model configuration', .FALSE. )
    748752    CALL cpu_log( log_point_s(79), 'pmci_model_config', 'start' )
     
    769773    CALL cpu_log( log_point_s(79), 'pmci_model_config', 'stop' )
    770774    CALL location_message( 'finished', .TRUE. )
     775#endif
    771776
    772777 END SUBROUTINE pmci_modelconfiguration
     
    33303335END SUBROUTINE pmci_set_array_pointer
    33313336
     3337
    33323338INTEGER FUNCTION get_number_of_childs ()
     3339
    33333340   IMPLICIT NONE
    33343341
     3342#if defined( __parallel )
    33353343   get_number_of_childs = SIZE( pmc_parent_for_child ) - 1
     3344#else
     3345   get_number_of_childs = 0
     3346#endif
    33363347
    33373348   RETURN
     3349
    33383350END FUNCTION get_number_of_childs
    33393351
     3352
    33403353INTEGER FUNCTION get_childid (id_index)
     3354
    33413355   IMPLICIT NONE
    33423356
    33433357   INTEGER,INTENT(IN)                 :: id_index
    33443358
     3359#if defined( __parallel )
    33453360   get_childid = pmc_parent_for_child(id_index)
     3361#else
     3362   get_childid = 0
     3363#endif
    33463364
    33473365   RETURN
     3366
    33483367END FUNCTION get_childid
     3368
    33493369
    33503370SUBROUTINE  get_child_edges (m, lx_coord, lx_coord_b, rx_coord, rx_coord_b,    &
Note: See TracChangeset for help on using the changeset viewer.