New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 2458 for branches/nemo_v3_3_beta/NEMOGCM/EXTERNAL/XMLIO_SERVER – NEMO

Ignore:
Timestamp:
2010-12-07T11:18:04+01:00 (13 years ago)
Author:
smasson
Message:

nemo_v3_3_beta: update mod_interface_ioipsl.f90, see http://forge.ipsl.jussieu.fr/ioserver/changeset/136

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/EXTERNAL/XMLIO_SERVER/src/IOSERVER/mod_interface_ioipsl.f90

    r2364 r2458  
    3838  USE ioipsl 
    3939  USE xmlio 
    40   USE mod_ioserver_namelist 
    4140  IMPLICIT NONE 
    4241    INTEGER,INTENT(IN)  :: nb_server 
     
    6564     
    6665    DO i=1,file_enabled%size 
    67       CALL sorted_list__new(axis_id) 
    6866       
    6967      pt_file_dep=>file_enabled%at(i)%pt 
    70       pt_file=>pt_file_dep%file 
    71        
    72       pt_grid=>pt_file_dep%grids%at(1)%pt 
    73       pt_domain=>pt_grid%domain 
    74       pt_zoom=>pt_file_dep%zooms%at(1)%pt 
    75 !      print *,TRIM(pt_file%name),' ',TRIM(pt_zoom%id) 
    76 !      print*,'Global --->',pt_zoom%ni_glo,pt_zoom%nj_glo,pt_zoom%ibegin_glo,pt_zoom%jbegin_glo 
    77 !      print*,'Local  --->',pt_zoom%ni_loc,pt_zoom%nj_loc,pt_zoom%ibegin_loc,pt_zoom%jbegin_loc 
    78        
    79       IF (pt_zoom%ni_loc*pt_zoom%nj_loc > 0) THEN 
    80          
    81         full_name=TRIM(pt_file%name) 
    82         IF (pt_file%has_name_suffix) full_name=TRIM(full_name)//TRIM(pt_file%name_suffix)  
    83         IF ( (pt_zoom%ni_loc == pt_zoom%ni_glo) .AND. (pt_zoom%nj_loc == pt_zoom%nj_glo) ) THEN  
    84  
    85           CALL histbeg(TRIM(full_name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat, &  
    86                      pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,         & 
    87                      initial_timestep, initial_date, timestep_value,                               & 
    88                      ioipsl_hori_id, ioipsl_file_id, snc4chunks=snc4ioset) 
    89          ELSE                                               
    90  
    91           CALL set_ioipsl_domain_id(pt_grid,nb_server,server_rank,ioipsl_domain_id) 
    92           CALL histbeg(TRIM(full_name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat,  & 
    93                      pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,          & 
    94                      initial_timestep, initial_date, timestep_value,                                & 
    95                      ioipsl_hori_id, ioipsl_file_id,domain_id=ioipsl_domain_id, snc4chunks=snc4ioset)                                               
    96         
    97          ENDIF 
    98          
    99        
    100         DO j=1,pt_file_dep%axis%size 
    101           pt_axis=>pt_file_dep%axis%at(j)%pt 
    102           CALL sorted_list__find(axis_id,hash(Pt_axis%name),ioipsl_axis_id,found) 
    103           IF (.NOT. found) THEN 
    104             IF (TRIM(pt_axis%name) /= "none") THEN 
     68 
     69      IF (pt_file_dep%fields%size>0) THEN 
     70        CALL sorted_list__new(axis_id) 
     71 
     72        pt_file=>pt_file_dep%file 
     73       
     74        pt_grid=>pt_file_dep%grids%at(1)%pt 
     75        pt_domain=>pt_grid%domain 
     76        pt_zoom=>pt_file_dep%zooms%at(1)%pt 
     77!        print *,TRIM(pt_file%name),' ',TRIM(pt_zoom%id) 
     78!        print*,'Global --->',pt_zoom%ni_glo,pt_zoom%nj_glo,pt_zoom%ibegin_glo,pt_zoom%jbegin_glo 
     79!        print*,'Local  --->',pt_zoom%ni_loc,pt_zoom%nj_loc,pt_zoom%ibegin_loc,pt_zoom%jbegin_loc 
     80       
     81        IF (pt_zoom%ni_loc*pt_zoom%nj_loc > 0) THEN 
     82         
     83          full_name=TRIM(pt_file%name) 
     84          IF (pt_file%has_name_suffix) full_name=TRIM(full_name)//TRIM(pt_file%name_suffix)  
     85          IF ( (pt_zoom%ni_loc == pt_zoom%ni_glo) .AND. (pt_zoom%nj_loc == pt_zoom%nj_glo) ) THEN  
     86 
     87            CALL histbeg(TRIM(full_name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat, &  
     88                       pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,         & 
     89                       initial_timestep, initial_date, timestep_value,                               & 
     90                       ioipsl_hori_id, ioipsl_file_id) 
     91           ELSE                                               
     92 
     93            CALL set_ioipsl_domain_id(pt_grid,nb_server,server_rank,ioipsl_domain_id) 
     94            CALL histbeg(TRIM(full_name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat,  & 
     95                       pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,          & 
     96                       initial_timestep, initial_date, timestep_value,                                & 
     97                       ioipsl_hori_id, ioipsl_file_id,domain_id=ioipsl_domain_id)                                               
     98           
     99           ENDIF 
     100         
     101       
     102          DO j=1,pt_file_dep%axis%size 
     103            pt_axis=>pt_file_dep%axis%at(j)%pt 
     104            CALL sorted_list__find(axis_id,hash(Pt_axis%name),ioipsl_axis_id,found) 
     105            IF (.NOT. found) THEN 
     106              IF (TRIM(pt_axis%name) /= "none") THEN 
    105107               
    106               IF (pt_axis%has_positive) THEN  
    107                 IF (pt_axis%positive) THEN 
    108                   direction="up" 
     108                IF (pt_axis%has_positive) THEN  
     109                  IF (pt_axis%positive) THEN 
     110                    direction="up" 
     111                  ELSE 
     112                    direction="down" 
     113                  ENDIF 
    109114                ELSE 
    110                   direction="down" 
     115                  direction='unknown' 
    111116                ENDIF 
    112               ELSE 
    113                 direction='unknown' 
     117 
     118                CALL histvert(ioipsl_file_id, TRIM(pt_axis%name),TRIM(pt_axis%description),    & 
     119                             TRIM(pt_axis%unit), pt_axis%size,pt_axis%values, ioipsl_axis_id,  & 
     120                           pdirect=direction) 
     121                CALL sorted_list__add(axis_id,hash(Pt_axis%name),ioipsl_axis_id) 
    114122              ENDIF 
    115  
    116               CALL histvert(ioipsl_file_id, TRIM(pt_axis%name),TRIM(pt_axis%description),    & 
    117                            TRIM(pt_axis%unit), pt_axis%size,pt_axis%values, ioipsl_axis_id,  & 
    118                            pdirect=direction) 
    119               CALL sorted_list__add(axis_id,hash(Pt_axis%name),ioipsl_axis_id) 
    120123            ENDIF 
    121           ENDIF 
    122         ENDDO 
    123          
    124         DO j=1,pt_file_dep%fields%size 
    125           pt_field=>pt_file_dep%fields%at(j)%pt 
    126           IF (pt_field%axis%name=="none") THEN 
    127             pt_field%internal(id_file)=ioipsl_file_id 
    128             CALL histdef(ioipsl_file_id, TRIM(pt_field%name), pt_field%description,            & 
    129                       &  pt_field%unit, pt_field%grid%domain%ni, pt_field%grid%domain%nj,      & 
    130                       &  ioipsl_hori_id, 1, 1, 1, -99, 32, pt_field%operation,                 & 
    131                       &  real(pt_field%freq_op), real(pt_file%output_freq) ) 
    132           ELSE 
    133             pt_field%internal(id_file)=ioipsl_file_id 
    134             CALL sorted_list__find(axis_id,hash(Pt_field%axis%name),ioipsl_axis_id,found) 
    135             CALL histdef(ioipsl_file_id, TRIM(pt_field%name), pt_field%description,          & 
    136                        & pt_field%unit, pt_field%grid%domain%ni, pt_field%grid%domain%nj,    & 
    137                        & ioipsl_hori_id, pt_field%axis%size, 1, pt_field%axis%size,          & 
    138                        & ioipsl_axis_id, 32, pt_field%operation, real(pt_field%freq_op),     & 
    139                        & real(pt_file%output_freq) ) 
    140           ENDIF 
    141         ENDDO 
    142         CALL histend(ioipsl_file_id, snc4chunks=snc4ioset) 
     124         ENDDO 
     125         
     126          DO j=1,pt_file_dep%fields%size 
     127            pt_field=>pt_file_dep%fields%at(j)%pt 
     128            IF (pt_field%axis%name=="none") THEN 
     129              pt_field%internal(id_file)=ioipsl_file_id 
     130              CALL histdef(ioipsl_file_id, TRIM(pt_field%name), pt_field%description,            & 
     131                        &  pt_field%unit, pt_field%grid%domain%ni, pt_field%grid%domain%nj,      & 
     132                        &  ioipsl_hori_id, 1, 1, 1, -99, 32, pt_field%operation,                 & 
     133                        &  real(pt_field%freq_op), real(pt_file%output_freq) ) 
     134            ELSE 
     135              pt_field%internal(id_file)=ioipsl_file_id 
     136              CALL sorted_list__find(axis_id,hash(Pt_field%axis%name),ioipsl_axis_id,found) 
     137              CALL histdef(ioipsl_file_id, TRIM(pt_field%name), pt_field%description,          & 
     138                         & pt_field%unit, pt_field%grid%domain%ni, pt_field%grid%domain%nj,    & 
     139                         & ioipsl_hori_id, pt_field%axis%size, 1, pt_field%axis%size,          & 
     140                         & ioipsl_axis_id, 32, pt_field%operation, real(pt_field%freq_op),     & 
     141                         & real(pt_file%output_freq) ) 
     142            ENDIF 
     143          ENDDO 
     144          CALL histend(ioipsl_file_id) 
     145        ENDIF 
     146        CALL sorted_list__delete(axis_id) 
    143147      ENDIF 
    144       CALL sorted_list__delete(axis_id) 
    145148    ENDDO 
    146149     
Note: See TracChangeset for help on using the changeset viewer.