------------------------------------------------------------------------------- {- OPTIONS_GHC -O2 #-} {-# OPTIONS_GHC -O0 #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE StandaloneDeriving #-} ------------------------------------------------------------------------------- -- For certain kinds of debugging, esp. of deepseq-bounded... #define REQUIRE_DATA_INSTANCE 0 ------------------------------------------------------------------------------- module Types_no_SOP where import Control.DeepSeq.Bounded import Control.DeepSeq.Generics --import Generics.SOP.TH import GHC.Generics ( Generic ) import Data.Typeable ( Typeable ) import Data.Data ( Data ) import System.Random #if 0 #if FORCING_STRATEGY == 4 import Seqaid.Runtime ( seqaid ) #endif #if FORCING_STRATEGY >= 5 --import Seqaid.Runtime -- comes in with Seqaid.TH import Seqaid.TH #endif #endif ------------------------------------------------------------------------------- type State = TA -- This is behaviourally a "strict blob", within the diagnostic -- purposes of leaky. It incurs a large, constant cost when -- the head is evaluated. This is also a reasonable model -- for function application (except then the cost is usually -- a function of argument values). [?] data Blob a = Blob [a] deriving (Show,Generic,Typeable,Data) instance (NFData a,Num a) => NFData (Blob a) where rnf x = force (doWork x) `seq` () instance (NFData a,Num a) => NFDataN (Blob a) where rnfn n x = force (doWork x) `seq` () #if REQUIRE_DATA_INSTANCE instance (NFData a,Num a,Typeable a,Data a) => NFDataP (Blob a) where rnfp p x = force (doWork x) `seq` () #else instance (NFData a,Num a,Typeable a) => NFDataP (Blob a) where rnfp p x = force (doWork x) `seq` () #endif doWork :: Num a => Blob a -> a doWork (Blob lst) = sum lst --doWork (Blob lst) = sum lst :: Num a => a -- XXX Why exactly is this needed, when it wasn't needed when -- everything was in one module??... #if 0 {-# NOINLINE hackblah #-} hackblah :: IO StdGen hackblah = getStdGen #else deriving instance Typeable StdGen #if REQUIRE_DATA_INSTANCE instance Data StdGen -- only for certain deepseq-bounded debugging #endif instance NFData StdGen where rnf x = () instance NFDataN StdGen where rnfn n x = () instance NFDataP StdGen where rnfp p x = () #endif #if 1 -- (No strict fields.) data TA = A1 Int | A2 TB Int TC data TB = B1 | B2 TC | B3 Int TA TB #if USE_STRICT_BLOB -- Note: I think Blob must NOT have a strictness bang (!). -- Later: I doubt it matters, the way doing Blob's now... data TC = C1 Int TC | C2 Int | C3 TC (Blob Int) ![Int] TC #else data TC = C1 Int TC | C2 Int | C3 TC ![Int] TC #endif #else -- All Int fields strict (!): data TA = A1 !Int | A2 TB !Int TC data TB = B1 | B2 TC | B3 !Int TA TB #if USE_STRICT_BLOB -- Note: I think Blob must NOT have a strictness bang (!). -- Later: I doubt it matters, the way doing Blob's now... data TC = C1 !Int TC | C2 !Int | C3 TC (Blob Int) ![Int] TC #else data TC = C1 !Int TC | C2 !Int | C3 TC ![Int] TC #endif #endif -------------------------------------------------------------------------------