99{-# LANGUAGE ScopedTypeVariables #-}
1010{-# LANGUAGE ViewPatterns #-}
1111
12+ #if MIN_VERSION_random(1,3,0)
13+ {-# OPTIONS_GHC -Wno-deprecations #-} -- Due to usage of `split`
14+ #endif
1215-- | Generate example CBOR given a CDDL specification
1316module Codec.CBOR.Cuddle.CBOR.Gen (generateCBORTerm , generateCBORTerm' ) where
1417
15- import qualified Control.Monad.State.Strict as MTL
1618import Capability.Reader
1719import Capability.Sink (HasSink )
1820import Capability.Source (HasSource , MonadState (.. ))
@@ -34,6 +36,7 @@ import Codec.CBOR.Write qualified as CBOR
3436import Control.Monad (join , replicateM , (<=<) )
3537import Control.Monad.Reader (Reader , runReader )
3638import Control.Monad.State.Strict (StateT , runStateT )
39+ import Control.Monad.State.Strict qualified as MTL
3740import Data.Bifunctor (second )
3841import Data.ByteString (ByteString )
3942import Data.ByteString.Base16 qualified as Base16
@@ -54,6 +57,11 @@ import System.Random.Stateful (
5457 randomM ,
5558 uniformByteStringM ,
5659 )
60+ #if MIN_VERSION_random(1,3,0)
61+ import System.Random.Stateful (
62+ SplitGen (.. )
63+ )
64+ #endif
5765
5866--------------------------------------------------------------------------------
5967-- Generator infrastructure
@@ -81,9 +89,17 @@ instance RandomGen g => RandomGen (GenState g) where
8189 genWord16 = withRandomSeed genWord16
8290 genWord32 = withRandomSeed genWord32
8391 genWord64 = withRandomSeed genWord64
84- split s =
85- case split (randomSeed s) of
86- (gen', gen) -> (s {randomSeed = gen'}, s {randomSeed = gen})
92+ split = splitGenStateWith split
93+
94+ #if MIN_VERSION_random(1,3,0)
95+ instance SplitGen g => SplitGen (GenState g ) where
96+ splitGen = splitGenStateWith splitGen
97+ #endif
98+
99+ splitGenStateWith :: (g -> (g , g )) -> GenState g -> (GenState g , GenState g )
100+ splitGenStateWith f s =
101+ case f (randomSeed s) of
102+ (gen', gen) -> (s {randomSeed = gen'}, s {randomSeed = gen})
87103
88104withRandomSeed :: (t -> (a , g )) -> GenState t -> (a , GenState g )
89105withRandomSeed f s =
0 commit comments