!---------------------------------------------------------------------------------------
! PREP_FLUXES: adjust_time
!---------------------------------------------------------------------------------------
!  FLEXINVERT is free software: you can redistribute it and/or modify
!  it under the terms of the GNU General Public License as published by
!  the Free Software Foundation, either version 3 of the License, or
!  (at your option) any later version.
!
!  FLEXINVERT is distributed in the hope that it will be useful,
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
!  GNU General Public License for more details.
!
!  You should have received a copy of the GNU General Public License
!  along with FLEXINVERT.  If not, see <http://www.gnu.org/licenses/>.
!
!  Copyright 2017, Rona Thompson
!---------------------------------------------------------------------------------------
!
!> adjust_time
!!
!! Purpose:    Calculates the time dimension of the output in julian days and
!!             adjusts the time for the selected year.
!!
!! Interface:
!!
!!    Inputs
!!             settings  -  settings data structure
!!             time      -  time dimension of input
!!             timeout   -  time dimension of output (zero on input)
!!
!!    Externals
!!             caldate
!!
!---------------------------------------------------------------------------------------

subroutine adjust_time(settings, time, time_out)

  use mod_settings
  use mod_dates
  use mod_var
  
  implicit none

  type (settings_t),          intent(in)     :: settings
  real, dimension(ntime),     intent(in out) :: time
  real, dimension(ntime_out), intent(in out) :: time_out

  integer  :: i, yyyymmdd, hhmiss
  real     :: days

  if (settings%timeref.ne.0) then
    ! input timestamp is julian days
    do i = 1, ntime_out
      time_out(i) = time(i) + juldate(int(settings%timeref),0) - &
                     juldate(19000101,0) 
    end do
    ! adjust time stamp to given year 
    call caldate(time_out(1) + juldate(19000101,0), yyyymmdd, hhmiss)
    if( yyyymmdd/10000 .ne. settings%year ) then
      time_out(:) = time_out(:) + juldate(settings%year*10000+101,0) - &
                     juldate(yyyymmdd,0)
    endif
  else if (trim(settings%timestamp).eq.'sec') then
    ! input timestamp is seconds
    days = 0.
    do i = 1, ntime_out
      time_out(i) = time(i)/3600./24. + juldate(settings%year*10000+101,0) - &
                     juldate(19000101,0)
    end do
  else if (trim(settings%timestamp).eq.'hour') then
    ! input timestamp is hours -> fossil fuel leave as hours
    do i = 1, ntime_out
      time_out(i) = time(i)
    end do
  else if (trim(settings%timestamp).eq.'month') then
    ! input timestamp is months
    days = 0.
    do i = 1, ntime_out
      if(i.gt.1) days = days + calceomday(int(settings%year*100+(i-1)))
      time_out(i) = days + juldate(settings%year*10000+101,0) - &
                     juldate(19000101,0)
    end do
  else
    write(*,*) 'WARNING: input timestamp not recognised'
  endif

end subroutine adjust_time