Ignore:
Timestamp:
2024-04-15T11:23:37+02:00 (3 months ago)
Author:
josefine.ghattas
Message:

Integrated [7912], [7925], [8179] and [8412] done on the trunk to output forcing file that can be used in offline mode. See ticket #899

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_driver/forcing_tools.f90

    r7901 r8531  
    44844484  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:) :: tmp_slab2d 
    44854485  CHARACTER(LEN=80) :: name 
     4486  CHARACTER(LEN=80) :: coordinates ! temporary variable for attribut coordinates 
    44864487  LOGICAL :: windzero 
    44874488  ! 
     
    45444545     iret = NF90_GET_ATT(force_id(fileindex), varid, 'cell_methods', cellmethod) 
    45454546     IF (iret /= NF90_NOERR) THEN 
    4546         ! If the attribute is not found then we set a reasonable default : instantaneous and centered. 
    4547         cellmethod="time: instantaneous" 
     4547        ! If the attribute is not found then we set undefined 
     4548        cellmethod="undefined" 
    45484549     ENDIF 
     4550 
     4551     ! Read also attribute coordinates that might contain information about the name of the time axis. 
     4552     ! If the forcing file is produced by XIOS, this is the case. 
     4553     ! Reading of the time axis name can fail if the attribute coordinates contains something else than the time axis name. 
     4554     iret = NF90_GET_ATT(force_id(fileindex), varid, 'coordinates', coordinates) 
     4555     IF (iret == NF90_NOERR) THEN 
     4556        ! The attribute 'coordinates' was found. This is probably containg the name of the time axis.  
     4557        ! We add this information in the begining of the celllmethod variable. 
     4558        cellmethod=TRIM(coordinates)//":"//TRIM(cellmethod) 
     4559     ENDIF 
     4560 
    45494561     ! 
    45504562     ! 
     
    46454657  ENDDO 
    46464658  ! 
    4647   ! Go through all the time axes we have to find the right one. 
     4659  ! Go through all the time axes we have to find the right one based on the information 
     4660  ! read from attribute cell_methods or coordinates 
    46484661  ! 
    46494662  timeindex=0 
     
    46824695           ENDDO 
    46834696           ! 
    4684            ! If there is no "(" then we have to find the centered axis. 
    46854697        ELSE  
     4698           ! There is no "(" so we set the centered axis by defaut 
    46864699           DO im=1,nbtmethods 
    46874700              IF ( INDEX(time_cellmethod(itbase+im), "cent") > 0 ) THEN 
     
    46914704        ENDIF 
    46924705        ! 
    4693         ! The name of the time axis was found bu no method could be identified 
     4706        ! The name of the time axis was found but no method could be identified 
    46944707        ! 
    46954708        IF ( timeindex < 1 ) THEN 
     
    47024715     ENDIF 
    47034716  ENDDO 
    4704   ! 
    4705   ! Should no corresponding time axis name be found,  
    4706   ! then we use the first centered one. 
    4707   ! 
    4708   itax=1 
    4709   DO WHILE ( timeindex < 1 )  
    4710      IF ( INDEX(time_cellmethod(itax), "cent") > 0 ) THEN 
    4711         timeindex = itax 
    4712      ELSE 
    4713         itax = itax + 1 
    4714      ENDIF 
    4715   ENDDO 
    4716   ! 
     4717 
     4718 
     4719  ! 
     4720  ! If still no corresponding time axis name has be found, then we use the first centered one. 
     4721  ! This is the case if none of the attributes cell_methods or coordinates were found or if they  
     4722  ! didn't include the name of the corresponding time axis. 
     4723  IF ( timeindex < 1 ) THEN 
     4724     CALL ipslerr(2,'forcing_attributetimeaxe',& 
     4725          'No information about the name of the time axis was found in the attributes cell_method or coordinantes', & 
     4726          'The first centered time axis will be used as defaut.', & 
     4727          'Attribute coordinates is optional but must not contain something else than the name of the time axis.') 
     4728     itax=1 
     4729     DO WHILE ( timeindex < 1 )  
     4730        IF ( INDEX(time_cellmethod(itax), "cent") > 0 ) THEN 
     4731           timeindex = itax 
     4732        ELSE 
     4733           itax = itax + 1 
     4734        ENDIF 
     4735     ENDDO 
     4736  END IF 
     4737   
    47174738END SUBROUTINE forcing_attributetimeaxe 
    47184739 
Note: See TracChangeset for help on using the changeset viewer.