Ignore:
Timestamp:
10/30/09 16:29:39 (15 years ago)
Author:
ymipsl
Message:

Correction bug sur les ids des file_group
+ possibilité de fixer les attributs des groupes à partir de l'ioserver

File:
1 edited

Legend:

Unmodified
Added
Removed
  • XMLIO_SERVER/trunk/src/XMLIO/mod_grid.f90

    r40 r42  
    3030  TYPE(sorted_list),POINTER,SAVE,PRIVATE     :: Ids  
    3131 
     32  INTERFACE grid__set_attribut 
     33    MODULE PROCEDURE grid__set_attribut_id,grid__set_attribut_pt 
     34  END INTERFACE 
     35 
    3236CONTAINS 
    3337  INCLUDE 'vector_grid_contains.inc' 
     
    121125 
    122126 
    123   SUBROUTINE grid__set_attribut(id,attrib) 
     127  SUBROUTINE grid__set_attribut_id(id,attrib,ok) 
     128  USE mod_attribut 
     129  USE error_msg 
     130  IMPLICIT NONE 
     131    CHARACTER(LEN=*),INTENT(IN)   :: id 
     132    TYPE(attribut),INTENT(IN)     :: attrib 
     133    LOGICAL,OPTIONAL,INTENT(OUT)  :: ok 
     134     
     135    TYPE(grid),POINTER              :: Pt_grid 
     136    INTEGER                         :: Pos 
     137    LOGICAL                         :: success 
     138     
     139    CALL sorted_list__find(Ids,hash(Id),Pos,success) 
     140    IF (success) THEN 
     141      Pt_grid=>grid_ids%at(Pos)%Pt 
     142      CALL grid__set_attribut_pt(Pt_grid,attrib) 
     143      IF (PRESENT(OK)) OK=.TRUE. 
     144    ELSE 
     145      IF (.NOT.PRESENT(OK)) THEN 
     146        WRITE(message,*) 'grid id :',id,'is undefined' 
     147        CALL error('mod_grid::grid__set_attribut') 
     148      ELSE 
     149        OK=.FALSE. 
     150      ENDIF 
     151    ENDIF   
     152   
     153  END SUBROUTINE grid__set_attribut_id 
     154       
     155  SUBROUTINE grid__set_attribut_pt(Pt_grid,attrib) 
    124156  USE mod_attribut 
    125157  USE mod_grid_attribut 
    126158  USE error_msg 
    127159  IMPLICIT NONE 
    128     CHARACTER(LEN=*),INTENT(IN) :: id 
     160    TYPE(grid),POINTER        :: Pt_grid 
    129161    TYPE(attribut),INTENT(IN) :: attrib 
    130  
    131     TYPE(grid),POINTER              :: Pt_grid 
    132     INTEGER                         :: Pos 
    133     LOGICAL                         :: success 
    134      
    135     CALL sorted_list__find(Ids,hash(Id),Pos,success) 
    136     IF (success) THEN 
    137       Pt_grid=>grid_ids%at(Pos)%Pt 
    138     ELSE 
    139       WRITE(message,*) 'grid id :',id,'is undefined' 
    140       CALL error('mod_grid::grid__set_attribut') 
    141     ENDIF   
    142162     
    143163    SELECT CASE(attrib%name) 
     
    148168     END SELECT 
    149169 
    150      WRITE(message,*) 'grid id ',id,' : Attribute type is incompatible with the provided value' 
     170     WRITE(message,*) 'grid attribut ',attrib%name,' : type :',attrib%type,' : Attribute type is incompatible with the provided value' 
    151171     CALL error('mod_grid::grid__set_attribut') 
    152172     
    153   END SUBROUTINE grid__set_attribut 
     173  END SUBROUTINE grid__set_attribut_pt 
    154174   
    155175  SUBROUTINE grid__set_dimension(pt_grid, ni, nj) 
Note: See TracChangeset for help on using the changeset viewer.