{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
module Control.Seq
(
Strategy
, using
, withStrategy
, r0
, rseq
, rdeepseq
, seqList
, seqListN
, seqListNth
, seqFoldable
, seqMap
, seqArray
, seqArrayBounds
, seqTuple2
, seqTuple3
, seqTuple4
, seqTuple5
, seqTuple6
, seqTuple7
, seqTuple8
, seqTuple9
) where
import Control.DeepSeq (NFData, deepseq)
#if MIN_VERSION_base(4,8,0)
import Data.Foldable (toList)
#else
import Data.Foldable (Foldable, toList)
#endif
import Data.Map (Map)
import qualified Data.Map (toList)
#if !((__GLASGOW_HASKELL__ >= 711) && MIN_VERSION_array(0,5,1))
import Data.Ix (Ix)
#endif
import Data.Array (Array)
import qualified Data.Array (bounds, elems)
infixl 0 `using`
type Strategy a = a -> ()
using :: a -> Strategy a -> a
a
x using :: forall a. a -> Strategy a -> a
`using` Strategy a
strat = Strategy a
strat a
x seq :: forall a b. a -> b -> b
`seq` a
x
withStrategy :: Strategy a -> a -> a
withStrategy :: forall a. Strategy a -> a -> a
withStrategy = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. a -> Strategy a -> a
using
r0 :: Strategy a
r0 :: forall a. Strategy a
r0 a
_ = ()
rseq :: Strategy a
rseq :: forall a. Strategy a
rseq a
x = a
x seq :: forall a b. a -> b -> b
`seq` ()
rdeepseq :: NFData a => Strategy a
rdeepseq :: forall a. NFData a => Strategy a
rdeepseq a
x = a
x forall a b. NFData a => a -> b -> b
`deepseq` ()
seqList :: Strategy a -> Strategy [a]
seqList :: forall a. Strategy a -> Strategy [a]
seqList Strategy a
_strat [] = ()
seqList Strategy a
strat (a
x:[a]
xs) = Strategy a
strat a
x seq :: forall a b. a -> b -> b
`seq` forall a. Strategy a -> Strategy [a]
seqList Strategy a
strat [a]
xs
seqListN :: Int -> Strategy a -> Strategy [a]
seqListN :: forall a. Int -> Strategy a -> Strategy [a]
seqListN Int
0 Strategy a
_strat [a]
_ = ()
seqListN !Int
_ Strategy a
_strat [] = ()
seqListN !Int
n Strategy a
strat (a
x:[a]
xs) = Strategy a
strat a
x seq :: forall a b. a -> b -> b
`seq` forall a. Int -> Strategy a -> Strategy [a]
seqListN (Int
nforall a. Num a => a -> a -> a
-Int
1) Strategy a
strat [a]
xs
seqListNth :: Int -> Strategy a -> Strategy [a]
seqListNth :: forall a. Int -> Strategy a -> Strategy [a]
seqListNth Int
0 Strategy a
strat (a
x:[a]
_) = Strategy a
strat a
x
seqListNth !Int
_ Strategy a
_strat [] = ()
seqListNth !Int
n Strategy a
strat (a
_:[a]
xs) = forall a. Int -> Strategy a -> Strategy [a]
seqListNth (Int
nforall a. Num a => a -> a -> a
-Int
1) Strategy a
strat [a]
xs
seqFoldable :: Foldable t => Strategy a -> Strategy (t a)
seqFoldable :: forall (t :: * -> *) a. Foldable t => Strategy a -> Strategy (t a)
seqFoldable Strategy a
strat = forall a. Strategy a -> Strategy [a]
seqList Strategy a
strat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
{-# SPECIALISE seqFoldable :: Strategy a -> Strategy [a] #-}
#if (__GLASGOW_HASKELL__ >= 711) && MIN_VERSION_array(0,5,1)
seqArray :: Strategy a -> Strategy (Array i a)
#else
seqArray :: Ix i => Strategy a -> Strategy (Array i a)
#endif
seqArray :: forall a i. Strategy a -> Strategy (Array i a)
seqArray Strategy a
strat = forall a. Strategy a -> Strategy [a]
seqList Strategy a
strat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i e. Array i e -> [e]
Data.Array.elems
#if (__GLASGOW_HASKELL__ >= 711) && MIN_VERSION_array(0,5,1)
seqArrayBounds :: Strategy i -> Strategy (Array i a)
#else
seqArrayBounds :: Ix i => Strategy i -> Strategy (Array i a)
#endif
seqArrayBounds :: forall i a. Strategy i -> Strategy (Array i a)
seqArrayBounds Strategy i
strat = forall a b. Strategy a -> Strategy b -> Strategy (a, b)
seqTuple2 Strategy i
strat Strategy i
strat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i e. Array i e -> (i, i)
Data.Array.bounds
seqMap :: Strategy k -> Strategy v -> Strategy (Map k v)
seqMap :: forall k v. Strategy k -> Strategy v -> Strategy (Map k v)
seqMap Strategy k
stratK Strategy v
stratV = forall a. Strategy a -> Strategy [a]
seqList (forall a b. Strategy a -> Strategy b -> Strategy (a, b)
seqTuple2 Strategy k
stratK Strategy v
stratV) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
Data.Map.toList
seqTuple2 :: Strategy a -> Strategy b -> Strategy (a,b)
seqTuple2 :: forall a b. Strategy a -> Strategy b -> Strategy (a, b)
seqTuple2 Strategy a
strat1 Strategy b
strat2 (a
x1,b
x2) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2
seqTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
seqTuple3 :: forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
seqTuple3 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 (a
x1,b
x2,c
x3) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2 seq :: forall a b. a -> b -> b
`seq` Strategy c
strat3 c
x3
seqTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a,b,c,d)
seqTuple4 :: forall a b c d.
Strategy a
-> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d)
seqTuple4 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 (a
x1,b
x2,c
x3,d
x4) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2 seq :: forall a b. a -> b -> b
`seq` Strategy c
strat3 c
x3 seq :: forall a b. a -> b -> b
`seq` Strategy d
strat4 d
x4
seqTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a,b,c,d,e)
seqTuple5 :: forall a b c d e.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy (a, b, c, d, e)
seqTuple5 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 (a
x1,b
x2,c
x3,d
x4,e
x5) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2 seq :: forall a b. a -> b -> b
`seq` Strategy c
strat3 c
x3 seq :: forall a b. a -> b -> b
`seq` Strategy d
strat4 d
x4 seq :: forall a b. a -> b -> b
`seq` Strategy e
strat5 e
x5
seqTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a,b,c,d,e,f)
seqTuple6 :: forall a b c d e f.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy (a, b, c, d, e, f)
seqTuple6 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2 seq :: forall a b. a -> b -> b
`seq` Strategy c
strat3 c
x3 seq :: forall a b. a -> b -> b
`seq` Strategy d
strat4 d
x4 seq :: forall a b. a -> b -> b
`seq` Strategy e
strat5 e
x5 seq :: forall a b. a -> b -> b
`seq` Strategy f
strat6 f
x6
seqTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a,b,c,d,e,f,g)
seqTuple7 :: forall a b c d e f g.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy g
-> Strategy (a, b, c, d, e, f, g)
seqTuple7 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6,g
x7) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2 seq :: forall a b. a -> b -> b
`seq` Strategy c
strat3 c
x3 seq :: forall a b. a -> b -> b
`seq` Strategy d
strat4 d
x4 seq :: forall a b. a -> b -> b
`seq` Strategy e
strat5 e
x5 seq :: forall a b. a -> b -> b
`seq` Strategy f
strat6 f
x6 seq :: forall a b. a -> b -> b
`seq` Strategy g
strat7 g
x7
seqTuple8 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy (a,b,c,d,e,f,g,h)
seqTuple8 :: forall a b c d e f g h.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy g
-> Strategy h
-> Strategy (a, b, c, d, e, f, g, h)
seqTuple8 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 Strategy h
strat8 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6,g
x7,h
x8) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2 seq :: forall a b. a -> b -> b
`seq` Strategy c
strat3 c
x3 seq :: forall a b. a -> b -> b
`seq` Strategy d
strat4 d
x4 seq :: forall a b. a -> b -> b
`seq` Strategy e
strat5 e
x5 seq :: forall a b. a -> b -> b
`seq` Strategy f
strat6 f
x6 seq :: forall a b. a -> b -> b
`seq` Strategy g
strat7 g
x7 seq :: forall a b. a -> b -> b
`seq` Strategy h
strat8 h
x8
seqTuple9 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy i -> Strategy (a,b,c,d,e,f,g,h,i)
seqTuple9 :: forall a b c d e f g h i.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy g
-> Strategy h
-> Strategy i
-> Strategy (a, b, c, d, e, f, g, h, i)
seqTuple9 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 Strategy h
strat8 Strategy i
strat9 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6,g
x7,h
x8,i
x9) =
Strategy a
strat1 a
x1 seq :: forall a b. a -> b -> b
`seq` Strategy b
strat2 b
x2 seq :: forall a b. a -> b -> b
`seq` Strategy c
strat3 c
x3 seq :: forall a b. a -> b -> b
`seq` Strategy d
strat4 d
x4 seq :: forall a b. a -> b -> b
`seq` Strategy e
strat5 e
x5 seq :: forall a b. a -> b -> b
`seq` Strategy f
strat6 f
x6 seq :: forall a b. a -> b -> b
`seq` Strategy g
strat7 g
x7 seq :: forall a b. a -> b -> b
`seq` Strategy h
strat8 h
x8 seq :: forall a b. a -> b -> b
`seq` Strategy i
strat9 i
x9