mirror of
https://github.com/codedownio/haskell-plot.git
synced 2025-04-28 09:06:05 +00:00
Fix build with mtl-2.3
This commit is contained in:
parent
cb4ac9e227
commit
a51efe80f8
@ -37,7 +37,9 @@ import Control.Monad.Trans()
|
|||||||
import Control.Monad.Fail ( MonadFail, fail )
|
import Control.Monad.Fail ( MonadFail, fail )
|
||||||
import Prelude hiding ( fail )
|
import Prelude hiding ( fail )
|
||||||
#endif
|
#endif
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
class Supply a b where
|
class Supply a b where
|
||||||
@ -125,4 +127,3 @@ instance MonadWriter w m => MonadWriter w (SupplyT s m) where
|
|||||||
return ((a,s'),f)
|
return ((a,s'),f)
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : Graphics.Rendering.Plot.Figure.Plot.Axis
|
-- Module : Graphics.Rendering.Plot.Figure.Plot.Axis
|
||||||
@ -33,6 +34,9 @@ import Data.Maybe (fromMaybe)
|
|||||||
|
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
|
|
||||||
import Graphics.Rendering.Plot.Types
|
import Graphics.Rendering.Plot.Types
|
||||||
import Graphics.Rendering.Plot.Defaults
|
import Graphics.Rendering.Plot.Defaults
|
||||||
@ -137,4 +141,3 @@ withTickLabelFormat m = do
|
|||||||
put $ ax { _tick_labels = map (execText m to) (_tick_labels ax) }
|
put $ ax { _tick_labels = map (execText m to) (_tick_labels ax) }
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -2,6 +2,7 @@
|
|||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : Graphics.Rendering.Plot.Figure.Plot.Data
|
-- Module : Graphics.Rendering.Plot.Figure.Plot.Data
|
||||||
@ -57,6 +58,10 @@ import Graphics.Rendering.Plot.Figure.Line
|
|||||||
import Graphics.Rendering.Plot.Figure.Point
|
import Graphics.Rendering.Plot.Figure.Point
|
||||||
import Graphics.Rendering.Plot.Figure.Bar
|
import Graphics.Rendering.Plot.Figure.Bar
|
||||||
|
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
dataSeriesNum :: DataSeries -> Int
|
dataSeriesNum :: DataSeries -> Int
|
||||||
@ -911,4 +916,3 @@ isMonotoneIncreasing :: Vector Double -> Bool
|
|||||||
isMonotoneIncreasing v = maybe False (\_ -> True) $ evalState (runMaybeT $ (mapVectorM_ monoStep (subVector 1 (size v -1) v))) (v `atIndex` 0)
|
isMonotoneIncreasing v = maybe False (\_ -> True) $ evalState (runMaybeT $ (mapVectorM_ monoStep (subVector 1 (size v -1) v))) (v `atIndex` 0)
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : Graphics.Rendering.Plot.Render.Plot
|
-- Module : Graphics.Rendering.Plot.Render.Plot
|
||||||
@ -60,6 +61,10 @@ import Graphics.Rendering.Plot.Render.Plot.Annotation
|
|||||||
--import Prelude hiding(min,max)
|
--import Prelude hiding(min,max)
|
||||||
--import qualified Prelude(max)
|
--import qualified Prelude(max)
|
||||||
|
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
bbPlot :: Int -> Int -> (Int,Int) -> Render ()
|
bbPlot :: Int -> Int -> (Int,Int) -> Render ()
|
||||||
@ -120,5 +125,3 @@ renderBorder True = do
|
|||||||
C.stroke
|
C.stroke
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : Graphics.Rendering.Plot.Render.Plot.Annotation
|
-- Module : Graphics.Rendering.Plot.Render.Plot.Annotation
|
||||||
@ -37,6 +38,10 @@ import Graphics.Rendering.Plot.Render.Plot.Format
|
|||||||
--import Prelude hiding(min,max)
|
--import Prelude hiding(min,max)
|
||||||
--import qualified Prelude(max)
|
--import qualified Prelude(max)
|
||||||
|
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
renderAnnotations :: Ranges -> Annotations -> Render ()
|
renderAnnotations :: Ranges -> Annotations -> Render ()
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : Graphics.Rendering.Plot.Render.Plot.Axis
|
-- Module : Graphics.Rendering.Plot.Render.Plot.Axis
|
||||||
@ -48,6 +49,10 @@ import qualified Text.Printf as Printf
|
|||||||
import Prelude hiding(min,max)
|
import Prelude hiding(min,max)
|
||||||
import qualified Prelude(max)
|
import qualified Prelude(max)
|
||||||
|
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
moveTo :: Double -> Double -> C.Render ()
|
moveTo :: Double -> Double -> C.Render ()
|
||||||
|
@ -1,6 +1,7 @@
|
|||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE UnicodeSyntax #-}
|
{-# LANGUAGE UnicodeSyntax #-}
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
@ -58,6 +59,10 @@ import Graphics.Rendering.Plot.Defaults
|
|||||||
import Prelude hiding(min,max,abs)
|
import Prelude hiding(min,max,abs)
|
||||||
import qualified Prelude
|
import qualified Prelude
|
||||||
|
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
findMinIdx, findMaxIdx :: Vector Double -> Double -> Int -> Int -> Int
|
findMinIdx, findMaxIdx :: Vector Double -> Double -> Int -> Int -> Int
|
||||||
@ -636,5 +641,3 @@ endWhiskerSample :: Double -> Double -> C.Render ()
|
|||||||
endWhiskerSample _ _ = return ()
|
endWhiskerSample _ _ = return ()
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : Graphics.Rendering.Plot.Render.Plot.Legend
|
-- Module : Graphics.Rendering.Plot.Render.Plot.Legend
|
||||||
@ -41,6 +42,10 @@ import Graphics.Rendering.Plot.Render.Plot.Glyph
|
|||||||
--import Prelude hiding(min,max)
|
--import Prelude hiding(min,max)
|
||||||
--import qualified Prelude(max)
|
--import qualified Prelude(max)
|
||||||
|
|
||||||
|
#if MIN_VERSION_mtl(2,3,0)
|
||||||
|
import Control.Monad
|
||||||
|
#endif
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
renderLegend :: Maybe LegendData -> DataSeries -> Render (Padding -> Render ())
|
renderLegend :: Maybe LegendData -> DataSeries -> Render (Padding -> Render ())
|
||||||
@ -301,4 +306,3 @@ getLabels (DS_1to1 d) = let mls = map (\(_,(DecSeries o d')) -> (maybe "" id $
|
|||||||
getLabels (DS_Surf _) = (0,[])
|
getLabels (DS_Surf _) = (0,[])
|
||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
Loading…
x
Reference in New Issue
Block a user