[haskell-gnuplot] CandleSticks

Sean McEligot seanmce33 at gmail.com
Mon Apr 12 14:24:15 EDT 2010


I had to make a change. I wanted to put a Moving Average line plot
(date,x) on the same chart as the candle (date, o,c,h,l). Here's the
patch. I'm just hacking this up for my immediate need. It's not a
proposal for a commit. It does get rid of the need for prepXTime which
I like. It's not backward compatible.

diff -rN old-gnuplot_0/src/Graphics/Gnuplot/Plot/TwoDimensional.hs
new-gnuplot_0/src/Graphics/Gnuplot/Plot/TwoDimensional.hs
9d8
<
12d10
<
14a13,28
> import Data.Time.Calendar (Day)
> import Data.Time.Format (formatTime, )
> import System.Locale (defaultTimeLocale, )
> import Data.Time.Clock
>
> data Rec = IntRec Int| FloatRec Float| DayRec Day
>
> instance Show (Rec ) where
>  show (IntRec i) = show i
>  show (FloatRec f) = show f
>  show (DayRec d) = formatTime defaultTimeLocale "%s" (UTCTime d 0)
> data Record =
>      Dim1 Rec
>    | Dim2 Rec Rec
>    | Dim5 Rec Rec Rec Rec Rec
>     deriving Show
56a71,88
> pathRecord :: [Record] -> T
> pathRecord dat =
>      case head dat of
>       Dim1 _ ->
>         error("Dim1 not yet supported")
>       Dim2 _ _ ->
>         Plot.withUniqueFile
>         (unlines (map (\(Dim2 x y) -> (show x) ++ ", " ++ (show y)) dat))
>         ([Graph.deflt (Graph.Dim2 1 2)])
>       Dim5 _ _ _ _ _ ->
>         Plot.withUniqueFile
>         (unlines (map (\(Dim5 a b c d e) ->
>                 show a ++ ", " ++
>                 show b ++ ", " ++
>                 show c ++ ", " ++
>                 show d ++ ", " ++
>                 show e ) dat))
>         ([Graph.deflt (Graph.Dim5 1 2 3 4 5)])
73a106
>
diff -rN old-gnuplot_0/src/Graphics/Gnuplot/Private/Graph2D.hs
new-gnuplot_0/src/Graphics/Gnuplot/Private/Graph2D.hs
19a20,21
>    | Dim5 {columnA,columnB,columnC,columnD,columnE:: Int}
>     deriving Show
26,27c28,29
< columnToString c =
<    case c of
---
> columnToString col =
>    case col of
29a32
>       Dim5 a b c d e  -> show a ++ ":" ++ show b ++ ":" ++ show c ++ ":" ++ show d ++ ":" ++ show e
diff -rN old-gnuplot_0/src/Graphics/Gnuplot/Simple.hs
new-gnuplot_0/src/Graphics/Gnuplot/Simple.hs
35a36,37
>     plotPathStyleRecord,
>     plotPathsStyleRecord,
216a219,226
> plotPathStyleRecord :: [Attribute] -> PlotStyle -> [Plot2D.Record] -> IO ()
> plotPathStyleRecord attrs style =
>    plot2d attrs . setPlotStyle style . Plot2D.pathRecord
>
> plotPathsStyleRecord :: [Attribute] -> [(PlotStyle, [Plot2D.Record])] -> IO ()
> plotPathsStyleRecord attrs =
>    plot2d attrs . mconcat .
>    map (\(style,xs) -> setPlotStyle style $ Plot2D.pathRecord xs)



More information about the Gnuplot mailing list