Ignore:
Timestamp:
Jun 11, 2014, 3:46:46 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r1997:2055 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/bibio/wxios.F90

    r1910 r2056  
    2626   
    2727    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    28     !   str + i   =>   str_i   !!!!!!!!!!!!!!!!!!!!
    29     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    30    
    31     SUBROUTINE concat(str, str2, str_str2)
    32         CHARACTER(len=*), INTENT(IN) :: str, str2
    33         CHARACTER(len=20), INTENT(OUT) :: str_str2
    34        
    35        
    36         str_str2 = TRIM(ADJUSTL(str//"_"//TRIM(ADJUSTL(str2))))
    37         !IF (prt_level >= 10) WRITE(lunout,*) "Xios. ",str,"+",str2,"=",str_str2
    38     END SUBROUTINE concat
    39    
    40     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    4128    !   36day => 36d etc     !!!!!!!!!!!!!!!!!!!!
    4229    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    10996    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    11097
    111     SUBROUTINE wxios_init(xios_ctx_name, locom, outcom)
     98    SUBROUTINE wxios_init(xios_ctx_name, locom, outcom, type_ocean)
    11299        IMPLICIT NONE
    113100        INCLUDE 'iniprint.h'
     
    116103      INTEGER, INTENT(IN), OPTIONAL :: locom
    117104      INTEGER, INTENT(OUT), OPTIONAL :: outcom
     105      CHARACTER(len=6), INTENT(IN), OPTIONAL :: type_ocean
    118106
    119107   
     
    142130        g_ctx_name = xios_ctx_name
    143131       
    144         CALL wxios_context_init()
    145        
     132        ! Si couple alors init fait dans cpl_init
     133        IF (.not. PRESENT(type_ocean)) THEN
     134            CALL wxios_context_init()
     135        ENDIF
     136
    146137    END SUBROUTINE wxios_init
    147138
     
    158149        g_ctx = xios_ctx
    159150
    160         IF (prt_level >= 10) WRITE(lunout,*) "wxios_context_init: Current context is ",trim(g_ctx_name)
    161 
     151        IF (prt_level >= 10) THEN
     152          WRITE(lunout,*) "wxios_context_init: Current context is ",trim(g_ctx_name)
     153          WRITE(lunout,*) "     now call xios_solve_inheritance()"
     154        ENDIF
    162155        !Une première analyse des héritages:
    163156        CALL xios_solve_inheritance()
     
    303296    ! Pour déclarer un axe vertical !!!!!!!!!!!!!!!
    304297    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    305     SUBROUTINE wxios_add_vaxis(axisgroup_id, axis_file, axis_size, axis_value)
    306         IMPLICIT NONE
    307         INCLUDE 'iniprint.h'
    308 
    309         CHARACTER (len=*), INTENT(IN) :: axisgroup_id, axis_file
     298    SUBROUTINE wxios_add_vaxis(axis_id, axis_size, axis_value)
     299        IMPLICIT NONE
     300        INCLUDE 'iniprint.h'
     301
     302        CHARACTER (len=*), INTENT(IN) :: axis_id
    310303        INTEGER, INTENT(IN) :: axis_size
    311304        REAL, DIMENSION(axis_size), INTENT(IN) :: axis_value
    312305       
    313         TYPE(xios_axisgroup) :: axgroup
    314         TYPE(xios_axis) :: ax
    315         CHARACTER(len=20) :: axis_id
    316        
    317        
    318         !Préparation du nom de l'axe:
    319         CALL concat(axisgroup_id, axis_file, axis_id)
     306!        TYPE(xios_axisgroup) :: axgroup
     307!        TYPE(xios_axis) :: ax
     308!        CHARACTER(len=50) :: axis_id
     309       
     310!        IF (len_trim(axisgroup_id).gt.len(axis_id)) THEN
     311!          WRITE(lunout,*) "wxios_add_vaxis: error, size of axis_id too small!!"
     312!          WRITE(lunout,*) "     increase it to at least ",len_trim(axisgroup_id)
     313!          CALL abort_gcm("wxios_add_vaxis","len(axis_id) too small",1)
     314!        ENDIF
     315!        axis_id=trim(axisgroup_id)
    320316       
    321317        !On récupère le groupe d'axes qui va bien:
    322         CALL xios_get_axisgroup_handle(axisgroup_id, axgroup)
     318        !CALL xios_get_axisgroup_handle(axisgroup_id, axgroup)
    323319       
    324320        !On ajoute l'axe correspondant à ce fichier:
    325         CALL xios_add_axis(axgroup, ax, TRIM(ADJUSTL(axis_id)))
     321        !CALL xios_add_axis(axgroup, ax, TRIM(ADJUSTL(axis_id)))
    326322       
    327323        !Et on le parametrise:
    328         CALL xios_set_axis_attr_hdl(ax, size=axis_size, value=axis_value)
     324        !CALL xios_set_axis_attr_hdl(ax, size=axis_size, value=axis_value)
     325       
     326        ! Ehouarn: New way to declare axis, without axis_group:
     327        CALL xios_set_axis_attr(trim(axis_id),size=axis_size,value=axis_value)
    329328       
    330329        !Vérification:
     
    332331            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_vaxis: Axis created: ", TRIM(ADJUSTL(axis_id))
    333332        ELSE
    334             WRITE(*,*) "wxios_add_vaxis: Invalid axis: ", TRIM(ADJUSTL(axis_id))
     333            WRITE(lunout,*) "wxios_add_vaxis: Invalid axis: ", TRIM(ADJUSTL(axis_id))
    335334        END IF
    336335
     
    367366       
    368367            IF (xios_is_valid_file("X"//fname)) THEN
    369                 IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_file: New file: ", "X"//fname
    370                 IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     368                IF (prt_level >= 10) THEN
     369                  WRITE(lunout,*) "wxios_add_file: New file: ", "X"//fname
     370                  WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     371                ENDIF
    371372            ELSE
    372                 WRITE(*,*) "wxios_add_file: Error, invalid file: ", "X"//trim(fname)
    373                 WRITE(*,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     373                WRITE(lunout,*) "wxios_add_file: Error, invalid file: ", "X"//trim(fname)
     374                WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
    374375            END IF
    375376        ELSE
    376             IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_file: File ",trim(fname), " défined using XML."
    377                 CALL xios_set_file_attr(fname, enabled=.TRUE.)
     377            IF (prt_level >= 10) THEN
     378              WRITE(lunout,*) "wxios_add_file: File ",trim(fname), " défined using XML."
     379            ENDIF
     380            ! Ehouarn: add an enable=.true. on top of xml definitions... why???
     381            CALL xios_set_file_attr(fname, enabled=.TRUE.)
    378382        END IF
    379383    END SUBROUTINE wxios_add_file
     
    432436        CHARACTER(len=*), INTENT(IN) :: op
    433437       
    434         CHARACTER(len=20) :: axis_id
     438        CHARACTER(len=20) :: axis_id ! Ehouarn: dangerous...
    435439        CHARACTER(len=100) :: operation
    436440        TYPE(xios_file) :: f
     
    441445       
    442446       
    443         !Préparation du nom de l'axe:
    444         CALL concat("presnivs", fname, axis_id)
     447        ! Ajout Abd pour NMC:
     448        IF (fid.LE.6) THEN
     449          axis_id="presnivs"
     450        ELSE
     451          axis_id="plev"
     452        ENDIF
    445453       
    446454        !on prépare le nom de l'opération:
     
    448456       
    449457       
    450        
    451458        !On selectionne le bon groupe de champs:
    452459        IF (fdim.EQ.2) THEN
    453             CALL xios_get_fieldgroup_handle("fields_2D", fieldgroup)
     460          CALL xios_get_fieldgroup_handle("fields_2D", fieldgroup)
    454461        ELSE
    455462          CALL xios_get_fieldgroup_handle("fields_3D", fieldgroup)
     
    515522            !Sinon on se contente de l'activer:
    516523            CALL xios_set_field_attr(fieldname, enabled=.TRUE.)
     524            !NB: This will override an enable=.false. set by a user in the xml file;
     525            !   then the only way to not output the field is by changing its
     526            !   output level
    517527        ENDIF       
    518528       
    519529    END SUBROUTINE wxios_add_field_to_file
    520530   
    521     SUBROUTINE wxios_update_calendar(ito)
    522         INTEGER, INTENT(IN) :: ito
    523         CALL xios_update_calendar(ito)
    524     END SUBROUTINE wxios_update_calendar
    525    
    526     SUBROUTINE wxios_write_2D(fieldname, fdata)
    527         CHARACTER(len=*), INTENT(IN) :: fieldname
    528         REAL, DIMENSION(:,:), INTENT(IN) :: fdata
    529 
    530         CALL xios_send_field(fieldname, fdata)
    531     END SUBROUTINE wxios_write_2D
    532    
    533     SUBROUTINE wxios_write_3D(fieldname, fdata)
    534         CHARACTER(len=*), INTENT(IN) :: fieldname
    535         REAL, DIMENSION(:,:,:), INTENT(IN) :: fdata
    536        
    537         CALL xios_send_field(fieldname, fdata)
    538     END SUBROUTINE wxios_write_3D
     531!    SUBROUTINE wxios_update_calendar(ito)
     532!        INTEGER, INTENT(IN) :: ito
     533!        CALL xios_update_calendar(ito)
     534!    END SUBROUTINE wxios_update_calendar
     535!   
     536!    SUBROUTINE wxios_write_2D(fieldname, fdata)
     537!        CHARACTER(len=*), INTENT(IN) :: fieldname
     538!        REAL, DIMENSION(:,:), INTENT(IN) :: fdata
     539!
     540!        CALL xios_send_field(fieldname, fdata)
     541!    END SUBROUTINE wxios_write_2D
     542   
     543!    SUBROUTINE wxios_write_3D(fieldname, fdata)
     544!        CHARACTER(len=*), INTENT(IN) :: fieldname
     545!        REAL, DIMENSION(:,:,:), INTENT(IN) :: fdata
     546!       
     547!        CALL xios_send_field(fieldname, fdata)
     548!    END SUBROUTINE wxios_write_3D
    539549   
    540550    SUBROUTINE wxios_closedef()
Note: See TracChangeset for help on using the changeset viewer.