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_zoom.f90

    r29 r40  
    120120   END SUBROUTINE zoom__set    
    121121 
     122 SUBROUTINE zoom__set_attribut(id,attrib) 
     123  USE mod_attribut 
     124  USE mod_zoom_attribut 
     125  USE error_msg 
     126  IMPLICIT NONE 
     127    CHARACTER(LEN=*),INTENT(IN) :: id 
     128    TYPE(attribut),INTENT(IN) :: attrib 
     129 
     130    TYPE(zoom),POINTER             :: Pt_zoom 
     131    INTEGER                         :: Pos 
     132    LOGICAL                         :: success 
     133     
     134    CALL sorted_list__find(Ids,hash(Id),Pos,success) 
     135    IF (success) THEN 
     136      Pt_zoom=>zoom_ids%at(Pos)%Pt 
     137    ELSE 
     138      WRITE(message,*) 'zoom id :',id,'is undefined' 
     139      CALL error('mod_zoom::zoom__set_attribut') 
     140    ENDIF   
     141     
     142    SELECT CASE(attrib%name) 
     143      CASE (zoom__name) 
     144        IF (attrib%type==string0) CALL  zoom__set(pt_zoom,name=attrib%string0_ptr) ; RETURN 
     145      CASE (zoom__description) 
     146        IF (attrib%type==string0) CALL  zoom__set(pt_zoom,description=attrib%string0_ptr) ; RETURN 
     147      CASE (zoom__ni) 
     148        IF (attrib%type==integer0) CALL  zoom__set(pt_zoom,ni_glo=attrib%integer0_ptr) ; RETURN 
     149      CASE (zoom__nj) 
     150        IF (attrib%type==integer0) CALL  zoom__set(pt_zoom,nj_glo=attrib%integer0_ptr) ; RETURN 
     151      CASE (zoom__ibegin) 
     152        IF (attrib%type==integer0) CALL  zoom__set(pt_zoom,ibegin_glo=attrib%integer0_ptr) ; RETURN 
     153      CASE (zoom__jbegin) 
     154        IF (attrib%type==integer0) CALL  zoom__set(pt_zoom,jbegin_glo=attrib%integer0_ptr) ; RETURN 
     155     END SELECT 
     156 
     157     WRITE(message,*) 'zoom id ',id,' : Attribute type is incompatible with the provided value' 
     158     CALL error('mod_zoom::zoom__set_attribut') 
     159     
     160  END SUBROUTINE zoom__set_attribut 
    122161 
    123162  SUBROUTINE zoom__get(Id,pt_zoom) 
Note: See TracChangeset for help on using the changeset viewer.