aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2025-04-05 12:31:40 -0700
committerJohn MacFarlane <[email protected]>2025-04-05 12:31:40 -0700
commitf8f7c29fb81468a7b559e9590089152cee5d0b04 (patch)
treee1fe17b93e6f74c99d3c72fbbe1734f70ea120d8 /src
parent0d2114ee4e3974583ee84e8a4e992562d6502f66 (diff)
Allow compilation with random 1.2.*.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Class/PandocPure.hs14
1 files changed, 12 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Class/PandocPure.hs b/src/Text/Pandoc/Class/PandocPure.hs
index c026d89f5..12923abb5 100644
--- a/src/Text/Pandoc/Class/PandocPure.hs
+++ b/src/Text/Pandoc/Class/PandocPure.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
@@ -49,7 +50,7 @@ import Data.Word (Word8)
import System.Directory (doesDirectoryExist, getDirectoryContents)
import System.FilePath ((</>))
import System.FilePath.Glob (match, compile)
-import System.Random (StdGen, splitGen, mkStdGen)
+import System.Random (StdGen, mkStdGen)
import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Class.PandocMonad
import Text.Pandoc.Error
@@ -59,6 +60,15 @@ import qualified Data.Map as M
import qualified Data.Text as T
import qualified System.Directory as Directory (getModificationTime)
+#if MIN_VERSION_random(1,3,0)
+import System.Random (splitGen, SplitGen)
+
+split :: SplitGen g => g -> (g, g)
+split = splitGen
+#else
+import System.Random (split)
+#endif
+
-- | The 'PureState' contains ersatz representations
-- of things that would normally be obtained through IO.
data PureState = PureState
@@ -180,7 +190,7 @@ instance PandocMonad PandocPure where
newStdGen = do
oldGen <- getsPureState stStdGen
- let (genToStore, genToReturn) = splitGen oldGen
+ let (genToStore, genToReturn) = split oldGen
modifyPureState $ \st -> st { stStdGen = genToStore }
return genToReturn