Ignore:
Timestamp:
09/23/13 18:06:31 (11 years ago)
Author:
ymipsl
Message:
  • XIOS integration -

Compiling with "-with_xios" option. Adapt path to find XIOS library (arch.path)
Retro-compatible with the old output. If xios is not present, dynamico will use the standard writefield function.
Need to have the iodef.xml configuration file in the exec directory

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/write_field.f90

    r161 r171  
    22USE genmod 
    33implicit none 
    4    
     4  PRIVATE   
    55  INTEGER,SAVE :: ncprec 
    66   
     
    1111  END TYPE ncvar 
    1212 
    13   integer, parameter :: MaxWriteField = 1000 
    14   integer, dimension(MaxWriteField),save :: FieldId 
    15   TYPE(ncvar), dimension(MaxWriteField),save :: FieldVarId 
    16   integer, dimension(MaxWriteField),save :: FieldIndex 
    17   character(len=255), dimension(MaxWriteField) ::  FieldName  
     13  INTEGER, PARAMETER :: MaxWriteField = 1000 
     14  INTEGER, DIMENSION(MaxWriteField),SAVE :: FieldId 
     15  TYPE(ncvar), dimension(MaxWriteField),SAVE :: FieldVarId 
     16  INTEGER, DIMENSION(MaxWriteField),SAVE :: FieldIndex 
     17  CHARACTER(len=255), DIMENSION(MaxWriteField) ::  FieldName  
    1818    
    19   integer,save :: NbField = 0 
     19  INTEGER,SAVE :: NbField = 0 
    2020   
    21   contains 
     21  PUBLIC init_writeField, writefield, close_files 
     22   
     23  CONTAINS 
    2224   
    2325    SUBROUTINE init_writeField 
Note: See TracChangeset for help on using the changeset viewer.