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/IOSERVER/mod_event_server.f90

    r26 r40  
    6464      CASE (event_id_write_Field3d) 
    6565        CALL event__write_Field3d 
     66 
     67      CASE (event_id_set_attribut) 
     68        CALL event__set_attribut 
    6669 
    6770      CASE (event_id_stop_ioserver) 
     
    414417     
    415418  END SUBROUTINE event__close_io_definition 
    416      
    417      
     419   
     420  SUBROUTINE event__set_attribut 
     421   USE mod_attribut 
     422   IMPLICIT NONE 
     423     TYPE(attribut) :: attrib 
     424     INTEGER        :: len_id 
     425      
     426     CALL unpack(len_id) 
     427     CALL sub_internal 
     428   CONTAINS 
     429       
     430     SUBROUTINE sub_internal 
     431       CHARACTER(LEN=len_id) :: id 
     432        
     433       CALL unpack(id) 
     434       CALL unpack(attrib) 
     435       CALL iom__set_attribut(id,attrib) 
     436       CALL attr_deallocate(attrib) 
     437     END SUBROUTINE sub_internal 
     438  END SUBROUTINE event__set_attribut     
     439 
    418440END MODULE mod_event_server    
Note: See TracChangeset for help on using the changeset viewer.