prismdrv_set_scc_info.F90

Go to the documentation of this file.
00001 !------------------------------------------------------------------------
00002 ! Copyright 2006-2010, CERFACS, Toulouse, France.
00003 ! All rights reserved. Use is subject to OASIS4 license terms.
00004 !-----------------------------------------------------------------------
00005 !BOP
00006 !
00007 ! !ROUTINE: PRISMDrv_Set_scc_info
00008 !
00009 ! !INTERFACE
00010 subroutine prismdrv_set_scc_info(id_err)
00011 
00012 !
00013 ! !USES:
00014 !
00015   USE PSMILe_scc
00016   USE PRISMDrv, dummy_interface => PRISMDrv_Set_scc_info
00017 
00018   IMPLICIT NONE
00019 
00020 !
00021 ! !PARAMETERS:
00022 !
00023 
00024 !
00025 ! ! RETURN VALUE
00026 !
00027   INTEGER, INTENT (Out)               :: id_err   ! error value
00028 
00029 ! !DESCRIPTION
00030 ! Subroutine "PRISMDrv_set_scc_info" sets the information got through the
00031 ! extraction of information in the SCC file.
00032 ! Th master process collects the xml infos and broadcast the ones needed to 
00033 ! the other processes.
00034 !
00035 ! !REVISED HISTORY
00036 !   Date      Programmer   Description
00037 ! ----------  ----------   -----------
00038 ! 03/10/2002  D. Declat    Creation
00039 !
00040 ! EOP
00041 !----------------------------------------------------------------------
00042 ! $Id: prismdrv_set_scc_info.F90 2399 2010-06-21 08:09:39Z coquart $
00043 ! $Author: coquart $
00044 !----------------------------------------------------------------------
00045 !
00046 ! 0. Local declarations
00047 !
00048   CHARACTER(LEN=len_cvs_string), SAVE  :: mycvs = 
00049      '$Id: prismdrv_set_scc_info.F90 2399 2010-06-21 08:09:39Z coquart $'
00050 
00051 !
00052 ! Name of the different hosts for one application
00053   CHARACTER(LEN=max_name), DIMENSION(:), ALLOCATABLE :: cla_appli_hostname
00054 
00055 ! Name of the different components for one application
00056   CHARACTER(LEN=max_name), DIMENSION(:), ALLOCATABLE :: cla_appli_compname
00057 
00058 ! Arguments for one application
00059   CHARACTER(LEN=max_name), DIMENSION(:), ALLOCATABLE :: cla_appli_args
00060 
00061 ! Number of processes for each hosts of one application
00062   INTEGER, DIMENSION(:), ALLOCATABLE :: ila_appli_hostnbprocs 
00063 
00064 ! Number of rank sets (min-max-inc) for all components for one application
00065   INTEGER, DIMENSION(:), ALLOCATABLE :: ila_appli_compnbranksets
00066 !
00067 ! Array of rank sets (min-max-inc) for all components for one application
00068   INTEGER, DIMENSION(:,:), ALLOCATABLE :: ila_appli_compranks
00069 
00070 !
00071   INTEGER :: i, ii
00072   INTEGER :: il_MPI
00073   INTEGER :: n_arg, n_host, n_comp, n_ranksets
00074   INTEGER :: il_status(MPI_STATUS_SIZE)
00075   INTEGER :: ila_scc_info(5)
00076 !
00077   INTEGER, PARAMETER         :: nerrp=2
00078   INTEGER                    :: ierrp(nerrp)
00079 !
00080 !----------------------------------------------------------------------
00081 !----------------------------------------------------------------------
00082 !
00083 !
00084 #ifdef VERBOSE
00085   PRINT *, '| Enter PRISMDrv_set_scc_info'
00086   call psmile_flushstd
00087 #endif
00088 ! The reading of the scc xml info are done by the master process only
00089 !> WARNING This is a workaround. The real Appl%rank (rank within the local communicator is determined in prismdrv_init_appl),
00090 !>         which is called later. This Appl%rank is the global rank. (for MPI1)
00091   IF (Appl%rank == PRISMdrv_root) THEN
00092 !
00093 ! 1. Extract information from SCC
00094 !
00095 !===> open the scc.xml file and load its elements into memory
00096 !
00097       call open_scc_file (id_err)
00098       IF ( id_err > 0 ) THEN
00099           call PSMILe_Abort
00100       ENDIF
00101 !
00102 ! 1.1. get the way used to launch the coupled system (MPI1 or MPI2)
00103 !
00104       call get_execution_mode(ig_MPI, id_err)
00105 #ifdef VERBOSE
00106       PRINT *, '| | MPI version : ',ig_MPI
00107       call psmile_flushstd
00108 #endif
00109 ! 
00110 ! 1.1. get the number of pes for the driver/transformer
00111       call get_transformer_pes (ig_driver_nb_pes, id_err)
00112 #ifdef VERBOSE
00113       PRINT *, '| | Number of pes for the driver/transformer : ', &
00114      ig_driver_nb_pes
00115       call psmile_flushstd
00116 #endif
00117 !  
00118 ! 1.2. Check if the SCC information about the MPI implementation 
00119 !      corresponds to the pre-compilation option 
00120 !
00121 #ifdef PRISM_with_MPI1
00122 #ifdef VERBOSE
00123       PRINT *, '| | option MPI1 pour la pre-compil'
00124       call psmile_flushstd
00125 #endif
00126       il_MPI = DRV_MPI1
00127 #else
00128 #ifdef VERBOSE
00129       PRINT *, '| | option MPI2 pour la pre-compil'
00130       call psmile_flushstd
00131 #endif
00132       il_MPI = DRV_MPI2
00133 #endif
00134 
00135 !
00136 ! 2. Get the experiment and run dates
00137 !
00138       call get_dates ( sga_experiment_start_date, &
00139      sga_experiment_end_date,   &
00140      sga_run_start_date,        &
00141      sga_run_end_date,          &
00142      id_err)
00143 
00144 !  
00145 ! 3. Read the information about the different applications
00146 !
00147 ! 3.1. get the number of applications
00148 
00149       CALL get_appli_number (ig_nb_appl, id_err)
00150 #ifdef VERBOSE
00151       PRINT *, '| | Number of applications ',ig_nb_appl
00152       call psmile_flushstd
00153 #endif
00154 ! The reading of the scc xml info are done by the master process only
00155 !  IF (Appl%rank == PRISMdrv_root) THEN
00156 !
00157 ! 3.2. allocate space for the information arrays for the applications
00158 !
00159       ALLOCATE ( cga_appli_name(0:ig_nb_appl), STAT = id_err )
00160       IF ( id_err > 0 ) THEN
00161       ierrp (1) = id_err
00162       ierrp (2) = ig_nb_appl
00163       call psmile_error_common ( PRISM_Error_Alloc, 'cga_appli_name', &
00164          ierrp, 2, __FILE__, __LINE__ )
00165       ENDIF
00166       ALLOCATE ( cga_appli_exe_name(0:ig_nb_appl), STAT = id_err )
00167       IF ( id_err > 0 ) THEN
00168       ierrp (1) = id_err
00169       ierrp (2) = ig_nb_appl
00170       call psmile_error_common ( PRISM_Error_Alloc, 'cga_appli_exe_name', &
00171          ierrp, 2, __FILE__, __LINE__ )
00172       ENDIF
00173       ALLOCATE ( iga_appli_nb_pes(0:ig_nb_appl), STAT = id_err )
00174       IF ( id_err > 0 ) THEN
00175       ierrp (1) = id_err
00176       ierrp (2) = ig_nb_appl
00177       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_nb_pes', &
00178          ierrp, 2, __FILE__, __LINE__ )
00179       ENDIF
00180       ALLOCATE ( iga_appli_nb_hosts(0:ig_nb_appl), STAT = id_err )
00181       IF ( id_err > 0 ) THEN
00182       ierrp (1) = id_err
00183       ierrp (2) = ig_nb_appl
00184       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_nb_hosts', &
00185          ierrp, 2, __FILE__, __LINE__ )
00186       ENDIF
00187       ALLOCATE ( iga_appli_nb_comps(0:ig_nb_appl), STAT = id_err )
00188       IF ( id_err > 0 ) THEN
00189       ierrp (1) = id_err
00190       ierrp (2) = ig_nb_appl
00191       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_nb_comps', &
00192          ierrp, 2, __FILE__, __LINE__ )
00193       ENDIF
00194       ALLOCATE ( iga_appli_nb_args(0:ig_nb_appl), STAT = id_err )
00195       IF ( id_err > 0 ) THEN
00196       ierrp (1) = id_err
00197       ierrp (2) = ig_nb_appl
00198       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_nb_args', &
00199          ierrp, 2, __FILE__, __LINE__ )
00200       ENDIF
00201       ALLOCATE ( iga_appli_redirect(0:ig_nb_appl), STAT = id_err )
00202       IF ( id_err > 0 ) THEN
00203       ierrp (1) = id_err
00204       ierrp (2) = ig_nb_appl
00205       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_redirect', &
00206          ierrp, 2, __FILE__, __LINE__ )
00207       ENDIF
00208       ALLOCATE ( iga_appli_nbtot_ranksets(1:ig_nb_appl), STAT = id_err )
00209       IF ( id_err > 0 ) THEN
00210       ierrp (1) = id_err
00211       ierrp (2) = ig_nb_appl
00212       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_nbtot_ranksets', &
00213          ierrp, 2, __FILE__, __LINE__ )
00214       ENDIF
00215       ALLOCATE ( comm_coupling(0:ig_nb_appl), STAT = id_err )
00216       IF ( id_err > 0 ) THEN
00217       ierrp (1) = id_err
00218       ierrp (2) = ig_nb_appl
00219       call psmile_error_common ( PRISM_Error_Alloc, 'comm_coupling', &
00220          ierrp, 2, __FILE__, __LINE__ )
00221       ENDIF
00222 
00223 !
00224 ! 3.3. Get the name, exe_name, nb of hosts, nb of comps
00225 !      and nb of arguments for each appli
00226 !
00227       CALL get_appli_details ( ig_nb_appl,                &
00228      cga_appli_name,            &
00229      cga_appli_exe_name,        &
00230      iga_appli_nb_hosts,        &
00231      iga_appli_redirect,        &
00232      iga_appli_nb_comps,        &
00233      iga_appli_nb_args,         &
00234      id_err )
00235 
00236 !
00237 ! 3.4. Compute the total number of hosts and components
00238 !
00239       DO i = 1, ig_nb_appl
00240 
00241     ig_nb_tot_hosts =  ig_nb_tot_hosts + iga_appli_nb_hosts(i) 
00242     ig_nb_tot_comps =  ig_nb_tot_comps + iga_appli_nb_comps(i)
00243     ig_nb_tot_args  =  ig_nb_tot_args  + iga_appli_nb_args(i)
00244 
00245       END DO
00246 
00247 ! 3.5. Allocate and fill the global arrays
00248 !
00249 ! 3.5.1. Allocate the argument, host-names, host-number-of-procs 
00250 !        and component-number-of-rank-sets arrays
00251       IF (ig_nb_tot_args == 0 ) THEN
00252          ALLOCATE ( cga_appli_args(0:0), STAT = id_err )
00253          cga_appli_args(0:0)=""
00254       ELSE
00255          ALLOCATE ( cga_appli_args(ig_nb_tot_args), STAT = id_err )
00256       ENDIF
00257       IF ( id_err > 0 ) THEN
00258       ierrp (1) = id_err
00259       ierrp (2) = ig_nb_tot_args
00260       call psmile_error_common ( PRISM_Error_Alloc, 'Nb tot args', &
00261          ierrp, 2, __FILE__, __LINE__ )
00262       ENDIF
00263 
00264       ALLOCATE ( cga_appli_hostname(ig_nb_tot_hosts), STAT = id_err )
00265       IF ( id_err > 0 ) THEN
00266       ierrp (1) = id_err
00267       ierrp (2) = ig_nb_tot_hosts
00268       call psmile_error_common ( PRISM_Error_Alloc, 'cga_appli_hostname', &
00269          ierrp, 2, __FILE__, __LINE__ )
00270       ENDIF
00271       ALLOCATE ( iga_appli_hostnbprocs(ig_nb_tot_hosts), STAT = id_err )
00272       IF ( id_err > 0 ) THEN
00273       ierrp (1) = id_err
00274       ierrp (2) = ig_nb_tot_hosts
00275       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_hostnbprocs', &
00276          ierrp, 2, __FILE__, __LINE__ )
00277       ENDIF
00278       ALLOCATE ( cga_appli_compname(ig_nb_tot_comps), STAT = id_err )
00279       IF ( id_err > 0 ) THEN
00280       ierrp (1) = id_err
00281       ierrp (2) = ig_nb_tot_comps
00282       call psmile_error_common ( PRISM_Error_Alloc, 'cga_appli_compname', &
00283          ierrp, 2, __FILE__, __LINE__ )
00284       ENDIF
00285       ALLOCATE ( iga_appli_compnbranksets(ig_nb_tot_comps), STAT = id_err )
00286       IF ( id_err > 0 ) THEN
00287       ierrp (1) = id_err
00288       ierrp (2) = ig_nb_tot_comps
00289       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_compnbranksets', &
00290          ierrp, 2, __FILE__, __LINE__ )
00291       ENDIF
00292 
00293 ! 3.5.2. For all the applications
00294       n_arg = 0
00295       n_host = 0
00296       n_comp = 0
00297 
00298       ig_nb_tot_pes = 0
00299       iga_appli_nb_pes(0) = ig_driver_nb_pes ! number of pes for the driver
00300 
00301       DO i = 1, ig_nb_appl
00302 
00303 ! 3.5.2.1 Allocate and get for each application
00304 !         the arguments
00305 !         the names and number of procs for all hosts
00306 !         the number of rank sets for all components
00307 
00308     IF (iga_appli_nb_args(i) .gt. 0) THEN
00309         ALLOCATE ( cla_appli_args(iga_appli_nb_args(i)), STAT = id_err )
00310         IF ( id_err > 0 ) THEN
00311         ierrp (1) = id_err
00312         ierrp (2) = iga_appli_nb_args(i)
00313         call psmile_error_common ( PRISM_Error_Alloc,'Nb appli args',&
00314            ierrp, 2, __FILE__, __LINE__ )
00315         ENDIF
00316     END IF
00317 
00318     IF (iga_appli_nb_hosts(i) .gt. 0) THEN
00319         ALLOCATE ( cla_appli_hostname(iga_appli_nb_hosts(i)),STAT =id_err)
00320         IF ( id_err > 0 ) THEN
00321         ierrp (1) = id_err
00322         ierrp (2) = iga_appli_nb_hosts(i)
00323         call psmile_error_common ( PRISM_Error_Alloc,'cla_appli_hostname',&
00324            ierrp, 2, __FILE__, __LINE__ )
00325         ENDIF
00326         ALLOCATE (ila_appli_hostnbprocs(iga_appli_nb_hosts(i)),STAT =id_err)
00327         IF ( id_err > 0 ) THEN
00328         ierrp (1) = id_err
00329         ierrp (2) = iga_appli_nb_hosts(i)
00330         call psmile_error_common (PRISM_Error_Alloc,'ila_appli_hostnbprocs',&
00331            ierrp, 2, __FILE__, __LINE__ )
00332         ENDIF
00333     END IF
00334 
00335     IF (iga_appli_nb_comps(i) .gt. 0) THEN
00336         ALLOCATE (cla_appli_compname(iga_appli_nb_comps(i)),STAT = id_err)
00337         IF ( id_err > 0 ) THEN
00338         ierrp (1) = id_err
00339         ierrp (2) = iga_appli_nb_comps(i)
00340         call psmile_error_common (PRISM_Error_Alloc,'cla_appli_compname',&
00341            ierrp, 2, __FILE__, __LINE__ )
00342         ENDIF
00343         ALLOCATE (ila_appli_compnbranksets(iga_appli_nb_comps(i)), &
00344            STAT = id_err )
00345         IF ( id_err > 0 ) THEN
00346         ierrp (1) = id_err
00347         ierrp (2) = iga_appli_nb_comps(i)
00348         call psmile_error_common (PRISM_Error_Alloc,'ila_appli_compnbranksets',&
00349            ierrp, 2, __FILE__, __LINE__ )
00350         ENDIF
00351     END IF
00352 
00353 ! 3.5.2.2. Get the information for arguments, hosts and components
00354 
00355     IF (iga_appli_nb_args(i) .gt. 0) THEN
00356         CALL get_appliarg_details ( i,                    &
00357            iga_appli_nb_args(i), &
00358            cla_appli_args,       &
00359            id_err )
00360     END IF
00361 
00362     IF (iga_appli_nb_hosts(i) .gt. 0) THEN
00363         CALL get_applihost_details ( i,                     &
00364            iga_appli_nb_hosts(i), &
00365            cla_appli_hostname,    &
00366            ila_appli_hostnbprocs, &
00367            id_err )
00368 
00369         iga_appli_nb_pes(i) = SUM(ila_appli_hostnbprocs(:))
00370 
00371         ig_nb_tot_pes = ig_nb_tot_pes + iga_appli_nb_pes(i)
00372     END IF
00373 
00374     IF (iga_appli_nb_comps(i) .gt. 0) THEN
00375         CALL get_applicomp_details ( i,                        &
00376            iga_appli_nb_comps(i),    &
00377            cla_appli_compname,       & 
00378            ila_appli_compnbranksets, &
00379            id_err )
00380 
00381         iga_appli_nbtot_ranksets(i) = SUM(ila_appli_compnbranksets(:))
00382     END IF
00383 
00384 ! 3.5.2.3. Store it in the global arrays
00385 
00386     IF (iga_appli_nb_args(i) .gt. 0) THEN
00387         cga_appli_args(n_arg+1:n_arg+iga_appli_nb_args(i)) =     &
00388            cla_appli_args(:) 
00389     END IF
00390 
00391     IF (iga_appli_nb_hosts(i) .gt. 0) THEN
00392         iga_appli_hostnbprocs(n_host+1:n_host+iga_appli_nb_hosts(i)) =  &
00393            ila_appli_hostnbprocs(:)     
00394         cga_appli_hostname(n_host+1:n_host+iga_appli_nb_hosts(i)) =     &
00395            cla_appli_hostname(:)     
00396     END IF
00397 
00398     IF (iga_appli_nb_comps(i) .gt. 0) THEN
00399         cga_appli_compname(n_comp+1:n_comp+iga_appli_nb_comps(i)) =  &
00400            cla_appli_compname(:)     
00401         iga_appli_compnbranksets(n_comp+1:n_comp+iga_appli_nb_comps(i)) = &
00402            ila_appli_compnbranksets(:)      
00403     END IF
00404 
00405 ! 3.5.2.4. Increase the index in the global arrays
00406 
00407     n_arg = n_arg + iga_appli_nb_args(i)
00408     n_host = n_host + iga_appli_nb_hosts(i)
00409     n_comp = n_comp + iga_appli_nb_comps(i)
00410 
00411 
00412 ! 3.5.2.5. Deallocate the local arrays
00413 
00414     IF (iga_appli_nb_args(i) .gt. 0) THEN
00415         DEALLOCATE ( cla_appli_args, STAT = id_err ) 
00416         IF (id_err > 0) THEN
00417         ierrp (1) = id_err
00418 
00419         call psmile_error_common ( PRISM_Error_Dealloc, 'Appli args', &
00420            ierrp, 1, __FILE__, __LINE__ )
00421         ENDIF
00422     END IF
00423 
00424     IF (iga_appli_nb_hosts(i) .gt. 0) THEN
00425         DEALLOCATE ( cla_appli_hostname, STAT = id_err ) 
00426         DEALLOCATE ( ila_appli_hostnbprocs, STAT = id_err ) 
00427         IF (id_err > 0) THEN
00428         ierrp (1) = id_err
00429 
00430         call psmile_error_common ( PRISM_Error_Dealloc, 'Appli hosts', &
00431            ierrp, 1, __FILE__, __LINE__ )
00432         ENDIF
00433     END IF
00434 
00435     IF (iga_appli_nb_comps(i) .gt. 0) THEN
00436         DEALLOCATE ( cla_appli_compname, STAT = id_err )
00437         DEALLOCATE ( ila_appli_compnbranksets, STAT = id_err )
00438         IF (id_err > 0) THEN
00439         ierrp (1) = id_err
00440 
00441         call psmile_error_common ( PRISM_Error_Dealloc, 'Appli comps', &
00442            ierrp, 1, __FILE__, __LINE__ )
00443         ENDIF
00444     END IF
00445 
00446       END DO
00447 
00448 #ifdef VERBOSE
00449       PRINT *, '| | Total number of processes: ', ig_nb_tot_pes
00450 #endif
00451       ig_nbtot_ranksets= SUM(iga_appli_nbtot_ranksets(:))
00452 
00453 !
00454 ! 3.6. Allocate and fill the rank sets (min-max-inc) arrays
00455 !
00456 ! 3.6.1. Allocate the rank sets (min-max-inc) arrays
00457 
00458       ALLOCATE ( iga_appli_compranks(ig_nbtot_ranksets,3), STAT = id_err )
00459       IF ( id_err > 0 ) THEN
00460       ierrp (1) = id_err
00461       ierrp (2) = ig_nbtot_ranksets
00462       call psmile_error_common ( PRISM_Error_Alloc, 'Nb tot ranksets', &
00463          ierrp, 2, __FILE__, __LINE__ )
00464       ENDIF
00465 
00466 ! 3.6.2. For all the applications
00467 
00468       n_ranksets = 0
00469 
00470       DO i = 1, ig_nb_appl
00471 
00472 ! 3.6.2.2. Allocate and get the rank sets (min-max-inc) 
00473 !          for all components of one application
00474     IF (iga_appli_nbtot_ranksets(i) .gt. 0) THEN
00475         ALLOCATE ( ila_appli_compranks (iga_appli_nbtot_ranksets(i),3), &
00476            STAT = id_err)
00477         IF ( id_err > 0 ) THEN
00478         ierrp (1) = id_err
00479         ierrp (2) = iga_appli_nbtot_ranksets(i)
00480         call psmile_error_common ( PRISM_Error_Alloc,'Appli nb tot ranksets',&
00481            ierrp, 2, __FILE__, __LINE__ )
00482         ENDIF
00483 
00484         CALL get_applicomprk_detls ( i,  &
00485            iga_appli_nbtot_ranksets(i),  &
00486            ila_appli_compranks,          &
00487            id_err )
00488 
00489             do ii = 1, iga_appli_nbtot_ranksets(i)
00490                
00491                if ( ila_appli_compranks(ii,1) == PSMILE_undef ) then
00492                   id_err = PRISM_Error_Parameter
00493                   ierrp(1) = PSMILe_undef
00494                   ierrp(2) = 0
00495                   call psmile_error_common ( PRISM_Error_Parameter, 'min_value', &
00496                        ierrp, nerrp, __FILE__, __LINE__ )
00497                endif
00498 
00499                if ( ila_appli_compranks(ii,2) < ila_appli_compranks(ii,1) ) then
00500                   ila_appli_compranks(ii,2) = ila_appli_compranks(ii,1)
00501                   PRINT *, '| | WARNING: driver set max_value equal to min_value ', ila_appli_compranks(ii,1) 
00502                endif
00503 
00504                if ( ila_appli_compranks(ii,3) <= 0 ) then
00505                   ila_appli_compranks(ii,3) = 1
00506                   PRINT *, '| | WARNING: driver set incr_value to 1!' 
00507                endif
00508 
00509             enddo
00510 
00511 ! 3.6.2.3. Store it in the global arrays
00512 
00513         iga_appli_compranks(n_ranksets+1:n_ranksets+iga_appli_nbtot_ranksets(i),:)&
00514            = ila_appli_compranks(:,:) 
00515 
00516 ! 3.6.2.4. Increase the index in the global arrays
00517 
00518         n_ranksets = n_ranksets + iga_appli_nbtot_ranksets(i)
00519 
00520 ! 3.6.2.5. Deallocate the local arrays
00521 
00522         DEALLOCATE ( ila_appli_compranks, STAT = id_err )
00523         IF (id_err > 0) THEN
00524         ierrp (1) = id_err
00525 
00526         call psmile_error_common ( PRISM_Error_Dealloc, 'Appli comp ranks', &
00527            ierrp, 1, __FILE__, __LINE__ )
00528         ENDIF
00529 
00530     END IF
00531 
00532       END DO
00533 
00534       ila_scc_info(1) = ig_MPI
00535       ila_scc_info(2) = ig_nb_appl
00536       ila_scc_info(3) = ig_driver_nb_pes
00537       ila_scc_info(4) = ig_nb_tot_comps
00538       ila_scc_info(5) = ig_nbtot_ranksets
00539 
00540       DO i = 1, ig_driver_nb_pes-1
00541 !> WARNING This is a workaround. A comm_drv_local is not yet defined at this point (done in prismdrv_init_appl)
00542 !> The driver processes should have the ranks from PRISMdrv_root to PRISMdrv_root +  ig_driver_nb_pes - 1
00543     CALL MPI_Send(ila_scc_info, 5, MPI_Integer, PRISMdrv_root + i,  0, &
00544        MPI_COMM_WORLD, id_err)
00545       END DO
00546 
00547 ! The other pes of the transformer get some info from the master and allocate
00548 ! some structure (the right values are not required in the structure)
00549   ELSE
00550 
00551       CALL MPI_Recv (ila_scc_info, 5, MPI_Integer, PRISMdrv_root, 0, &
00552      MPI_COMM_WORLD, il_status, id_err)
00553 
00554       ig_MPI             = ila_scc_info(1)
00555       ig_nb_appl         = ila_scc_info(2)
00556       ig_driver_nb_pes   = ila_scc_info(3)
00557       ig_nb_tot_comps    = ila_scc_info(4)
00558       ig_nbtot_ranksets  = ila_scc_info(5)
00559 
00560       ALLOCATE ( comm_coupling(0:ig_nb_appl), STAT = id_err )
00561       IF ( id_err > 0 ) THEN
00562       ierrp (1) = id_err
00563       ierrp (2) = ig_nb_appl
00564       call psmile_error_common ( PRISM_Error_Alloc, 'comm_coupling', &
00565          ierrp, 2, __FILE__, __LINE__ )
00566       ENDIF
00567 
00568       ALLOCATE ( iga_appli_nb_pes(0:ig_nb_appl), STAT = id_err )
00569       IF ( id_err > 0 ) THEN
00570       ierrp (1) = id_err
00571       ierrp (2) = ig_nb_appl
00572       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_nb_pes', &
00573          ierrp, 2, __FILE__, __LINE__ )
00574       ENDIF
00575       iga_appli_nb_pes(:) = 0
00576 
00577       ALLOCATE ( cga_appli_name(0:ig_nb_appl), STAT = id_err )
00578       IF ( id_err > 0 ) THEN
00579       ierrp (1) = id_err
00580       ierrp (2) = ig_nb_appl
00581       call psmile_error_common ( PRISM_Error_Alloc, 'cga_appli_name', &
00582          ierrp, 2, __FILE__, __LINE__ )
00583       ENDIF
00584       cga_appli_name(:) = 'trans'
00585 
00586       ALLOCATE ( iga_appli_nb_comps(0:ig_nb_appl), STAT = id_err )
00587       IF ( id_err > 0 ) THEN
00588       ierrp (1) = id_err
00589       ierrp (2) = ig_nb_appl
00590       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_nb_comps', &
00591          ierrp, 2, __FILE__, __LINE__ )
00592       ENDIF
00593       iga_appli_nb_comps(:) = 0
00594 
00595       ALLOCATE ( cga_appli_compname(ig_nb_tot_comps), STAT = id_err )
00596       IF ( id_err > 0 ) THEN
00597       ierrp (1) = id_err
00598       ierrp (2) = ig_nb_tot_comps
00599       call psmile_error_common ( PRISM_Error_Alloc, 'cga_appli_compname', &
00600          ierrp, 2, __FILE__, __LINE__ )
00601       ENDIF
00602       ALLOCATE ( iga_appli_redirect(0:ig_nb_appl), STAT = id_err )
00603       IF ( id_err > 0 ) THEN
00604       ierrp (1) = id_err
00605       ierrp (2) = ig_nb_appl
00606       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_redirect', &
00607          ierrp, 2, __FILE__, __LINE__ )
00608       ENDIF
00609 
00610       ALLOCATE ( iga_appli_compnbranksets(ig_nb_tot_comps), STAT = id_err )
00611       IF ( id_err > 0 ) THEN
00612       ierrp (1) = id_err
00613       ierrp (2) = ig_nb_tot_comps
00614       call psmile_error_common ( PRISM_Error_Alloc, 'iga_appli_compnbranksets', &
00615          ierrp, 2, __FILE__, __LINE__ )
00616       ENDIF
00617       ALLOCATE ( iga_appli_compranks(ig_nbtot_ranksets,3), STAT = id_err )
00618       IF ( id_err > 0 ) THEN
00619       ierrp (1) = id_err
00620       ierrp (2) = ig_nbtot_ranksets
00621       call psmile_error_common ( PRISM_Error_Alloc, 'Nb tot ranksets', &
00622          ierrp, 2, __FILE__, __LINE__ )
00623       ENDIF
00624 
00625 
00626   END IF
00627 !
00628 #ifdef VERBOSE
00629   PRINT *, '| Quit PRISMDrv_set_scc_info'
00630   PRINT *, '|'
00631   call psmile_flushstd
00632 #endif
00633 END SUBROUTINE PRISMDrv_set_scc_info
00634 
00635 
00636 
00637 

Generated on 18 Mar 2011 for Oasis4 by  doxygen 1.6.1