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 2765 for vendors/XMLIO_SERVER/current/src/IOSERVER/mod_interface_ioipsl.f90 – NEMO

Ignore:
Timestamp:
2011-05-13T16:45:07+02:00 (13 years ago)
Author:
smasson
Message:

Load working_directory into vendors/XMLIO_SERVER/current.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • vendors/XMLIO_SERVER/current/src/IOSERVER/mod_interface_ioipsl.f90

    r1897 r2765  
    6464     
    6565    DO i=1,file_enabled%size 
    66       CALL sorted_list__new(axis_id) 
    6766       
    6867      pt_file_dep=>file_enabled%at(i)%pt 
    69       pt_file=>pt_file_dep%file 
    70        
    71       pt_grid=>pt_file_dep%grids%at(1)%pt 
    72       pt_domain=>pt_grid%domain 
    73       pt_zoom=>pt_file_dep%zooms%at(1)%pt 
    74 !      print *,TRIM(pt_file%name),' ',TRIM(pt_zoom%id) 
    75 !      print*,'Global --->',pt_zoom%ni_glo,pt_zoom%nj_glo,pt_zoom%ibegin_glo,pt_zoom%jbegin_glo 
    76 !      print*,'Local  --->',pt_zoom%ni_loc,pt_zoom%nj_loc,pt_zoom%ibegin_loc,pt_zoom%jbegin_loc 
    77        
    78       IF (pt_zoom%ni_loc*pt_zoom%nj_loc > 0) THEN 
    79          
    80         full_name=TRIM(pt_file%name) 
    81         IF (pt_file%has_name_suffix) full_name=TRIM(full_name)//TRIM(pt_file%name_suffix)  
    82         IF ( (pt_zoom%ni_loc == pt_zoom%ni_glo) .AND. (pt_zoom%nj_loc == pt_zoom%nj_glo) ) THEN  
    83  
    84           CALL histbeg(TRIM(full_name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat, &  
    85                      pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,         & 
    86                      initial_timestep, initial_date, timestep_value,                               & 
    87                      ioipsl_hori_id, ioipsl_file_id) 
    88          ELSE                                               
    89  
    90           CALL set_ioipsl_domain_id(pt_grid,nb_server,server_rank,ioipsl_domain_id) 
    91           CALL histbeg(TRIM(full_name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat,  & 
    92                      pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,          & 
    93                      initial_timestep, initial_date, timestep_value,                                & 
    94                      ioipsl_hori_id, ioipsl_file_id,domain_id=ioipsl_domain_id)                                               
    95         
    96          ENDIF 
    97          
    98        
    99         DO j=1,pt_file_dep%axis%size 
    100           pt_axis=>pt_file_dep%axis%at(j)%pt 
    101           CALL sorted_list__find(axis_id,hash(Pt_axis%name),ioipsl_axis_id,found) 
    102           IF (.NOT. found) THEN 
    103             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 
    104107               
    105               IF (pt_axis%has_positive) THEN  
    106                 IF (pt_axis%positive) THEN 
    107                   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 
    108114                ELSE 
    109                   direction="down" 
     115                  direction='unknown' 
    110116                ENDIF 
    111               ELSE 
    112                 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) 
    113122              ENDIF 
    114  
    115               CALL histvert(ioipsl_file_id, TRIM(pt_axis%name),TRIM(pt_axis%description),    & 
    116                            TRIM(pt_axis%unit), pt_axis%size,pt_axis%values, ioipsl_axis_id,  & 
    117                            pdirect=direction) 
    118               CALL sorted_list__add(axis_id,hash(Pt_axis%name),ioipsl_axis_id) 
    119123            ENDIF 
    120           ENDIF 
    121         ENDDO 
    122          
    123         DO j=1,pt_file_dep%fields%size 
    124           pt_field=>pt_file_dep%fields%at(j)%pt 
    125           IF (pt_field%axis%name=="none") THEN 
    126             pt_field%internal(id_file)=ioipsl_file_id 
    127             CALL histdef(ioipsl_file_id, TRIM(pt_field%name), pt_field%description,            & 
    128                       &  pt_field%unit, pt_field%grid%domain%ni, pt_field%grid%domain%nj,      & 
    129                       &  ioipsl_hori_id, 1, 1, 1, -99, 32, pt_field%operation,                 & 
    130                       &  real(pt_field%freq_op), real(pt_file%output_freq) ) 
    131           ELSE 
    132             pt_field%internal(id_file)=ioipsl_file_id 
    133             CALL sorted_list__find(axis_id,hash(Pt_field%axis%name),ioipsl_axis_id,found) 
    134             CALL histdef(ioipsl_file_id, TRIM(pt_field%name), pt_field%description,          & 
    135                        & pt_field%unit, pt_field%grid%domain%ni, pt_field%grid%domain%nj,    & 
    136                        & ioipsl_hori_id, pt_field%axis%size, 1, pt_field%axis%size,          & 
    137                        & ioipsl_axis_id, 32, pt_field%operation, real(pt_field%freq_op),     & 
    138                        & real(pt_file%output_freq) ) 
    139           ENDIF 
    140         ENDDO 
    141         CALL histend(ioipsl_file_id) 
     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) 
    142147      ENDIF 
    143       CALL sorted_list__delete(axis_id) 
    144148    ENDDO 
    145149     
Note: See TracChangeset for help on using the changeset viewer.