Ignore:
Timestamp:
09/17/09 10:02:37 (15 years ago)
Author:
ymipsl
Message:
  • Les attributs XML peuvent désormais être passer dynamiquement à travers l'interface du server IO.
  • ajout d'un attribut name_suffix pour les fichiers

YM

File:
1 edited

Legend:

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

    r29 r40  
    120120  END SUBROUTINE grid__set 
    121121 
     122 
     123  SUBROUTINE grid__set_attribut(id,attrib) 
     124  USE mod_attribut 
     125  USE mod_grid_attribut 
     126  USE error_msg 
     127  IMPLICIT NONE 
     128    CHARACTER(LEN=*),INTENT(IN) :: id 
     129    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   
     142     
     143    SELECT CASE(attrib%name) 
     144      CASE (grid__name) 
     145        IF (attrib%type==string0) CALL  grid__set(pt_grid,name=attrib%string0_ptr) ; RETURN 
     146      CASE (grid__description) 
     147        IF (attrib%type==string0) CALL  grid__set(pt_grid,description=attrib%string0_ptr) ; RETURN 
     148     END SELECT 
     149 
     150     WRITE(message,*) 'grid id ',id,' : Attribute type is incompatible with the provided value' 
     151     CALL error('mod_grid::grid__set_attribut') 
     152     
     153  END SUBROUTINE grid__set_attribut 
     154   
    122155  SUBROUTINE grid__set_dimension(pt_grid, ni, nj) 
    123156  IMPLICIT NONE 
Note: See TracChangeset for help on using the changeset viewer.