module TextPlot
(
Function
, Range
, Plot ()
, EditPlot(..), (.+), (.-), (.|)
, XYPlot(..), emptyXYPlot
, ParamXYPlot(..), ParamFunction(..), emptyParamXYPlot
, PolarPlot(..), PolarFunction(..), emptyPolarPlot
, PlotConfig(..), defaultConfig
, plot
, plotWithConfig
, printPlot
) where
import Control.Monad (forM_, when)
import Control.Monad.ST (ST)
import Data.Array
import Data.Array.ST
import Text.Printf (printf)
type TextPlot = [[Char]]
type Range = (Double, Double)
defaultXrange :: Range
defaultXrange = (0.0, 1.0)
defaultYrange :: Range
defaultYrange = (0.0, 1.0)
type Function = Double -> Double
instance Show Function where show = const "<function::Double->Double>"
class Plot plot => EditPlot plot function | plot -> function where
thenPlot :: plot -> function -> plot
xlim :: plot -> Range -> plot
ylim :: plot -> Range -> plot
(.+) :: EditPlot p f => p -> f -> p
(.+) = thenPlot
(.-) :: EditPlot p f => p -> Range -> p
(.-) = xlim
(.|) :: EditPlot p f => p -> Range -> p
(.|) = ylim
class Plot plot => Dimensions plot where
getXlim :: plot -> Range
getYlim :: plot -> Range
data XYPlot = XYPlot {
fp'xlim :: Range
, fp'ylim :: Range
, fp'functions :: [Function]
} deriving Show
emptyXYPlot :: XYPlot
emptyXYPlot = XYPlot defaultXrange defaultYrange []
instance EditPlot XYPlot Function where
thenPlot plot f = let fs = fp'functions plot
in plot { fp'functions = f:fs }
xlim plot r = plot { fp'xlim = r }
ylim plot r = plot { fp'ylim = r }
instance Dimensions XYPlot where
getXlim = fp'xlim
getYlim = fp'ylim
data ParamFunction = ParamFunction {
xfun :: Function
, yfun :: Function
, tlim :: Range
} deriving Show
data ParamXYPlot = ParamXYPlot {
param'xlim :: Range
, param'ylim :: Range
, param'functions :: [ParamFunction]
} deriving Show
emptyParamXYPlot :: ParamXYPlot
emptyParamXYPlot = ParamXYPlot defaultXrange defaultYrange []
instance EditPlot ParamXYPlot ParamFunction where
thenPlot plot f = let fs = param'functions plot
in plot { param'functions = f:fs }
xlim plot r = plot { param'xlim = r }
ylim plot r = plot { param'ylim = r }
instance Dimensions ParamXYPlot where
getXlim = param'xlim
getYlim = param'ylim
data PolarFunction = PolarFunction {
rfun :: Function
, philim :: (Double,Double)
} deriving Show
data PolarPlot = PolarPlot {
polar'xlim :: Range
, polar'ylim :: Range
, polar'functions :: [PolarFunction]
} deriving Show
emptyPolarPlot :: PolarPlot
emptyPolarPlot = PolarPlot defaultXrange defaultYrange []
instance EditPlot PolarPlot PolarFunction where
thenPlot plot f = let fs = polar'functions plot
in plot { polar'functions = f:fs }
xlim plot r = plot { polar'xlim = r }
ylim plot r = plot { polar'ylim = r }
instance Dimensions PolarPlot where
getXlim = polar'xlim
getYlim = polar'ylim
class Plot a where
draw :: PlotConfig -> a -> TextPlot
data PlotConfig = PlotConfig {
c'width :: Int
, c'height :: Int
, c'samples :: Int
, c'showAxes :: Bool
} deriving (Show, Eq)
defaultConfig :: PlotConfig
defaultConfig = PlotConfig 61 20 256 True
instance Plot XYPlot where
draw (PlotConfig width height _ showAxes) plt =
addAxes showAxes plt . fromArray $ runSTArray $ do
arr <- createArray width height
let xrange@(xmin,xmax) = fp'xlim plt
let yrange = fp'ylim plt
let dx = (xmaxxmin)/(fromIntegral width 1)
let xs = [ xmin + (fromIntegral c)*dx | c <- [0..width1] ]
forM_ (reverse (zip (fp'functions plt) symbols)) $
\(f, sym) -> markPoints xrange yrange arr sym xs (map f xs)
return arr
instance Plot ParamXYPlot where
draw (PlotConfig width height samples showAxes) plt =
addAxes showAxes plt . fromArray $ runSTArray $ do
arr <- createArray width height
let xrange = param'xlim plt
let yrange = param'ylim plt
let fns = param'functions plt
forM_ (reverse (zip fns symbols)) $
\(f, sym) -> do
let (tmin,tmax) = tlim f
let dt = (tmaxtmin)/(fromIntegral samples 1)
let ts = [ (fromIntegral t)*dt | t <- [0..samples1] ]
let xs = map (xfun f) ts
let ys = map (yfun f) ts
markPoints xrange yrange arr sym xs ys
return arr
instance Plot PolarPlot where
draw (PlotConfig width height samples showAxes) plt =
addAxes showAxes plt . fromArray $ runSTArray $ do
arr <- createArray width height
let xrange = polar'xlim plt
let yrange = polar'ylim plt
let fns = polar'functions plt
forM_ (reverse (zip fns symbols)) $
\(f, sym) -> do
let (phimin, phimax) = philim f
let dphi = (phimaxphimin)/(fromIntegral samples 1)
let phis = [ (fromIntegral t)*dphi | t <- [0..samples1] ]
let rs = map (rfun f) phis
let toCartesian (r,phi) = (r*cos phi, r*sin phi)
let (xs,ys) = unzip . map toCartesian $ zip rs phis
markPoints xrange yrange arr sym xs ys
return arr
plot :: Plot p => p -> String
plot = plotWithConfig defaultConfig
plotWithConfig :: Plot p => PlotConfig -> p -> String
plotWithConfig config = unlines . draw config
printPlot :: Plot p => p -> IO()
printPlot = putStr . plot
symbols :: String
symbols = cycle "ox+#*@-"
createArray :: Int -> Int -> ST s (STArray s (Int,Int) Char)
createArray width height = do
let screenDims = ((0,0),(height1,width1))
newArray screenDims ' ' :: ST s (STArray s (Int,Int) Char)
markPoints :: Range
-> Range
-> STArray s (Int,Int) Char
-> Char
-> [Double]
-> [Double]
-> ST s (STArray s (Int,Int) Char)
markPoints (xmin,xmax) (ymin,ymax) arr sym xs ys = do
((rmin,cmin),(rmax,cmax)) <- getBounds arr
let width = cmaxcmin+1
let height = rmaxrmin+1
let w = fromIntegral width
let h = fromIntegral height
let dx = (xmaxxmin)/(w1)
let dy = (ymaxymin)/(h1)
let cols = [ round$(xxmin)/dx | x <- xs ]
let rows = [ round$(h1(yymin)/dy) | y <- ys ]
forM_ (zip cols rows) $ \(c, r) ->
when (r >= rmin && r <= rmax && c >= cmin && c < cmax) $
writeArray arr (r,c) sym
return arr
fromArray :: Array (Int,Int) a -> [[a]]
fromArray arr = splitEvery width (elems arr)
where
splitEvery :: Int -> [a] -> [[a]]
splitEvery _ [] = []
splitEvery n xs = (take n xs) : splitEvery n (drop n xs)
width :: Int
width = let ((_,colmin),(_,colmax)) = bounds arr
in colmax colmin + 1
addAxes :: Dimensions plot => Bool -> plot -> TextPlot -> TextPlot
addAxes False _ txt = txt
addAxes True p txt = addYAxis (getYlim p) . addXAxis (getXlim p) $ txt
addXAxis :: Range -> TextPlot -> TextPlot
addXAxis (xmin,xmax) lns =
let w = maximum . map length $ lns
xminLabel = printf "%-g" (toF xmin)
xmaxLabel = printf "%g" (toF xmax)
axis = "+" ++ replicate (w2) '-' ++ "+->"
padw = w (length xminLabel + length xmaxLabel)
labels = xminLabel ++ replicate padw ' ' ++ xmaxLabel
in lns ++ [axis,labels]
addYAxis :: Range -> TextPlot -> TextPlot
addYAxis (ymin,ymax) lns =
let minLabel = printf "%g" (toF ymin)
maxLabel = printf "%g" (toF ymax)
lw = max (length minLabel) (length maxLabel) + 1
tip = replicate lw ' ' ++ "^"
maxL = replicate (lw length maxLabel 1) ' ' ++ maxLabel ++ " +"
midL = replicate lw ' ' ++ "|"
minL = replicate (lw length minLabel 1) ' ' ++ minLabel ++ " +"
axisL = replicate (lw + 1) ' '
n = length lns
labels = (tip:maxL:(replicate (n4) midL)) ++ [minL, axisL, axisL]
in zipWith (++) labels ("":lns)
toF :: Double -> Float
toF = fromRational . toRational