{-# LANGUAGE RecordWildCards #-}
module Unison.NamesWithHistory
( diff,
push,
lookupHQType,
lookupHQType',
lookupHQTerm,
lookupHQTerm',
lookupRelativeHQType,
lookupRelativeHQType',
lookupRelativeHQTerm,
lookupRelativeHQTerm',
hasTermNamed,
hasTypeNamed,
typeName,
termNamesByLength,
longestTermName,
termName,
lookupHQPattern,
Diff (..),
SearchType (..),
)
where
import Data.List.Extra (nubOrd)
import Data.Map qualified as Map
import Data.Set qualified as Set
import Unison.ConstructorReference (ConstructorReference)
import Unison.ConstructorType qualified as CT
import Unison.HashQualified (HashQualified)
import Unison.HashQualified qualified as HQ
import Unison.HashQualifiedPrime qualified as HQ'
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.Names (Names (..))
import Unison.Names qualified as Names
import Unison.Prelude
import Unison.Reference as Reference
import Unison.Referent as Referent
import Unison.ShortHash (ShortHash)
import Unison.Util.List qualified as List
import Unison.Util.Relation (Relation)
import Unison.Util.Relation qualified as R
import Unison.Util.Relation qualified as Relation
data SearchType
= IncludeSuffixes
| ExactName
deriving (SearchType -> SearchType -> Bool
(SearchType -> SearchType -> Bool)
-> (SearchType -> SearchType -> Bool) -> Eq SearchType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SearchType -> SearchType -> Bool
== :: SearchType -> SearchType -> Bool
$c/= :: SearchType -> SearchType -> Bool
/= :: SearchType -> SearchType -> Bool
Eq, Eq SearchType
Eq SearchType =>
(SearchType -> SearchType -> Ordering)
-> (SearchType -> SearchType -> Bool)
-> (SearchType -> SearchType -> Bool)
-> (SearchType -> SearchType -> Bool)
-> (SearchType -> SearchType -> Bool)
-> (SearchType -> SearchType -> SearchType)
-> (SearchType -> SearchType -> SearchType)
-> Ord SearchType
SearchType -> SearchType -> Bool
SearchType -> SearchType -> Ordering
SearchType -> SearchType -> SearchType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SearchType -> SearchType -> Ordering
compare :: SearchType -> SearchType -> Ordering
$c< :: SearchType -> SearchType -> Bool
< :: SearchType -> SearchType -> Bool
$c<= :: SearchType -> SearchType -> Bool
<= :: SearchType -> SearchType -> Bool
$c> :: SearchType -> SearchType -> Bool
> :: SearchType -> SearchType -> Bool
$c>= :: SearchType -> SearchType -> Bool
>= :: SearchType -> SearchType -> Bool
$cmax :: SearchType -> SearchType -> SearchType
max :: SearchType -> SearchType -> SearchType
$cmin :: SearchType -> SearchType -> SearchType
min :: SearchType -> SearchType -> SearchType
Ord, Int -> SearchType -> ShowS
[SearchType] -> ShowS
SearchType -> String
(Int -> SearchType -> ShowS)
-> (SearchType -> String)
-> ([SearchType] -> ShowS)
-> Show SearchType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SearchType -> ShowS
showsPrec :: Int -> SearchType -> ShowS
$cshow :: SearchType -> String
show :: SearchType -> String
$cshowList :: [SearchType] -> ShowS
showList :: [SearchType] -> ShowS
Show)
diff :: Names -> Names -> Diff
diff :: Names -> Names -> Diff
diff Names
n1 Names
n2 = Names -> Names -> Names -> Diff
Diff Names
n1 Names
added Names
removed
where
added :: Names
added =
Relation Name Referent -> Relation Name Reference -> Names
Names
(Names -> Relation Name Referent
terms Names
n2 Relation Name Referent
-> Relation Name Referent -> Relation Name Referent
forall a b.
(Ord a, Ord b) =>
Relation a b -> Relation a b -> Relation a b
`R.difference` Names -> Relation Name Referent
terms Names
n1)
(Names -> Relation Name Reference
types Names
n2 Relation Name Reference
-> Relation Name Reference -> Relation Name Reference
forall a b.
(Ord a, Ord b) =>
Relation a b -> Relation a b -> Relation a b
`R.difference` Names -> Relation Name Reference
types Names
n1)
removed :: Names
removed =
Relation Name Referent -> Relation Name Reference -> Names
Names
(Names -> Relation Name Referent
terms Names
n1 Relation Name Referent
-> Relation Name Referent -> Relation Name Referent
forall a b.
(Ord a, Ord b) =>
Relation a b -> Relation a b -> Relation a b
`R.difference` Names -> Relation Name Referent
terms Names
n2)
(Names -> Relation Name Reference
types Names
n1 Relation Name Reference
-> Relation Name Reference -> Relation Name Reference
forall a b.
(Ord a, Ord b) =>
Relation a b -> Relation a b -> Relation a b
`R.difference` Names -> Relation Name Reference
types Names
n2)
data Diff = Diff
{ Diff -> Names
originalNames :: Names,
Diff -> Names
addedNames :: Names,
Diff -> Names
removedNames :: Names
}
deriving (Int -> Diff -> ShowS
[Diff] -> ShowS
Diff -> String
(Int -> Diff -> ShowS)
-> (Diff -> String) -> ([Diff] -> ShowS) -> Show Diff
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Diff -> ShowS
showsPrec :: Int -> Diff -> ShowS
$cshow :: Diff -> String
show :: Diff -> String
$cshowList :: [Diff] -> ShowS
showList :: [Diff] -> ShowS
Show)
push :: Names -> Names -> Names
push :: Names -> Names -> Names
push Names
n0 Names
ns = Names -> Names -> Names
unionLeft0 Names
n1 Names
ns
where
n1 :: Names
n1 = Names -> Names
suffixify0 Names
n0
unionLeft0 :: Names -> Names -> Names
unionLeft0 :: Names -> Names -> Names
unionLeft0 Names
n1 Names
n2 = Relation Name Referent -> Relation Name Reference -> Names
Names Relation Name Referent
terms' Relation Name Reference
types'
where
terms' :: Relation Name Referent
terms' = Names -> Relation Name Referent
terms Names
n1 Relation Name Referent
-> Relation Name Referent -> Relation Name Referent
forall a. Semigroup a => a -> a -> a
<> Set Name -> Relation Name Referent -> Relation Name Referent
forall a b. (Ord a, Ord b) => Set a -> Relation a b -> Relation a b
R.subtractDom (Relation Name Referent -> Set Name
forall a b. Relation a b -> Set a
R.dom (Relation Name Referent -> Set Name)
-> Relation Name Referent -> Set Name
forall a b. (a -> b) -> a -> b
$ Names -> Relation Name Referent
terms Names
n1) (Names -> Relation Name Referent
terms Names
n2)
types' :: Relation Name Reference
types' = Names -> Relation Name Reference
types Names
n1 Relation Name Reference
-> Relation Name Reference -> Relation Name Reference
forall a. Semigroup a => a -> a -> a
<> Set Name -> Relation Name Reference -> Relation Name Reference
forall a b. (Ord a, Ord b) => Set a -> Relation a b -> Relation a b
R.subtractDom (Relation Name Reference -> Set Name
forall a b. Relation a b -> Set a
R.dom (Relation Name Reference -> Set Name)
-> Relation Name Reference -> Set Name
forall a b. (a -> b) -> a -> b
$ Names -> Relation Name Reference
types Names
n1) (Names -> Relation Name Reference
types Names
n2)
suffixify0 :: Names -> Names
suffixify0 :: Names -> Names
suffixify0 Names
ns = Names
ns Names -> Names -> Names
forall a. Semigroup a => a -> a -> a
<> Names
suffixNs
where
suffixNs :: Names
suffixNs = Relation Name Referent -> Relation Name Reference -> Names
Names ([(Name, Referent)] -> Relation Name Referent
forall a b. (Ord a, Ord b) => [(a, b)] -> Relation a b
R.fromList [(Name, Referent)]
uniqueTerms) ([(Name, Reference)] -> Relation Name Reference
forall a b. (Ord a, Ord b) => [(a, b)] -> Relation a b
R.fromList [(Name, Reference)]
uniqueTypes)
terms' :: Map Name [Referent]
terms' = [(Name, Referent)] -> Map Name [Referent]
forall (f :: * -> *) k v.
(Foldable f, Ord k) =>
f (k, v) -> Map k [v]
List.multimap [(Name
n, Referent
ref) | (Name
n0, Referent
ref) <- Relation Name Referent -> [(Name, Referent)]
forall a b. Relation a b -> [(a, b)]
R.toList (Names -> Relation Name Referent
terms Names
ns), Name
n <- Name -> [Name]
Name.suffixes Name
n0]
types' :: Map Name [Reference]
types' = [(Name, Reference)] -> Map Name [Reference]
forall (f :: * -> *) k v.
(Foldable f, Ord k) =>
f (k, v) -> Map k [v]
List.multimap [(Name
n, Reference
ref) | (Name
n0, Reference
ref) <- Relation Name Reference -> [(Name, Reference)]
forall a b. Relation a b -> [(a, b)]
R.toList (Names -> Relation Name Reference
types Names
ns), Name
n <- Name -> [Name]
Name.suffixes Name
n0]
uniqueTerms :: [(Name, Referent)]
uniqueTerms = [(Name
n, Referent
ref) | (Name
n, [Referent] -> [Referent]
forall a. Ord a => [a] -> [a]
nubOrd -> [Referent
ref]) <- Map Name [Referent] -> [(Name, [Referent])]
forall k a. Map k a -> [(k, a)]
Map.toList Map Name [Referent]
terms']
uniqueTypes :: [(Name, Reference)]
uniqueTypes = [(Name
n, Reference
ref) | (Name
n, [Reference] -> [Reference]
forall a. Ord a => [a] -> [a]
nubOrd -> [Reference
ref]) <- Map Name [Reference] -> [(Name, [Reference])]
forall k a. Map k a -> [(k, a)]
Map.toList Map Name [Reference]
types']
lookupRelativeHQType :: SearchType -> HashQualified Name -> Names -> Set TypeReference
lookupRelativeHQType :: SearchType -> HashQualified Name -> Names -> Set Reference
lookupRelativeHQType SearchType
searchType HashQualified Name
hq Names
ns =
let rs :: Set Reference
rs = SearchType -> HashQualified Name -> Names -> Set Reference
lookupHQType SearchType
searchType HashQualified Name
hq Names
ns
keep :: Reference -> Bool
keep Reference
r = (Name -> Bool) -> Set Name -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool
not (Bool -> Bool) -> (Name -> Bool) -> Name -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Bool
Name.isAbsolute) (Reference -> Relation Name Reference -> Set Name
forall b a. Ord b => b -> Relation a b -> Set a
R.lookupRan Reference
r (Names -> Relation Name Reference
Names.types Names
ns))
in case (Reference -> Bool) -> Set Reference -> Set Reference
forall a. (a -> Bool) -> Set a -> Set a
Set.filter Reference -> Bool
keep Set Reference
rs of
Set Reference
rs'
| Set Reference -> Bool
forall a. Set a -> Bool
Set.null Set Reference
rs' -> Set Reference
rs
| Bool
otherwise -> Set Reference
rs'
lookupRelativeHQType' :: SearchType -> HQ'.HashQualified Name -> Names -> Set TypeReference
lookupRelativeHQType' :: SearchType -> HashQualified Name -> Names -> Set Reference
lookupRelativeHQType' SearchType
searchType =
SearchType -> HashQualified Name -> Names -> Set Reference
lookupRelativeHQType SearchType
searchType (HashQualified Name -> Names -> Set Reference)
-> (HashQualified Name -> HashQualified Name)
-> HashQualified Name
-> Names
-> Set Reference
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashQualified Name -> HashQualified Name
forall n. HashQualified n -> HashQualified n
HQ'.toHQ
lookupHQType :: SearchType -> HashQualified Name -> Names -> Set TypeReference
lookupHQType :: SearchType -> HashQualified Name -> Names -> Set Reference
lookupHQType SearchType
searchType =
SearchType
-> (Names -> Relation Name Reference)
-> (ShortHash -> Reference -> Bool)
-> HashQualified Name
-> Names
-> Set Reference
forall r.
Ord r =>
SearchType
-> (Names -> Relation Name r)
-> (ShortHash -> r -> Bool)
-> HashQualified Name
-> Names
-> Set r
lookupHQRef SearchType
searchType Names -> Relation Name Reference
Names.types ShortHash -> Reference -> Bool
Reference.isPrefixOf
lookupHQType' :: SearchType -> HQ'.HashQualified Name -> Names -> Set TypeReference
lookupHQType' :: SearchType -> HashQualified Name -> Names -> Set Reference
lookupHQType' SearchType
searchType =
SearchType -> HashQualified Name -> Names -> Set Reference
lookupHQType SearchType
searchType (HashQualified Name -> Names -> Set Reference)
-> (HashQualified Name -> HashQualified Name)
-> HashQualified Name
-> Names
-> Set Reference
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashQualified Name -> HashQualified Name
forall n. HashQualified n -> HashQualified n
HQ'.toHQ
hasTermNamed :: SearchType -> Name -> Names -> Bool
hasTermNamed :: SearchType -> Name -> Names -> Bool
hasTermNamed SearchType
searchType Name
n Names
ns = Bool -> Bool
not (Set Referent -> Bool
forall a. Set a -> Bool
Set.null (Set Referent -> Bool) -> Set Referent -> Bool
forall a b. (a -> b) -> a -> b
$ SearchType -> HashQualified Name -> Names -> Set Referent
lookupHQTerm SearchType
searchType (Name -> HashQualified Name
forall n. n -> HashQualified n
HQ.NameOnly Name
n) Names
ns)
hasTypeNamed :: SearchType -> Name -> Names -> Bool
hasTypeNamed :: SearchType -> Name -> Names -> Bool
hasTypeNamed SearchType
searchType Name
n Names
ns = Bool -> Bool
not (Set Reference -> Bool
forall a. Set a -> Bool
Set.null (Set Reference -> Bool) -> Set Reference -> Bool
forall a b. (a -> b) -> a -> b
$ SearchType -> HashQualified Name -> Names -> Set Reference
lookupHQType SearchType
searchType (Name -> HashQualified Name
forall n. n -> HashQualified n
HQ.NameOnly Name
n) Names
ns)
lookupRelativeHQTerm :: SearchType -> HashQualified Name -> Names -> Set Referent
lookupRelativeHQTerm :: SearchType -> HashQualified Name -> Names -> Set Referent
lookupRelativeHQTerm SearchType
searchType HashQualified Name
hq Names
ns =
let rs :: Set Referent
rs = SearchType -> HashQualified Name -> Names -> Set Referent
lookupHQTerm SearchType
searchType HashQualified Name
hq Names
ns
keep :: Referent -> Bool
keep Referent
r = (Name -> Bool) -> Set Name -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool
not (Bool -> Bool) -> (Name -> Bool) -> Name -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Bool
Name.isAbsolute) (Referent -> Relation Name Referent -> Set Name
forall b a. Ord b => b -> Relation a b -> Set a
R.lookupRan Referent
r (Names -> Relation Name Referent
Names.terms Names
ns))
in case (Referent -> Bool) -> Set Referent -> Set Referent
forall a. (a -> Bool) -> Set a -> Set a
Set.filter Referent -> Bool
keep Set Referent
rs of
Set Referent
rs'
| Set Referent -> Bool
forall a. Set a -> Bool
Set.null Set Referent
rs' -> Set Referent
rs
| Bool
otherwise -> Set Referent
rs'
lookupRelativeHQTerm' :: SearchType -> HQ'.HashQualified Name -> Names -> Set Referent
lookupRelativeHQTerm' :: SearchType -> HashQualified Name -> Names -> Set Referent
lookupRelativeHQTerm' SearchType
searchType =
SearchType -> HashQualified Name -> Names -> Set Referent
lookupRelativeHQTerm SearchType
searchType (HashQualified Name -> Names -> Set Referent)
-> (HashQualified Name -> HashQualified Name)
-> HashQualified Name
-> Names
-> Set Referent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashQualified Name -> HashQualified Name
forall n. HashQualified n -> HashQualified n
HQ'.toHQ
lookupHQTerm :: SearchType -> HashQualified Name -> Names -> Set Referent
lookupHQTerm :: SearchType -> HashQualified Name -> Names -> Set Referent
lookupHQTerm SearchType
searchType =
SearchType
-> (Names -> Relation Name Referent)
-> (ShortHash -> Referent -> Bool)
-> HashQualified Name
-> Names
-> Set Referent
forall r.
Ord r =>
SearchType
-> (Names -> Relation Name r)
-> (ShortHash -> r -> Bool)
-> HashQualified Name
-> Names
-> Set r
lookupHQRef SearchType
searchType Names -> Relation Name Referent
Names.terms ShortHash -> Referent -> Bool
Referent.isPrefixOf
lookupHQTerm' :: SearchType -> HQ'.HashQualified Name -> Names -> Set Referent
lookupHQTerm' :: SearchType -> HashQualified Name -> Names -> Set Referent
lookupHQTerm' SearchType
searchType =
SearchType -> HashQualified Name -> Names -> Set Referent
lookupHQTerm SearchType
searchType (HashQualified Name -> Names -> Set Referent)
-> (HashQualified Name -> HashQualified Name)
-> HashQualified Name
-> Names
-> Set Referent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashQualified Name -> HashQualified Name
forall n. HashQualified n -> HashQualified n
HQ'.toHQ
lookupHQRef ::
forall r.
(Ord r) =>
SearchType ->
(Names -> Relation Name r) ->
(ShortHash -> r -> Bool) ->
HashQualified Name ->
Names ->
Set r
lookupHQRef :: forall r.
Ord r =>
SearchType
-> (Names -> Relation Name r)
-> (ShortHash -> r -> Bool)
-> HashQualified Name
-> Names
-> Set r
lookupHQRef SearchType
searchType Names -> Relation Name r
which ShortHash -> r -> Bool
isPrefixOf HashQualified Name
hq Names
names =
case HashQualified Name
hq of
HQ.NameOnly Name
n -> Name -> Relation Name r -> Set r
doSearch Name
n Relation Name r
refs
HQ.HashQualified Name
n ShortHash
sh -> Relation Name r -> Set r
matches Relation Name r
refs
where
matches :: Relation Name r -> Set r
matches :: Relation Name r -> Set r
matches Relation Name r
ns =
(r -> Bool) -> Set r -> Set r
forall a. (a -> Bool) -> Set a -> Set a
Set.filter (ShortHash -> r -> Bool
isPrefixOf ShortHash
sh) (Name -> Relation Name r -> Set r
doSearch Name
n Relation Name r
ns)
HQ.HashOnly ShortHash
sh -> Relation Name r -> Set r
matches Relation Name r
refs
where
matches :: Relation Name r -> Set r
matches :: Relation Name r -> Set r
matches Relation Name r
ns =
(r -> Bool) -> Set r -> Set r
forall a. (a -> Bool) -> Set a -> Set a
Set.filter (ShortHash -> r -> Bool
isPrefixOf ShortHash
sh) (Relation Name r -> Set r
forall a b. Relation a b -> Set b
R.ran Relation Name r
ns)
where
doSearch :: Name -> Relation Name r -> Set r
doSearch = case SearchType
searchType of
SearchType
IncludeSuffixes -> Name -> Relation Name r -> Set r
forall r. Ord r => Name -> Relation Name r -> Set r
Name.searchByRankedSuffix
SearchType
ExactName -> Name -> Relation Name r -> Set r
forall a b. Ord a => a -> Relation a b -> Set b
Relation.lookupDom
refs :: Relation Name r
refs = Names -> Relation Name r
which Names
names
typeName :: Int -> Reference -> Names -> Set (HQ'.HashQualified Name)
typeName :: Int -> Reference -> Names -> Set (HashQualified Name)
typeName Int
length Reference
r Names
names =
(Name -> HashQualified Name)
-> Set Name -> Set (HashQualified Name)
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map
(\Name
n -> if Name -> Bool
isConflicted Name
n then Name -> HashQualified Name
hq Name
n else Name -> HashQualified Name
forall n. n -> HashQualified n
HQ'.fromName Name
n)
(Reference -> Relation Name Reference -> Set Name
forall b a. Ord b => b -> Relation a b -> Set a
R.lookupRan Reference
r (Relation Name Reference -> Set Name)
-> (Names -> Relation Name Reference) -> Names -> Set Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Names -> Relation Name Reference
Names.types (Names -> Set Name) -> Names -> Set Name
forall a b. (a -> b) -> a -> b
$ Names
names)
where
hq :: Name -> HashQualified Name
hq Name
n = Int -> HashQualified Name -> HashQualified Name
forall n. Int -> HashQualified n -> HashQualified n
HQ'.take Int
length (Name -> Reference -> HashQualified Name
forall n. n -> Reference -> HashQualified n
HQ'.fromNamedReference Name
n Reference
r)
isConflicted :: Name -> Bool
isConflicted Name
n = Name -> Relation Name Reference -> Bool
forall a b. Ord a => a -> Relation a b -> Bool
R.manyDom Name
n (Names -> Relation Name Reference
Names.types Names
names)
termNamesByLength :: Int -> Referent -> Names -> [HQ'.HashQualified Name]
termNamesByLength :: Int -> Referent -> Names -> [HashQualified Name]
termNamesByLength Int
length Referent
r Names
ns =
(HashQualified Name -> Int)
-> [HashQualified Name] -> [HashQualified Name]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn HashQualified Name -> Int
len (Set (HashQualified Name) -> [HashQualified Name]
forall a. Set a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Set (HashQualified Name) -> [HashQualified Name])
-> Set (HashQualified Name) -> [HashQualified Name]
forall a b. (a -> b) -> a -> b
$ Int -> Referent -> Names -> Set (HashQualified Name)
termName Int
length Referent
r Names
ns)
where
len :: HashQualified Name -> Int
len (HQ'.NameOnly Name
n) = Name -> Int
Name.countSegments Name
n
len (HQ'.HashQualified Name
n ShortHash
_) = Name -> Int
Name.countSegments Name
n
longestTermName :: Int -> Referent -> Names -> HQ.HashQualified Name
longestTermName :: Int -> Referent -> Names -> HashQualified Name
longestTermName Int
length Referent
r Names
ns =
case [HashQualified Name] -> [HashQualified Name]
forall a. [a] -> [a]
reverse (Int -> Referent -> Names -> [HashQualified Name]
termNamesByLength Int
length Referent
r Names
ns) of
[] -> Int -> HashQualified Name -> HashQualified Name
forall n. Int -> HashQualified n -> HashQualified n
HQ.take Int
length (Referent -> HashQualified Name
HQ.fromReferent Referent
r)
(HashQualified Name
h : [HashQualified Name]
_) -> HashQualified Name -> HashQualified Name
forall n. HashQualified n -> HashQualified n
HQ'.toHQ HashQualified Name
h
termName :: Int -> Referent -> Names -> Set (HQ'.HashQualified Name)
termName :: Int -> Referent -> Names -> Set (HashQualified Name)
termName Int
length Referent
r Names
names =
(Name -> HashQualified Name)
-> Set Name -> Set (HashQualified Name)
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map
(\Name
n -> if Name -> Bool
isConflicted Name
n then Name -> HashQualified Name
hq Name
n else Name -> HashQualified Name
forall n. n -> HashQualified n
HQ'.fromName Name
n)
(Referent -> Relation Name Referent -> Set Name
forall b a. Ord b => b -> Relation a b -> Set a
R.lookupRan Referent
r (Relation Name Referent -> Set Name)
-> (Names -> Relation Name Referent) -> Names -> Set Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Names -> Relation Name Referent
Names.terms (Names -> Set Name) -> Names -> Set Name
forall a b. (a -> b) -> a -> b
$ Names
names)
where
hq :: Name -> HashQualified Name
hq Name
n = Int -> HashQualified Name -> HashQualified Name
forall n. Int -> HashQualified n -> HashQualified n
HQ'.take Int
length (Name -> Referent -> HashQualified Name
forall n. n -> Referent -> HashQualified n
HQ'.fromNamedReferent Name
n Referent
r)
isConflicted :: Name -> Bool
isConflicted Name
n = Name -> Relation Name Referent -> Bool
forall a b. Ord a => a -> Relation a b -> Bool
R.manyDom Name
n (Names -> Relation Name Referent
Names.terms Names
names)
lookupHQPattern ::
SearchType ->
HQ.HashQualified Name ->
CT.ConstructorType ->
Names ->
Set ConstructorReference
lookupHQPattern :: SearchType
-> HashQualified Name
-> ConstructorType
-> Names
-> Set ConstructorReference
lookupHQPattern SearchType
searchType HashQualified Name
hq ConstructorType
ctt Names
names =
[ConstructorReference] -> Set ConstructorReference
forall a. Ord a => [a] -> Set a
Set.fromList
[ ConstructorReference
r
| Referent.Con ConstructorReference
r ConstructorType
ct <- Set Referent -> [Referent]
forall a. Set a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Set Referent -> [Referent]) -> Set Referent -> [Referent]
forall a b. (a -> b) -> a -> b
$ SearchType -> HashQualified Name -> Names -> Set Referent
lookupHQTerm SearchType
searchType HashQualified Name
hq Names
names,
ConstructorType
ct ConstructorType -> ConstructorType -> Bool
forall a. Eq a => a -> a -> Bool
== ConstructorType
ctt
]