[Thread Prev][Thread Next][Index]

Re: How to plot data at particular time of a file



On Tue, 18 Jan 2005, Yogesh K. Tiwari wrote:
> Can we plot saparately the 'night and early morning' (local time) and
> 'noon and afternoon'(local time) CO2 values verses other variables like
> lon,lat.
> Is it possible in ferret that any function takes care of time of the day
> and it takes out that part of data separately on the map.

Hi Yogesh,
	I'm not aware of built-in ferret functions to compute local
time-of-day but it is easy to do yourself.
	On the simplest level, if the "date/time" of your data has its
origin at Greenwich then the local time will differ by "longitude/15"
hours.
	To do a better job you would need to introduce solar declination,
altitude and the solar hour angle, as a function of latitude, longitude
and day of year.  If you do a Google search on "Equation of Time" you
will come up with several hits.  When I did this some time ago the one
that proved most useful was some fortran code which is easily translated
into ferretese.  I've appended it but the header records of the code is
!##################################################################
!##################################################################
!######                                                      ######
!######               SUBROUTINE SOLAR_POS                   ######
!######             ARPS Data Analysis System                ######
!######                                                      ######
!######                     Developed by                     ######
!######     Center for Analysis and Prediction of Storms     ######
!######                University of Oklahoma                ######
!######                                                      ######
!##################################################################
!##################################################################

Some ferret.jnl stuff I used in testing the algorithms are

let twopi=8*atan(1.)
let jd=i  ! day of year , you would substitute a definition based
          ! on the time axis of your data
let dayang1=twopi*(jd-1)/365.25
let dayang2=2*dayang1
let dayang3=3*dayang1
let timeq=0.000075+0.001868*COS(dayang1)-0.032077*SIN(dayang1) - \
          0.014615*COS(dayang2)-0.040849*SIN(dayang2)
let soldec=0.006918-0.399912*COS(dayang1)+0.070257*SIN(dayang1) - \
          0.006758*COS(dayang2)+0.000907*SIN(dayang2) - \
          0.002697*COS(dayang3)+0.001480*SIN(dayang3)

plot/i=1:365 timeq   ! the equation of time is computed in radians so
                     ! you will need to convert it into appropriate
                     ! units in adjusting local time (in hours)

plot/i=1:365 soldec  ! notice that soldec is in radians - depending on
                     ! your application you may need to convert to degrees

Hope these algorithms help,
Good luck,
Mick
!##################################################################
!##################################################################
!######                                                      ######
!######               SUBROUTINE SOLAR_POS                   ######
!######             ARPS Data Analysis System                ######
!######                                                      ######
!######                     Developed by                     ######
!######     Center for Analysis and Prediction of Storms     ######
!######                University of Oklahoma                ######
!######                                                      ######
!##################################################################
!##################################################################
!
SUBROUTINE solar_pos(rlat,rlon,i4time,alt,dec,hrangle) 4,4
!-----------------------------------------------------------------------
!  PURPOSE:
!  This subroutine calculates the solar declination,
!  solar altitude angle, and the solar hour angle according to
!  the time and the latitude and longitude.
!-----------------------------------------------------------------------
!  AUTHOR:  (Jian Zhang)
!          Based on the LAPS cloud analysis code by Steve Albers,
!          January,  1994.
!  MODIFICATION HISTORY:
!  04/22/96  J. Zhang
!            Modified for ADAS analysis.
!-----------------------------------------------------------------------
!
! Argument      I/O     Type                    Description
! --------      ---     ----    ----------------------------------------
! RLAT           I      R*4     Latitude (degrees)
! RLNG           I      R*4     Longitude (degrees)
! I4TIME         I       I      Time in absolute seconds from 00:00 UTC
!                            1/1/1960
!
!-----------------------------------------------------------------------
!
!  Variable Declarations:
!
!-----------------------------------------------------------------------
!
  IMPLICIT NONE
!
!  INPUT:
!
  REAL :: rlat,rlon            ! lat and lon of the data point.
  INTEGER :: i4time            ! the data time in seconds from 1/1/1977
