{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Development.IDE.Types.KnownTargets (KnownTargets, Target(..), toKnownFiles) where
import Control.DeepSeq
import Data.Hashable
import Data.HashMap.Strict
import qualified Data.HashMap.Strict as HMap
import Data.HashSet
import qualified Data.HashSet as HSet
import Development.IDE.GHC.Compat (ModuleName)
import Development.IDE.GHC.Orphans ()
import Development.IDE.Types.Location
import GHC.Generics
type KnownTargets = HashMap Target (HashSet NormalizedFilePath)
data Target = TargetModule ModuleName | TargetFile NormalizedFilePath
deriving ( Target -> Target -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Target -> Target -> Bool
$c/= :: Target -> Target -> Bool
== :: Target -> Target -> Bool
$c== :: Target -> Target -> Bool
Eq, forall x. Rep Target x -> Target
forall x. Target -> Rep Target x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Target x -> Target
$cfrom :: forall x. Target -> Rep Target x
Generic, Int -> Target -> ShowS
[Target] -> ShowS
Target -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Target] -> ShowS
$cshowList :: [Target] -> ShowS
show :: Target -> String
$cshow :: Target -> String
showsPrec :: Int -> Target -> ShowS
$cshowsPrec :: Int -> Target -> ShowS
Show )
deriving anyclass (Eq Target
Int -> Target -> Int
Target -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Target -> Int
$chash :: Target -> Int
hashWithSalt :: Int -> Target -> Int
$chashWithSalt :: Int -> Target -> Int
Hashable, Target -> ()
forall a. (a -> ()) -> NFData a
rnf :: Target -> ()
$crnf :: Target -> ()
NFData)
toKnownFiles :: KnownTargets -> HashSet NormalizedFilePath
toKnownFiles :: KnownTargets -> HashSet NormalizedFilePath
toKnownFiles = forall a. (Eq a, Hashable a) => [HashSet a] -> HashSet a
HSet.unions forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. HashMap k v -> [v]
HMap.elems