Changeset 187


Ignore:
Timestamp:
05/03/11 11:55:06 (13 years ago)
Author:
hozdoba
Message:
 
Location:
XMLIO_V2/dev/dev_rv
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • XMLIO_V2/dev/dev_rv/Makefile.wk

    r186 r187  
    22###################        Projet xios - xmlioserver       ##################### 
    33#                                                                              # 
    4 #         * Copyright © OZDOBA Hervé (herve.ozdoba@lsce.ipsl.fr) *             # 
     4#                   * © OZDOBA Hervé (herve.ozdoba@lsce.ipsl.fr) *             # 
    55#                   * © MEURDESOIF Yann (yann.meurdesoif@cea.fr) *             # 
    66#                                    * Avril 2010 - Octobre 2011 *             # 
     
    1515VTK       = no 
    1616GUI       = no 
    17 NPROC     = 3 
     17NPROC     = 6 
    1818CSUITE    = gnu 
    1919PFORME    = fedora-wk 
  • XMLIO_V2/dev/dev_rv/src/xmlio/attribute_template_impl.hpp

    r182 r187  
    5959         T CAttributeTemplate<T>::getValue(void) const 
    6060      { 
     61         if (SuperClass::isEmpty()) 
     62            ERROR("T CAttributeTemplate<T>::getValue(void) const", 
     63                  << "[ id = " << this->getId() << "]" 
     64                  << " L'attribut est requis mais n'est pas défini !"); 
    6165         return (SuperClass::getValue<T>()); 
    6266      } 
  • XMLIO_V2/dev/dev_rv/src/xmlio/fake_client/fake_nemo.f90

    r184 r187  
    2020                                                  comm_client_server   ! communicateur client-serveur 
    2121      REAL(kind = 8), DIMENSION(10000)  :: real_array 
    22       INTEGER                           :: rankGrp, error 
    23       INTEGER                           :: ibegin, iend, jbegin, jend, data_ni, data_ibegin 
     22      INTEGER                           :: rankGrp, sizeGrp, error, i 
     23      INTEGER                           :: ibegin, iend, jbegin, jend, data_ni, data_ibegin, ni_glo, nj_glo 
    2424      TYPE(XDate)                       :: init_date_nemo  = XDate(1985, 03, 15, 17, 35, 00) 
    2525      TYPE(XHandle)                     :: nemo_style_ctxt = NULLHANDLE 
     
    2828                                           temp_mod__  = NULLHANDLE, & 
    2929                                           temp_mod___ = NULLHANDLE 
    30  
    31  
    32  
     30                                            
    3331      CALL MPI_COMM_RANK(comm_client, rankGrp, error) 
    34  
     32      CALL MPI_COMM_SIZE(comm_client, sizeGrp, error) 
     33       
     34      DO i = 1, 10000 
     35         real_array(i) = i; 
     36      END DO 
     37       
    3538      IF (rankGrp .EQ. 0) THEN 
    3639          PRINT*," Starting NEMO Client Tests ..." 
     
    7174                                ftype          = GFIELD,       & 
    7275                                operation_     = "instant",    & 
    73                                 enabled_       = .TRUE._1) 
     76                                enabled_       = .TRUE._1,     & 
     77                                freq_op_       = "1h") 
    7478 
    7579      CALL xml_tree_add(parent_hdl  = temp_mod,        & 
     
    214218                        child_id    = "simple_domaine_grp") 
    215219 
     220 
     221      ni_glo = 100 
     222      nj_glo = 50 
    216223      IF (rankGrp .EQ. 0) THEN 
    217224         ibegin = 1 
     225         iend   = 26 
     226         jbegin = 1 
     227         jend   = 50 
     228         data_ni     = 25 
     229         data_ibegin = 0 
     230      ELSE IF (rankGrp .EQ. 1) THEN 
     231         ibegin = 25 
    218232         iend   = 51 
    219233         jbegin = 1 
    220234         jend   = 50 
    221          data_ni     = 50 
    222          data_ibegin = 0 
    223       ELSE IF (rankGrp .EQ. 1) THEN 
     235         data_ni     = 25 
     236         data_ibegin = 1 
     237      ELSE IF (rankGrp .EQ. 2) THEN 
    224238         ibegin = 50 
     239         iend   = 76 
     240         jbegin = 1 
     241         jend   = 50 
     242         data_ni     = 25 
     243         data_ibegin = 1 
     244      ELSE IF (rankGrp .EQ. 3) THEN 
     245         ibegin = 75 
    225246         iend   = 100 
    226247         jbegin = 1 
    227248         jend   = 50 
    228          data_ni     = 50 
    229          data_ibegin = 1 
     249         data_ni     = 25 
     250         data_ibegin = 1          
    230251      END IF  
    231252 
     
    235256                                 latvalue_      = real_array(1:((jend-jbegin+1)*(iend-ibegin+1))), & 
    236257                                 data_dim_      = 2,              & 
    237                                  ni_glo_        = 100,            & 
    238                                  nj_glo_        = 50,             & 
     258                                 ni_glo_        = ni_glo,         & 
     259                                 nj_glo_        = nj_glo,         & 
    239260                                 ibegin_        = ibegin,         & 
    240261                                 iend_          = iend,           & 
     
    269290                                 zoom_ibegin_   = 21,                 & 
    270291                                 zoom_jbegin_   = 5 ,                 & 
    271                                  zoom_ni_       = 60,                 & 
     292                                 zoom_ni_       = 20,                 & 
    272293                                 zoom_nj_       = 15) 
    273294 
     
    278299                        child_id    = "simple_domaine1") 
    279300 
     301 
     302      ni_glo = 90 
     303      nj_glo = 20 
    280304      IF (rankGrp .EQ. 0) THEN 
    281305         ibegin = 1 
    282306         iend   = 90 
    283307         jbegin = 1 
    284          jend   = 10         
     308         jend   = 5         
    285309      ELSE IF (rankGrp .EQ. 1) THEN 
    286310         ibegin = 1 
    287311         iend   = 90 
     312         jbegin = 6 
     313         jend   = 10 
     314      ELSE IF (rankGrp .EQ. 2) THEN 
     315         ibegin = 1 
     316         iend   = 90 
    288317         jbegin = 11 
     318         jend   = 15 
     319      ELSE IF (rankGrp .EQ. 3) THEN 
     320         ibegin = 1 
     321         iend   = 90 
     322         jbegin = 16 
    289323         jend   = 20 
    290324      END IF 
     
    298332                                 latvalue_      = real_array(1:((jend-jbegin+1)*(iend-ibegin+1))), & 
    299333                                 data_dim_      = 2,              & 
    300                                  ni_glo_        = 90,             & 
    301                                  nj_glo_        = 20,             & 
     334                                 ni_glo_        = ni_glo,         & 
     335                                 nj_glo_        = nj_glo,         & 
    302336                                 ibegin_        = ibegin,         & 
    303337                                 iend_          = iend,           & 
  • XMLIO_V2/dev/dev_rv/src/xmlio/functor.cpp

    r152 r187  
    1515 
    1616      CFunctor::CFunctor(const StdString & id, DoubleArray doutput, 
    17                          const std::vector<size_t> size, 
     17                         const std::vector<StdSize> size, 
    1818                         const CFunData & data, CFuncType type) 
    1919         : SuperClass(id) 
     
    3636      { return (this->doutput); } 
    3737 
    38       const std::vector<size_t> & CFunctor::getShape(void) const 
     38      const std::vector<StdSize> & CFunctor::getShape(void) const 
    3939      { return (this->size); } 
    4040 
    41       size_t CFunctor::getSize(void) const 
     41      StdSize CFunctor::getSize(void) const 
    4242      { return (this->doutput->size()); } 
    4343 
    4444      //--------------------------------------------------------------- 
    4545 
    46       void CFunctor::resize(size_t x, size_t y, size_t z) 
     46      void CFunctor::resize(StdSize x, StdSize y, StdSize z) 
    4747      { 
    4848         this->size.clear(); 
     
    5555      void CFunctor::resize(const std::vector<StdSize> & sizes) 
    5656      { 
    57          size_t newsize = 1; 
     57         StdSize newsize = 1; 
    5858         this->size.clear(); 
    5959         std::vector<StdSize>::const_iterator it = sizes.begin(), end = sizes.end(); 
  • XMLIO_V2/dev/dev_rv/src/xmlio/main_server.cpp

    r185 r187  
    1616      CXIOSManager::Initialise(CXIOSManager::CLIENT_SERVER, &argc, &argv); 
    1717       
    18       CXIOSManager::AddClient("nemo"    , 2, 2, &nemo_fake_entry); 
     18      CXIOSManager::AddClient("nemo"    , 4, 2, &nemo_fake_entry); 
    1919      //CXIOSManager::AddClient("orchidee", 1, 1, &orchidee_fake_entry); 
    2020      //CXIOSManager::AddClient("lmdz"    , 4, 2, &lmdz_fake_entry); 
  • XMLIO_V2/dev/dev_rv/src/xmlio/manager/xios_manager.hpp

    r180 r187  
    4848                                     comm::CMPIManager::GetCommWorld()); 
    4949 
    50       protected : 
     50      public : 
    5151 
    5252         /// Accesseurs statiques /// 
     
    5454         static XIOSStatus GetStatus(void); 
    5555         static StdString  GetClientName(void); 
     56          
     57      protected : 
    5658          
    5759         static StdSize GetNbClient(void); 
  • XMLIO_V2/dev/dev_rv/src/xmlio/node/domain.cpp

    r185 r187  
    55#include "group_template_impl.hpp" 
    66 
     7#include "mpi_manager.hpp" 
     8 
    79#include <algorithm> 
    810 
     
    1416   CDomain::CDomain(void) 
    1517      : CObjectTemplate<CDomain>(), CDomainAttributes() 
    16       , isChecked(false), local_mask(new CArray<int, 2>(boost::extents[10][10])), relFiles() 
     18      , isChecked(false), local_mask(new CArray<int, 2>(boost::extents[0][0])), relFiles() 
    1719      , ibegin_sub(), iend_sub(), jbegin_sub(), jend_sub() 
    1820      , lonvalue_sub(), latvalue_sub() 
     
    2123   CDomain::CDomain(const StdString & id) 
    2224      : CObjectTemplate<CDomain>(id), CDomainAttributes() 
    23       , isChecked(false), local_mask(new CArray<int, 2>(boost::extents[10][10])), relFiles() 
     25      , isChecked(false), local_mask(new CArray<int, 2>(boost::extents[0][0])), relFiles() 
    2426      , ibegin_sub(), iend_sub(), jbegin_sub(), jend_sub() 
    2527      , lonvalue_sub(), latvalue_sub() 
     
    124126          (ni_glo.isEmpty() || nj_glo.getValue() <= 0 )) 
    125127         ERROR("CDomain::checkAttributes(void)", 
     128               << "[ Id = " << this->getId() << " ] " 
    126129               << "Le domaine global est mal défini," 
    127130               << " vérifiez les valeurs de \'ni_glo\' et \'nj_glo\' !") ; 
     
    159162          ibegin.getValue() < 1 || iend.getValue() > ni_glo.getValue()) 
    160163         ERROR("CDomain::checkAttributes(void)", 
     164               << "[ Id = " << this->getId() << " ] " 
    161165               << "Domaine local mal défini," 
    162166               << " vérifiez les valeurs ni, ni_glo, ibegin, iend") ; 
     
    294298         data_ibegin.setValue(0) ; 
    295299      if (data_jbegin.isEmpty() && (data_dim.getValue() == 2)) 
    296            data_jbegin.setValue(0) ; 
     300         data_jbegin.setValue(0) ; 
    297301 
    298302      if (!data_ni.isEmpty() && (data_ni.getValue() <= 0)) 
     
    398402   void CDomain::completeLonLat(void) 
    399403   { 
    400       //ARRAY_CREATE(value, valuetype, numdims, extent)// todo 
    401       //ARRAY_CREATE(value, valuetype, numdims, extent) 
     404      ARRAY_CREATE(lonvalue_temp, double, 1, [0]); 
     405      ARRAY_CREATE(latvalue_temp, double, 1, [0]); 
     406       
     407      const int ibegin_serv  = ibegin.getValue(), 
     408                jbegin_serv  = jbegin.getValue(), 
     409                zoom_ni_serv = zoom_ni_loc.getValue(), 
     410                zoom_nj_serv = zoom_nj_loc.getValue(); 
     411                       
     412      /*std::cout << "Rang du serveur :" << comm::CMPIManager::GetCommRank()   << std::endl 
     413                << "Begin serv : "     << ibegin_serv << ", " << jbegin_serv <<  std::endl 
     414                << "End serv : "       << iend_serv   << ", " << jend_serv   <<  std::endl 
     415                << "Zoom_loc begin : " << zoom_ibegin_loc << ", " << zoom_jbegin_loc <<  std::endl 
     416                << "Zoom_loc size : "  << zoom_ni_loc << ", " << zoom_nj_loc <<  std::endl;*/ 
     417       
    402418       
    403419      ARRAY(double, 1) lonvalue_ = this->lonvalue.getValue(), 
     
    406422      if (this->data_dim.getValue() == 2) 
    407423      { 
     424         StdSize dm = zoom_ni_serv * zoom_nj_serv; 
    408425         StdSize dn = this->ni.getValue() * this->nj.getValue(); 
     426          
    409427         lonvalue_->resize(boost::extents[dn]); 
    410428         latvalue_->resize(boost::extents[dn]); 
    411  
    412          for (StdSize k = 0; k < lonvalue_sub.size(); k++) 
    413          { 
    414             int l = 0; 
    415             ARRAY(double, 1) lonvalue_loc = this->lonvalue_sub[k], 
    416                              latvalue_loc = this->latvalue_sub[k]; 
    417             const int ibegin_loc = ibegin_sub[k], iend_loc = iend_sub[k], 
    418                       jbegin_loc = jbegin_sub[k], jend_loc = jend_sub[k]; 
    419                                                                   
    420             for (int i = ibegin_loc-1; i <= (iend_loc-1); i++) 
    421             { 
    422                for (int j = jbegin_loc-1; j <= (jend_loc-1); j++) 
    423                { 
    424                   (*lonvalue_)[i+j*this->ni.getValue()] = (*lonvalue_loc)[l];               
    425                   (*latvalue_)[i+j*this->ni.getValue()] = (*latvalue_loc)[l++]; 
    426                } 
    427             } 
    428          }    
    429       } 
    430       else 
    431       { 
    432          StdSize dn = this->ni.getValue(); 
    433          lonvalue_->resize(boost::extents[dn]); 
    434          latvalue_->resize(boost::extents[dn]); 
     429         lonvalue_temp->resize(boost::extents[dm]); 
     430         latvalue_temp->resize(boost::extents[dm]); 
    435431          
    436432         for (StdSize k = 0; k < lonvalue_sub.size(); k++) 
     
    442438                      jbegin_loc = jbegin_sub[k], jend_loc = jend_sub[k]; 
    443439                       
    444             for (int i = ibegin_loc-1; i <= (iend_loc-1); i++) 
     440            for (int i = ibegin_loc - ibegin_serv; i < (iend_loc - ibegin_serv + 1); i++) 
     441            { 
     442               for (int j = jbegin_loc - jbegin_serv; j < (jend_loc - jbegin_serv + 1); j++) 
     443               { 
     444                  (*lonvalue_)[i + j * this->ni.getValue()] = (*lonvalue_loc)[l];               
     445                  (*latvalue_)[i + j * this->ni.getValue()] = (*latvalue_loc)[l++]; 
     446               } 
     447            } 
     448         } 
     449         this->lonvalue.setValue(lonvalue_temp); 
     450         this->latvalue.setValue(latvalue_temp); 
     451      } 
     452      else 
     453      { 
     454         lonvalue_->resize(boost::extents[this->ni.getValue()]); 
     455         latvalue_->resize(boost::extents[this->nj.getValue()]); 
     456         lonvalue_temp->resize(boost::extents[zoom_ni_serv]); 
     457         latvalue_temp->resize(boost::extents[zoom_nj_serv]); 
     458          
     459         for (StdSize k = 0; k < lonvalue_sub.size(); k++) 
     460         { 
     461            int l = 0; 
     462            ARRAY(double, 1) lonvalue_loc = this->lonvalue_sub[k], 
     463                             latvalue_loc = this->latvalue_sub[k]; 
     464            const int ibegin_loc = ibegin_sub[k], iend_loc = iend_sub[k], 
     465                      jbegin_loc = jbegin_sub[k], jend_loc = jend_sub[k]; 
     466                       
     467            for (int i = ibegin_loc - ibegin_serv; i < (iend_loc - ibegin_loc + 1); i++) 
    445468               (*lonvalue_)[i] = (*lonvalue_loc)[l++]; 
    446469                
    447             for (int j = jbegin_loc-1, l = 0; j <= (jend_loc-1); j++) 
     470            for (int j = jbegin_loc - jbegin_serv; j < (jend_loc - jbegin_loc + 1); j++) 
    448471               (*latvalue_)[j] = (*latvalue_loc)[l++]; 
    449          }          
     472         }        
     473         this->lonvalue.setValue(lonvalue_temp); 
     474         this->latvalue.setValue(latvalue_temp); 
    450475      } 
    451476   } 
     
    551576      else 
    552577      { // CÃŽté serveur uniquement 
    553          this->completeLonLat(); 
     578         if (!this->isEmpty()) 
     579            this->completeLonLat(); 
    554580      } 
    555581      this->completeMask(); 
  • XMLIO_V2/dev/dev_rv/src/xmlio/node/field.cpp

    r182 r187  
    77#include "node_type.hpp" 
    88 
     9#include "xios_manager.hpp" 
     10 
    911namespace xmlioserver{ 
    1012namespace tree { 
     
    1416   CField::CField(void) 
    1517      : CObjectTemplate<CField>(), CFieldAttributes() 
    16       , baseRefObject(), refObject(), grid(), file(), foperation(NULL) 
     18      , refObject(), baseRefObject() 
     19      , grid(), file() 
     20      , freq_operation(), freq_write() 
     21      , foperation() 
     22      , data() 
    1723   { /* Ne rien faire de plus */ } 
    1824 
    1925   CField::CField(const StdString & id) 
    2026      : CObjectTemplate<CField>(id), CFieldAttributes() 
    21       , baseRefObject(), refObject(), foperation(NULL) 
     27      , refObject(), baseRefObject() 
     28      , grid(), file() 
     29      , freq_operation(), freq_write() 
     30      , foperation() 
     31      , data() 
    2232   { /* Ne rien faire de plus */ } 
    2333 
     
    2636      this->grid.reset() ; 
    2737      this->file.reset() ; 
    28       if (this->foperation == NULL) 
    29          delete this->foperation; 
     38      this->foperation.reset() ; 
     39      this->data.reset() ; 
    3040   } 
    3141 
     
    107117      boost::shared_ptr<CField> refer_sptr; 
    108118      CField * refer_ptr = this; 
     119       
    109120      this->baseRefObject = CObjectFactory::GetObject<CField>(this); 
     121       
    110122      while (refer_ptr->hasDirectFieldReference()) 
    111123      { 
     
    131143   void  CField::solveOperation(void) 
    132144   { 
    133       // TODO : à compléter; 
     145      using namespace func; 
     146      using namespace date; 
     147        
     148      StdString id = this->getBaseFieldReference()->getId();       
     149      if (operation.isEmpty() || freq_op.isEmpty() || this->file->output_freq.isEmpty()) 
     150      { 
     151         ERROR("CField::solveOperation(void)", 
     152               << "[ id = " << id << "]" 
     153               << "Impossible de définir une opération pour le champ !"); 
     154      } 
     155 
     156      if (CXIOSManager::GetStatus() == CXIOSManager::LOC_SERVER) 
     157      { 
     158         this->freq_operation = CDuration::FromString(this->file->output_freq.getValue()); 
     159         this->freq_write     = CDuration::FromString(this->file->output_freq.getValue()); 
     160         //this->foperation = boost::shared_ptr<func::CFunctor>(new CInstant()); 
     161      } 
     162      else 
     163      { 
     164         this->freq_operation = CDuration::FromString(freq_op.getValue()); 
     165         this->freq_write     = CDuration::FromString(this->file->output_freq.getValue()); 
     166          
     167#define DECLARE_FUNCTOR(MType, mtype) \ 
     168   if  (operation.getValue().compare(#mtype) == 0){} 
     169      //this->foperation = boost::shared_ptr<func::CFunctor>(new C##MType()); 
     170    
     171#include "functor_type.conf" 
     172      } 
    134173   } 
    135174    
  • XMLIO_V2/dev/dev_rv/src/xmlio/node/field.hpp

    r181 r187  
    55#include "xmlioserver_spl.hpp" 
    66#include "group_factory.hpp" 
    7  
    87#include "functor.hpp" 
    98#include "functor_type.hpp" 
    10  
     9#include "duration.hpp" 
    1110#include "declare_group.hpp" 
    1211 
     
    9089 
    9190         /// Propriétés privées /// 
     91          
     92         std::vector<boost::shared_ptr<CField> > refObject; 
    9293         boost::shared_ptr<CField> baseRefObject; 
    93          std::vector<boost::shared_ptr<CField> > refObject; 
     94         boost::shared_ptr<CGrid>  grid ; 
     95         boost::shared_ptr<CFile>  file; 
    9496 
    95          boost::shared_ptr<CGrid> grid ; 
    96          boost::shared_ptr<CFile> file; 
    97  
    98          func::CFunctor * foperation; 
     97         date::CDuration freq_operation, freq_write; 
     98         boost::shared_ptr<func::CFunctor> foperation; 
     99          
     100         ARRAY(double, 1) data; 
    99101 
    100102   }; // class CField 
  • XMLIO_V2/dev/dev_rv/src/xmlio/output/nc4_data_output.cpp

    r185 r187  
    6464         if (domain->IsWritten(this->filename)) return; 
    6565         domain->checkAttributes(); 
     66          
     67         if (domain->isEmpty()) return; 
    6668 
    6769         std::vector<StdString> dim0, dim1; 
     
    201203         boost::shared_ptr<CDomain> domain = 
    202204            CObjectFactory::GetObject<CDomain>(grid->domain_ref.getValue()); 
     205             
     206         if (domain->isEmpty()) return; 
    203207 
    204208         StdString timeid    = StdString("time_counter"); 
     
    263267                  SuperClassWriter::addAttribute 
    264268                     ("units", field->unit.getValue(), &fieldid); 
    265  
    266                if (!field->operation.isEmpty()) 
    267                   SuperClassWriter::addAttribute 
     269                      
     270               SuperClassWriter::addAttribute 
    268271                     ("online_operation", field->operation.getValue(), &fieldid); 
    269  
    270                {  
     272                      
     273               if (wtime) 
     274               { 
     275                  SuperClassWriter::addAttribute 
     276                        ("interval_operation", field->freq_op.getValue(), &fieldid); 
     277                  SuperClassWriter::addAttribute 
     278                        ("interval_write", field->getRelFile()->output_freq.getValue(), &fieldid); 
     279               } 
     280 
     281               {  // Ecriture des coordonnées 
     282                
    271283                  StdString coordstr; //boost::algorithm::join(coodinates, " ") 
    272284                  std::vector<StdString>::iterator  
  • XMLIO_V2/dev/dev_rv/xmlioserver.geany

    r170 r187  
    1919 
    2020[files] 
    21 current_page=2 
    22 FILE_NAME_0=0;Make;0;16;1;1;0;/work/dev_rv/Makefile.wk;0;3 
    23 FILE_NAME_1=0;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/main_server.cpp;0;3 
    24 FILE_NAME_2=0;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/xml_node.cpp;0;3 
     21current_page=9 
     22FILE_NAME_0=840;Make;0;16;1;1;0;/work/dev_rv/Makefile.wk;0;3 
     23FILE_NAME_1=138;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/main_server.cpp;0;3 
     24FILE_NAME_2=13467;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/node/grid.cpp;0;3 
     25FILE_NAME_3=2395;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/node/domain.hpp;0;3 
     26FILE_NAME_4=3378;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/node/grid.hpp;0;3 
     27FILE_NAME_5=1286;Conf;0;16;0;1;0;/work/dev_rv/src/xmlio/config/domain_attribute.conf;0;3 
     28FILE_NAME_6=160;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/output/onetcdf4.hpp;0;3 
     29FILE_NAME_7=2909;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/output/nc4_data_output.cpp;0;3 
     30FILE_NAME_8=356;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/array_mac.hpp;0;3 
     31FILE_NAME_9=4101;Fortran;0;16;0;1;0;/work/dev_rv/src/xmlio/fortran/impi_interface.f90;0;3 
     32FILE_NAME_10=6236;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/manager/mpi_manager.cpp;0;3 
     33FILE_NAME_11=189;C++;0;16;0;1;0;/work/dev_rv/src/xmlio/fortran/impi_interface.hpp;0;3 
    2534 
    2635[build-menu] 
Note: See TracChangeset for help on using the changeset viewer.