!
!  OUTPUT:
!
  REAL :: alt      ! solar altitude angle for the data pt. at the time
  REAL :: dec      ! solar declination for the data pt. at the time
  REAL :: hrangle  ! hour angle for the data pt. at the time
!
!  LOCAL:
!
  INTEGER :: iyr,imon,idy,ihr,imin,isec,jd
  REAL :: pi,rpd
  PARAMETER (pi=3.1415926, rpd=pi/180.)
  REAL :: eqt,timeq,soldec,coszen
!
!
!@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
!
!  Beginning of executable code
!
!@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
!
!-----------------------------------------------------------------------
!
      CALL abss2ctim[Image](i4time, iyr, imon, idy, ihr, imin, isec )
      CALL julday[Image](iyr,imon,idy,jd)
!Equation of Time (Degrees) & Solar declination
      eqt = timeq(jd)/rpd 
      dec = soldec(jd)/rpd
      hrangle = (ihr-12)*15. + imin/4. + isec/240. + rlon + eqt

      coszen = SIN(rlat*rpd)*SIN(dec*rpd)
     1            + COS(rlat*rpd)*COS(dec*rpd)*COS(hrangle*rpd)
      alt = 90. - ACOS(coszen)/rpd

      IF(hrangle .lt. -180.) hrangle = hrangle + 360.
      IF(hrangle .gt. +180.) hrangle = hrangle - 360.

!      write(6,*)'jd,ihr,imin',jd,ihr,imin
!      write(6,*)'hrangle,dec,alt',hrangle,dec,alt

      RETURN
      END

!-----------------------------------------------------------------------
! The following functions are used to calculate geometric solar
! parameters. These formulas are from Paltridge and Platt, 1976.
! They reference Spencer, 1971 for the solar declination and
! equation of time.
!  AUTHOR: J. Wakefield
!  01/28/1982, Original version
!  MODIFICATION HISTORY
!  04/22/1996 C Jian Zhang
!  Modified for ARPSDAS, added documents.
!
      FUNCTION radnorm(jd)
!
!-----------------------------------------------------------------------
! Purpose:
!  Calculate normalized earth-sun distance factor (R0/R)**2,
!  where JD is input Julian day number
!-----------------------------------------------------------------------

      dayang1=2.*3.14159265*(jd-1)/365.
      dayang2=2.*dayang1

      radnorm= 1.000110
     1          +0.034221*COS(dayang1)+0.001280*SIN(dayang1)
     1          +0.000719*COS(dayang2)+0.000077*SIN(dayang2)

      RETURN
      END
!
      FUNCTION soldec(jd)
!
!-----------------------------------------------------------------------
! Purpose:
!  Calculate solar declination angle (radians), JD is input
!  Julian day number
!-----------------------------------------------------------------------
!
      dayang1=2.*3.14159265*(jd-1)/365.
      dayang2=2.*dayang1
      dayang3=3.*dayang1

      soldec=  0.006918
     1        -0.399912*COS(dayang1)+0.070257*SIN(dayang1)
     1        -0.006758*COS(dayang2)+0.000907*SIN(dayang2)
     1      -0.002697*COS(dayang3)+0.001480*SIN(dayang3)

      RETURN
      END
!
      FUNCTION timeq(jd)
!
!-----------------------------------------------------------------------
! Purpose:
!  Equation of time (radians), JD is input Julian day number
!-----------------------------------------------------------------------
!
      dayang1=2.*3.14159265*(jd-1)/365.
      dayang2=2.*dayang1

      timeq=   0.000075
     1        +0.001868*COS(dayang1)-0.032077*SIN(dayang1)
     1        -0.014615*COS(dayang2)-0.040849*SIN(dayang2)

      RETURN
      END

[Thread Prev][Thread Next][Index]

Dept of Commerce / NOAA / OAR / PMEL / TMAP

Contact Us | Privacy Policy | Disclaimer | Accessibility Statement