-- Unreachability

module Yhc.Core.Unreachable (
-- *Unreachability
-- $unreach
   coreUnreachableFuncs
  ,coreUnreachableDatas) where

import Yhc.Core
import qualified Data.Set as S

-- $unreach 'Yhc.Core.Reachable.coreReachable' fails if any of the
-- function\/constructor calls cannot be matched by a function defined in the
-- linked Core. The two functions provided in this module help detect
-- missing (in other words, unreachable) functions to give user alerts,
-- or to automatically create some missing items where possible.

-- |Determine missing (unreachable) functions.
--  /All functions called/ except /All functions defined/


coreUnreachableFuncs :: Core -> [CoreFuncName]

coreUnreachableFuncs core =
  let cfuns = coreFuncs core
      calledBy fn = [f | CoreFun f <- universeExpr fn]
      called = foldl (flip S.insert) S.empty (concat $ map calledBy cfuns)
      defined = S.fromList (map coreFuncName cfuns)
  in  S.toList (called S.\\ defined)

-- |Determine missing (unreachable) data constructors.
-- /All ctors called\/used in patterns/ except /All ctors defined/

coreUnreachableDatas :: Core -> [CoreCtorName]

coreUnreachableDatas core =
  let called = S.fromList $ [x | CoreCon x <- universeExpr core] ++
              [x | CoreCase _ alts <- universeExpr core, (PatCon x _,_) <- alts]
      defined = S.fromList $ map coreCtorName $ 
                             concat $ map coreDataCtors $ coreDatas core
  in S.toList (called S.\\ defined)