Commit 90f967c1 authored by Sumit Sahrawat's avatar Sumit Sahrawat

Formatting fixes

parent 007e9532
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{- There are 3 types of plots to consider in haskell-gnuplot: Plot, Frame and Multiplot. {- There are 3 types of plots to consider in haskell-gnuplot: Plot, Frame and Multiplot.
Plot types are the actual plots, whereas Frame types are plots with additional options Plot types are the actual plots, whereas Frame types are plots with additional options
e.g. custom axes tics, graph title etc.. Multiplots are collections of 2D and/or 3D plots. e.g. custom axes tics, graph title etc.. Multiplots are collections of 2D and/or 3D plots.
...@@ -26,50 +27,51 @@ import IHaskell.Display ...@@ -26,50 +27,51 @@ import IHaskell.Display
-- Plot-types -- Plot-types
instance (C x, C y) => IHaskellDisplay (P.T (Tw.T x y)) where instance (C x, C y) => IHaskellDisplay (P.T (Tw.T x y)) where
display fig = do display fig = do
pngDisp <- graphDataPNG2P fig pngDisp <- graphDataPNG2P fig
svgDisp <- graphDataSVG2P fig svgDisp <- graphDataSVG2P fig
return $ Display [pngDisp, svgDisp] return $ Display [pngDisp, svgDisp]
instance (C x, C y, C z) => IHaskellDisplay (P.T (Th.T x y z)) where instance (C x, C y, C z) => IHaskellDisplay (P.T (Th.T x y z)) where
display fig = do display fig = do
pngDisp <- graphDataPNG3P fig pngDisp <- graphDataPNG3P fig
svgDisp <- graphDataSVG3P fig svgDisp <- graphDataSVG3P fig
return $ Display [pngDisp, svgDisp] return $ Display [pngDisp, svgDisp]
-- Frame-types -- Frame-types
instance (C x, C y) => IHaskellDisplay (F.T (Tw.T x y)) where instance (C x, C y) => IHaskellDisplay (F.T (Tw.T x y)) where
display fig = do display fig = do
pngDisp <- graphDataPNG2F fig pngDisp <- graphDataPNG2F fig
svgDisp <- graphDataSVG2F fig svgDisp <- graphDataSVG2F fig
return $ Display [pngDisp, svgDisp] return $ Display [pngDisp, svgDisp]
instance (C x, C y, C z) => IHaskellDisplay (F.T (Th.T x y z)) where instance (C x, C y, C z) => IHaskellDisplay (F.T (Th.T x y z)) where
display fig = do display fig = do
pngDisp <- graphDataPNG3F fig pngDisp <- graphDataPNG3F fig
svgDisp <- graphDataSVG3F fig svgDisp <- graphDataSVG3F fig
return $ Display [pngDisp, svgDisp] return $ Display [pngDisp, svgDisp]
-- Type: Multiplot -- Type: Multiplot
instance IHaskellDisplay M.T where instance IHaskellDisplay M.T where
display fig = do display fig = do
pngDisp <- graphDataPNGM fig pngDisp <- graphDataPNGM fig
svgDisp <- graphDataSVGM fig svgDisp <- graphDataSVGM fig
return $ Display [pngDisp, svgDisp] return $ Display [pngDisp, svgDisp]
-- Filename -- Filename
name = ".ihaskell-gnuplot." name = ".ihaskell-gnuplot."
-- Width and height -- Width and height
w = 300 w = 300
h = 300 h = 300
graphDataPNG2P :: (C x, C y) => P.T (Tw.T x y) -> IO DisplayData graphDataPNG2P :: (C x, C y) => P.T (Tw.T x y) -> IO DisplayData
graphDataPNG2P graph = do graphDataPNG2P graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Pn.cons $ name ++ "png" let fname = Pn.cons $ name ++ "png"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
...@@ -81,7 +83,7 @@ graphDataSVG2P graph = do ...@@ -81,7 +83,7 @@ graphDataSVG2P graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Sv.cons $ name ++ "svg" let fname = Sv.cons $ name ++ "svg"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
...@@ -93,7 +95,7 @@ graphDataPNG2F graph = do ...@@ -93,7 +95,7 @@ graphDataPNG2F graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Pn.cons $ name ++ "png" let fname = Pn.cons $ name ++ "png"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
...@@ -105,7 +107,7 @@ graphDataSVG2F graph = do ...@@ -105,7 +107,7 @@ graphDataSVG2F graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Sv.cons $ name ++ "svg" let fname = Sv.cons $ name ++ "svg"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
...@@ -117,7 +119,7 @@ graphDataPNG3P graph = do ...@@ -117,7 +119,7 @@ graphDataPNG3P graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Pn.cons $ name ++ "png" let fname = Pn.cons $ name ++ "png"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
...@@ -129,11 +131,11 @@ graphDataSVG3P graph = do ...@@ -129,11 +131,11 @@ graphDataSVG3P graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Sv.cons $ name ++ "svg" let fname = Sv.cons $ name ++ "svg"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
imgData <- Char.readFile $ name ++ "svg" imgData <- Char.readFile $ name ++ "svg"
return $ svg $ Char.unpack imgData return $ svg $ Char.unpack imgData
graphDataPNG3F :: (C x, C y, C z) => F.T (Th.T x y z) -> IO DisplayData graphDataPNG3F :: (C x, C y, C z) => F.T (Th.T x y z) -> IO DisplayData
...@@ -141,7 +143,7 @@ graphDataPNG3F graph = do ...@@ -141,7 +143,7 @@ graphDataPNG3F graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Pn.cons $ name ++ "png" let fname = Pn.cons $ name ++ "png"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
...@@ -153,20 +155,19 @@ graphDataSVG3F graph = do ...@@ -153,20 +155,19 @@ graphDataSVG3F graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Sv.cons $ name ++ "svg" let fname = Sv.cons $ name ++ "svg"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
imgData <- Char.readFile $ name ++ "svg" imgData <- Char.readFile $ name ++ "svg"
return $ svg $ Char.unpack imgData return $ svg $ Char.unpack imgData
graphDataPNGM :: M.T -> IO DisplayData graphDataPNGM :: M.T -> IO DisplayData
graphDataPNGM graph = do graphDataPNGM graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Pn.cons $ name ++ "png" let fname = Pn.cons $ name ++ "png"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
...@@ -178,7 +179,7 @@ graphDataSVGM graph = do ...@@ -178,7 +179,7 @@ graphDataSVGM graph = do
switchToTmpDir switchToTmpDir
-- Write the image. -- Write the image.
let fname = Sv.cons $ name ++ "svg" let fname = Sv.cons $ name ++ "svg"
plot fname graph plot fname graph
-- Read back, and convert to base64. -- Read back, and convert to base64.
......
import Distribution.Simple import Distribution.Simple
main = defaultMain main = defaultMain
...@@ -288,7 +288,8 @@ data Message = ...@@ -288,7 +288,8 @@ data Message =
KernelInfoReply KernelInfoReply
{ header :: MessageHeader { header :: MessageHeader
, protocolVersion :: String -- ^ current protocol version, major and minor , protocolVersion :: String -- ^ current protocol version, major and minor
, banner :: String -- ^ Kernel information description e.g. (IHaskell 0.8.3.0 GHC 7.10.2) , banner :: String -- ^ Kernel information description e.g. (IHaskell 0.8.3.0 GHC
-- 7.10.2)
, implementation :: String -- ^ e.g. IHaskell , implementation :: String -- ^ e.g. IHaskell
, implementationVersion :: String -- ^ The version of the implementation , implementationVersion :: String -- ^ The version of the implementation
, languageInfo :: LanguageInfo , languageInfo :: LanguageInfo
......
...@@ -4,93 +4,94 @@ import IHaskellPrelude ...@@ -4,93 +4,94 @@ import IHaskellPrelude
ihaskellCSS :: String ihaskellCSS :: String
ihaskellCSS = ihaskellCSS =
unlines [ unlines
-- Custom IHaskell CSS [
"/* Styles used for the Hoogle display in the pager */" -- Custom IHaskell CSS
, ".hoogle-doc {" "/* Styles used for the Hoogle display in the pager */"
, "display: block;" , ".hoogle-doc {"
, "padding-bottom: 1.3em;" , "display: block;"
, "padding-left: 0.4em;" , "padding-bottom: 1.3em;"
, "}" , "padding-left: 0.4em;"
, ".hoogle-code {" , "}"
, "display: block;" , ".hoogle-code {"
, "font-family: monospace;" , "display: block;"
, "white-space: pre;" , "font-family: monospace;"
, "}" , "white-space: pre;"
, ".hoogle-text {" , "}"
, "display: block;" , ".hoogle-text {"
, "}" , "display: block;"
, ".hoogle-name {" , "}"
, "color: green;" , ".hoogle-name {"
, "font-weight: bold;" , "color: green;"
, "}" , "font-weight: bold;"
, ".hoogle-head {" , "}"
, "font-weight: bold;" , ".hoogle-head {"
, "}" , "font-weight: bold;"
, ".hoogle-sub {" , "}"
, "display: block;" , ".hoogle-sub {"
, "margin-left: 0.4em;" , "display: block;"
, "}" , "margin-left: 0.4em;"
, ".hoogle-package {" , "}"
, "font-weight: bold;" , ".hoogle-package {"
, "font-style: italic;" , "font-weight: bold;"
, "}" , "font-style: italic;"
, ".hoogle-module {" , "}"
, "font-weight: bold;" , ".hoogle-module {"
, "}" , "font-weight: bold;"
, ".hoogle-class {" , "}"
, "font-weight: bold;" , ".hoogle-class {"
, "}" , "font-weight: bold;"
, , "}"
-- Styles used for basic displays ,
".get-type {" -- Styles used for basic displays
, "color: green;" ".get-type {"
, "font-weight: bold;" , "color: green;"
, "font-family: monospace;" , "font-weight: bold;"
, "display: block;" , "font-family: monospace;"
, "white-space: pre-wrap;" , "display: block;"
, "}" , "white-space: pre-wrap;"
, ".show-type {" , "}"
, "color: green;" , ".show-type {"
, "font-weight: bold;" , "color: green;"
, "font-family: monospace;" , "font-weight: bold;"
, "margin-left: 1em;" , "font-family: monospace;"
, "}" , "margin-left: 1em;"
, ".mono {" , "}"
, "font-family: monospace;" , ".mono {"
, "display: block;" , "font-family: monospace;"
, "}" , "display: block;"
, ".err-msg {" , "}"
, "color: red;" , ".err-msg {"
, "font-style: italic;" , "color: red;"
, "font-family: monospace;" , "font-style: italic;"
, "white-space: pre;" , "font-family: monospace;"
, "display: block;" , "white-space: pre;"
, "}" , "display: block;"
, "#unshowable {" , "}"
, "color: red;" , "#unshowable {"
, "font-weight: bold;" , "color: red;"
, "}" , "font-weight: bold;"
, ".err-msg.in.collapse {" , "}"
, "padding-top: 0.7em;" , ".err-msg.in.collapse {"
, "}" , "padding-top: 0.7em;"
, , "}"
-- Code that will get highlighted before it is highlighted ,
".highlight-code {" -- Code that will get highlighted before it is highlighted
, "white-space: pre;" ".highlight-code {"
, "font-family: monospace;" , "white-space: pre;"
, "}" , "font-family: monospace;"
, , "}"
-- Hlint styles ,
".suggestion-warning { " -- Hlint styles
, "font-weight: bold;" ".suggestion-warning { "
, "color: rgb(200, 130, 0);" , "font-weight: bold;"
, "}" , "color: rgb(200, 130, 0);"
, ".suggestion-error { " , "}"
, "font-weight: bold;" , ".suggestion-error { "
, "color: red;" , "font-weight: bold;"
, "}" , "color: red;"
, ".suggestion-name {" , "}"
, "font-weight: bold;" , ".suggestion-name {"
, "}" , "font-weight: bold;"
] , "}"
]
...@@ -187,7 +187,7 @@ htmlSuggestions = concatMap toHtml ...@@ -187,7 +187,7 @@ htmlSuggestions = concatMap toHtml
_ -> "warning" _ -> "warning"
style :: String -> String -> String style :: String -> String -> String
style = printf "<div class=\"suggestion-%s\">%s</div>" style = printf "<div class=\"suggestion-%s\">%s</div>"
named :: String -> String named :: String -> String
named = printf "<div class=\"suggestion-name\" style=\"clear:both;\">%s</div>" named = printf "<div class=\"suggestion-name\" style=\"clear:both;\">%s</div>"
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment