Ignore:
Timestamp:
06/04/19 18:03:54 (5 years ago)
Author:
dubos
Message:

devel : introduced derived type to store cell bounds

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/sphere/geometry.f90

    r863 r879  
    104104  USE field_mod 
    105105  IMPLICIT NONE 
    106    
     106  INTEGER, PARAMETER :: nvertex=6    ! FIXME unstructured 
     107 
    107108    CALL allocate_field(geom%Ai,field_t,type_real,name='Ai') 
    108109 
    109110    CALL allocate_field(geom%xyz_i,field_t,type_real,3) 
    110     CALL allocate_field(geom%lon_i,field_t,type_real) 
    111     CALL allocate_field(geom%lat_i,field_t,type_real) 
     111    CALL allocate_field(geom%lon_i,field_t,type_real, name='lon_i') 
     112    CALL allocate_field(geom%lat_i,field_t,type_real, name='lat_i') 
    112113    CALL allocate_field(geom%elon_i,field_t,type_real,3) 
    113114    CALL allocate_field(geom%elat_i,field_t,type_real,3) 
     
    115116 
    116117    CALL allocate_field(geom%xyz_e,field_u,type_real,3) 
    117     CALL allocate_field(geom%lon_e,field_u,type_real) 
    118     CALL allocate_field(geom%lat_e,field_u,type_real) 
     118    CALL allocate_field(geom%lon_e,field_u,type_real, name='lon_e') 
     119    CALL allocate_field(geom%lat_e,field_u,type_real, name='lat_e') 
    119120    CALL allocate_field(geom%elon_e,field_u,type_real,3) 
    120121    CALL allocate_field(geom%elat_e,field_u,type_real,3) 
     
    123124 
    124125    CALL allocate_field(geom%xyz_v,field_z,type_real,3) 
    125     CALL allocate_field(geom%de,field_u,type_real) 
    126     CALL allocate_field(geom%le,field_u,type_real) 
    127     CALL allocate_field(geom%le_de,field_u,type_real) 
     126    CALL allocate_field(geom%de,field_u,type_real, name='de') 
     127    CALL allocate_field(geom%le,field_u,type_real, name='le') 
     128    CALL allocate_field(geom%le_de,field_u,type_real, name='le_de') 
    128129    CALL allocate_field(geom%bi,field_t,type_real) 
    129     CALL allocate_field(geom%Av,field_z,type_real) 
    130     CALL allocate_field(geom%S1,field_t,type_real,6) 
    131     CALL allocate_field(geom%S2,field_t,type_real,6) 
    132     CALL allocate_field(geom%Riv,field_t,type_real,6) 
    133     CALL allocate_field(geom%Riv2,field_t,type_real,6) 
    134     CALL allocate_field(geom%ne,field_t,type_integer,6) 
    135     CALL allocate_field(geom%Wee,field_u,type_real,5,2) 
     130    CALL allocate_field(geom%Av,field_z,type_real, name='Av') 
     131    CALL allocate_field(geom%S1,field_t,type_real,nvertex) 
     132    CALL allocate_field(geom%S2,field_t,type_real,nvertex) 
     133    CALL allocate_field(geom%Riv,field_t,type_real,nvertex) 
     134    CALL allocate_field(geom%Riv2,field_t,type_real,nvertex) 
     135    CALL allocate_field(geom%ne,field_t,type_integer,nvertex) 
     136    CALL allocate_field(geom%Wee,field_u,type_real,5,2) ! FIXME unstructured 
    136137    CALL allocate_field(geom%bi,field_t,type_real) 
    137     CALL allocate_field(geom%fv,field_z,type_real) 
     138    CALL allocate_field(geom%fv,field_z,type_real, name='fv') 
    138139 
    139140  END SUBROUTINE allocate_geometry 
Note: See TracChangeset for help on using the changeset viewer.