[haskell-gnuplot] CandleSticks

Sean McEligot seanmce33 at gmail.com
Fri Apr 9 23:20:01 EDT 2010


I'm not sure about the names I used, but here's a working patch and a demo

diff -rN old-gnuplot_0/src/Graphics/Gnuplot/Plot/TwoDimensional.hs
new-gnuplot_0/src/Graphics/Gnuplot/Plot/TwoDimensional.hs
56a57,67
> path5 :: Show a => [(a,a,a,a,a)] -> T
> path5 dat =
>    Plot.withUniqueFile
>       (unlines (map (\(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)])
>
diff -rN old-gnuplot_0/src/Graphics/Gnuplot/Private/Graph2D.hs
new-gnuplot_0/src/Graphics/Gnuplot/Private/Graph2D.hs
19a20
>    | Dim5 {columnA,columnB,columnC,columnD,columnE  :: Int}
26,27c27,28
< columnToString c =
<    case c of
---
> columnToString col =
>    case col of
29a31
>       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
34a35
>     plotPathStyle5,
35a37
>     plotPathsStyle5,
211a214,217
> plotPathStyle5 :: Show a => [Attribute] -> PlotStyle -> [(a,a,a,a,a)] -> IO ()
> plotPathStyle5 attrs style =
>    plot2d attrs . setPlotStyle style . Plot2D.path5
>
216a223,226
> plotPathsStyle5 :: Show a => [Attribute] -> [(PlotStyle, [(a,a,a,a,a)])] -> IO ()
> plotPathsStyle5 attrs =
>    plot2d attrs . mconcat .
>    map (\(style,xs) -> setPlotStyle style $ Plot2D.path5 xs)
diff -rN old-gnuplot_0/src/Graphics/Gnuplot/Time.hs
new-gnuplot_0/src/Graphics/Gnuplot/Time.hs
22a23,26
>
> prepXTime5 :: (FormatTime a, Read b) => [(a,b,b,b,b)] -> [(b, b,b,b,b)]
> prepXTime5 = map (\(a,b,c,d,e) -> (read$formatTime defaultTimeLocale "%s" a, b,c,d,e))
>

-- candledemo.hs
module Main where
import Finance.Quote.Yahoo
import Data.Maybe
import Graphics.Gnuplot.Simple
import Graphics.Gnuplot.Time
import Data.List
import Data.Time

sym :: QuoteSymbol
sym = "SPY" :: QuoteSymbol

start :: Day
start = fromGregorian 2010 4 8 :: Day

end :: Day
end = fromGregorian 2010 1 8 :: Day

dayToUtc:: (Day,a,b,c,d) -> (UTCTime,a,b,c,d)
dayToUtc (a,b,c,d,e) = (UTCTime a 0, b,c,d,e)

dateopen :: HistoricalQuote -> (Day, QuoteCurrency, QuoteCurrency,
QuoteCurrency, QuoteCurrency)
dateopen h = (date h, open h, close h, high h, low h)

main :: IO ()
main = do
 h <- getHistoricalQuote sym end start Daily
 case h of
    Nothing -> error "getHistoricalQuote failed"
    Just l -> do
       graph$ prepXTime5 $map (dayToUtc . dateopen) l
 return ()

graph :: (Show a) => [(a, a, a,a,a)] -> IO ()
graph prices = plotPathStyle5 [XTime, XFormat "%m-%d", Title "CandleSticks"]
            (PlotStyle CandleSticks (CustomStyle [])) prices



On Fri, Apr 9, 2010 at 2:52 PM, Henning Thielemann
<haskell at henning-thielemann.de> wrote:
>
> On Fri, 9 Apr 2010, Sean McEligot wrote:
>
>> I don't see candlesticks in Demo.hs or anything that takes more than
>> two (x,y) plot points.
>>
>> Here's an example of what I'm trying to do.
>>
>> http://www.gnuplot.info/demo_canvas/candlesticks.html
>
> I see, candlesticks are quite different from other plot types. The quick
> hack would be to add a Dim5 constructor to Graphics.Gnuplot.Private.Graph2D.
> But a clean version had to assert that candlesticks can only be used with
> Dim5 and other plot types can only use Dim1 and Dim2.
>



More information about the Gnuplot mailing list