#define DO_TRACE 0
#define INCLUDE_SHOW_INSTANCES 0
#if __GLASGOW_HASKELL__ < 708
#endif
module Control.DeepSeq.Bounded.Generic.GNFDataP
(
grnfp
#if 0
, deepseq
, force
, NFData ( rnf )
, ($!!)
#endif
)
where
import Control.DeepSeq.Bounded.NFDataN ( NFDataN )
import Control.DeepSeq ( NFData )
import Data.Typeable ( Typeable )
import Control.DeepSeq.Bounded.NFDataP ( NFDataP, rnfp )
import Control.DeepSeq.Bounded.NFDataN ( rnfn )
import Control.DeepSeq ( rnf )
import Control.DeepSeq.Bounded.NFDataP ( handleAttrs )
import Control.DeepSeq.Bounded.Pattern ( Rose(..), Pattern(..) )
import Control.DeepSeq.Bounded.Pattern ( PatNode(..), PatNodeAttrs(..) )
import Control.DeepSeq.Bounded.Pattern ( getPatNodeAttrs )
import Generics.SOP
#if USE_PAR_PATNODE
import Control.Parallel ( par )
#endif
#if USE_PSEQ_PATNODE
import Control.Parallel ( pseq )
#endif
import Data.Maybe
import Debug.Trace ( trace )
#if DO_TRACE
mytrace = trace
mytrace' = trace
#else
mytrace x y = y
mytrace' x y = y
#endif
grnfp :: forall a.
(
Generic a
, HasDatatypeInfo a
, All2 NFDataP (Code a)
#if INCLUDE_SHOW_INSTANCES
, All2 Show (Code a)
#endif
, NFDataP a
) => Pattern -> a -> ()
grnfp pat x = grnfp' dti proxy_a pat x xrep
where
dti = datatypeInfo proxy_a
proxy_a = Proxy :: Proxy a
xrep = from x
grnfp' :: forall a.
(
Generic a
, HasDatatypeInfo a
, All2 NFDataP (Code a)
#if INCLUDE_SHOW_INSTANCES
, All2 Show (Code a)
#endif
, NFDataP a
) =>
DatatypeInfo (Code a)
-> Proxy a
-> Pattern
-> a
-> Rep a
-> ()
grnfp' (ADT _ _ cs) proxy_a pat x xrep
= grnfpS cs proxy_a pat x xrep
grnfp' (Newtype _ _ c ) proxy_a pat x xrep
= grnfpS (c :* Nil) proxy_a pat x xrep
grnfpS :: forall a xss.
(
All2 NFDataP xss
#if INCLUDE_SHOW_INSTANCES
, All2 Show xss
#endif
, NFDataP a
) =>
NP ConstructorInfo xss
-> Proxy a
-> Pattern
-> a
-> SOP I xss
-> ()
grnfpS _ _ (Node WI{} _) _ _ = ()
grnfpS (m :* _) proxy_a pat@(Node pas pcs) x (SOP (Z xs))
| not status = patMatchFail'' msg `seq` ()
| handleAttrs pat x `seq` pat == Node XX [] = undefined
#if USE_PAR_PATNODE
| doSpark as = case pas of
WW{} -> rnf x `par` ()
WN{} -> rnfn n x `par` ()
otherwise -> dorecurs
#endif
| TR{} <- pas = if elem tx treps then dorecurs else ()
#if USE_WW_DEEPSEQ
| TI{} <- pas = if elem tx treps then () else rnf x
| TW{} <- pas = if elem tx treps then rnf x else ()
#else
| TI{} <- pas = if elem tx treps then () else rnfn 999999 x
#endif
#if USE_WW_DEEPSEQ
| WW{} <- pas = rnf x
#endif
| WN{} <- pas = rnfn n x
#if USE_WW_DEEPSEQ
| TW{} <- pas = if elem tx treps then rnf x else ()
#endif
| otherwise = dorecurs
where
as = getPatNodeAttrs pas
treps = typeConstraints as
n = depth as
(status,mmsg) = grnfpP_validate True pas pcs tx xs
!_ = mytrace ("*** "++tx) $ ()
tx | (Constructor n) <- m = n
| (Infix n _ _) <- m = n
| (Record n _) <- m = n
!_ = mytrace ("VVV "++show status) $ ()
msg = fromJust mmsg
#if USE_PAR_PATNODE
#if DO_TRACE
dorecurs | doSpark as = grnfpP_ m () True pas pcs xs `par` ()
| otherwise = grnfpP_ m () True pas pcs xs `seq` ()
#else
dorecurs | doSpark as = grnfpP m () True pas pcs xs `par` ()
| otherwise = grnfpP m () True pas pcs xs `seq` ()
#endif
#else
#if DO_TRACE
dorecurs = grnfpP_ m () True p pcs xs `seq` ()
#else
dorecurs = grnfpP m () True p pcs xs `seq` ()
#endif
#endif
grnfpS (m :* ms) proxy_a pat x (SOP (S xss))
= grnfpS ms proxy_a pat x (SOP xss)
grnfpS _ _ _ _ _ = error "grnfpS: unexpected case!!"
grnfpP :: forall cs xs.
(
All NFDataP xs
#if INCLUDE_SHOW_INSTANCES
, All Show xs
#endif
) =>
ConstructorInfo cs
-> ()
-> Bool
-> PatNode
-> [Pattern]
-> NP I xs
-> ()
grnfpP ci acc b pp [] Nil = acc
grnfpP ci acc True pp [] (I x :* xs)
= grnfpP ci acc True pp [] xs
grnfpP ci acc b pp (p@(Node pas pgcs):pcs) (I x :* xs)
= grnfpP ci (acc `seq` step) False pp pcs xs
where
step | WI{} <- pas = ()
| TR{} <- pas = if elem tx treps then thestep else ()
#if USE_WW_DEEPSEQ
| TI{} <- pas = if elem tx treps then () else rnf x
| TW{} <- pas = if elem tx treps then rnf x else ()
#else
| TI{} <- pas = if elem tx treps then () else rnfn 999999 x
#endif
| otherwise = thestep
where
as = getPatNodeAttrs pas
treps = typeConstraints as
thestep = rnfp p x
tx | (Constructor n) <- ci = n
| (Infix n _ _) <- ci = n
| (Record n _) <- ci = n
grnfpP ci acc b pp ps xs
= error $ "*6* "++show b++" "++show pp++" "++show ps++" "++show (lenxs xs)
grnfpP_validate :: forall xs.
(
All NFDataP xs
#if INCLUDE_SHOW_INSTANCES
, All Show xs
#endif
) =>
Bool
-> PatNode
-> [Pattern]
-> String
-> NP I xs
-> (Bool, Maybe String)
grnfpP_validate True pp@(TR as) ps tx xss
| b = grnfpP_validate' True pp ps tx xss
| otherwise = (False,Just $ "<generic> TR ctor name constraint mismatch (not "++tx++")")
where b = head cnames == tx
cnames = typeConstraints as
#if USE_WW_DEEPSEQ
grnfpP_validate True pp@(TW as) ps tx xss
| b = grnfpP_validate' True pp ps tx xss
| otherwise = (False,Just $ "<generic> TW ctor [should be type!] name constraint mismatch (not "++tx++")")
where b = head cnames == tx
cnames = typeConstraints as
#endif
grnfpP_validate True pp@(TI as) ps tx xss
| b = grnfpP_validate' True pp ps tx xss
| otherwise = (False,Just $ "<generic> TI ctor [should be type!] name constraint mismatch (not "++tx++")")
where b = head cnames == tx
cnames = typeConstraints as
grnfpP_validate b pp ps tx xss
= grnfpP_validate' b pp ps tx xss
grnfpP_validate' :: forall xs.
(
All NFDataP xs
#if INCLUDE_SHOW_INSTANCES
, All Show xs
#endif
) =>
Bool
-> PatNode
-> [Pattern]
-> String
-> NP I xs
-> (Bool, Maybe String)
grnfpP_validate' True (WI as) [] tx xss = (True,Nothing)
grnfpP_validate' True (WS as) [] tx xss = (True,Nothing)
grnfpP_validate' True (WN as) [] tx xss = (True,Nothing)
grnfpP_validate' True (WW as) [] tx xss = (True,Nothing)
grnfpP_validate' True pp ps tx xss
| WS{} <- pp = if lenps > 0 then (False,Nothing) else (True,Nothing)
| b = (True,Nothing)
| otherwise = (False,Just "<generic> arity mismatch #1")
where
b = lenps == lenxs xss
lenps = length ps
grnfpP_validate' False pp [] tx Nil
= (True,Nothing)
grnfpP_validate' False pp (p:pcs) tx (I x :* xs)
= grnfpP_validate False pp pcs tx xs
grnfpP_validate' b pp ps tx xs
= error $ " &&& " ++ show b ++ " " ++ show pp ++ " " ++ show ps
lenxs :: NP I xs' -> Int
lenxs Nil = 0
lenxs (I x' :* xs') = 1 + lenxs xs'
lenxs _ = error "lenxs: unexpected"
#if 0
arity :: Data a => a -> Int
arity = length . gmapQ (const ())
#endif
patMatchFail'' :: String -> ()
patMatchFail'' msg
#if 0
= error "BOO!!!!"
#else
#if WARN_PATTERN_MATCH_FAILURE
= trace ("GNFDataP: warning: pattern match failure (" ++ msg ++ ")") $ ()
#else
= ()
#endif
#endif