Maintainer | Toshio Ito <debug.ito@gmail.com> |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type LinkSampleUnifier n na fla sla = SnapshotNode n na -> SnapshotNode n na -> [LinkSample n fla] -> WriterLoggingM [LinkSample n sla]
- data LinkSample n la = LinkSample {
- lsSubjectNode :: n
- lsTargetNode :: n
- lsLinkState :: LinkState
- lsTimestamp :: Timestamp
- lsLinkAttributes :: la
- type LinkSampleID n = Pair n
- linkSampleId :: LinkSample n la -> LinkSampleID n
- toLinkSamples :: FoundNode n na la -> [LinkSample n la]
- unifyToOne :: (Eq n, Show n) => LinkSampleUnifier n na la la
- unifyToMany :: (Eq n, Show n, Ord lsid) => (LinkSample n fla -> lsid) -> LinkSampleUnifier n na fla fla
- unifyStd :: (Eq n, Show n, Ord lsid) => UnifyStdConfig n na fla sla lsid -> LinkSampleUnifier n na fla sla
- data UnifyStdConfig n na fla sla lsid = UnifyStdConfig {
- makeLinkSubId :: LinkSample n fla -> lsid
- mergeSamples :: [LinkSample n fla] -> [LinkSample n fla] -> Maybe (LinkSample n sla)
- negatesLinkSample :: SnapshotNode n na -> LinkSample n sla -> Bool
- defUnifyStdConfig :: Eq n => UnifyStdConfig n na fla fla ()
- latestLinkSample :: [LinkSample n la] -> Maybe (LinkSample n la)
- defNegatesLinkSample :: Eq n => SnapshotNode n na -> LinkSample n la -> Bool
Types
type LinkSampleUnifier n na fla sla = SnapshotNode n na -> SnapshotNode n na -> [LinkSample n fla] -> WriterLoggingM [LinkSample n sla] Source #
Function to unify LinkSample
s collected for the given pair of
nodes and return LinkSample
per physical link. The returned
LinkSample
s will be directly converted to SnapshotLink
s in the
snapshot graph.
This function has a number of important roles during construction of the snapshot graph.
- Because a link can be observed from both of its end nodes, there
can be multiple
LinkSample
s for one physical link. This function is supposed to return one reasonable link sample for the physical link from those input link samples. - There can be multiple physical links for a given pair of nodes,
but the
Spider
has no way to distinguish them. So, this function is supposed to distinguishLinkSample
s for different physical links, and return one or moreLinkSample
s, each of which corresponds to a physical link. - Sometimes a link is found by one end node but not found by the
other end node. Should
Spider
treats the link is available or not? This function is supposed to answer that question by returning non-empty result (if the link is available) or empty result (if the link is not available.) - Sometimes it is natural to have different data models of link
attributes for
FoundLink
s (fla
) and forSnapshotLink
s (sla
). For example, when you want to combine link attributes obtained from both of the end nodes to make the link attributes ofSnapshotLink
. This function is supposed to convert the link attribute type.
data LinkSample n la Source #
LinkSample
is an intermediate type between
FoundLink
and
SnapshotLink
. LinkSample
s are collected from
the history graph, and are unified into
SnapshotLink
s.
LinkSample | |
|
Instances
(Eq n, Eq la) => Eq (LinkSample n la) Source # | |
Defined in NetSpider.Unify (==) :: LinkSample n la -> LinkSample n la -> Bool # (/=) :: LinkSample n la -> LinkSample n la -> Bool # | |
(Ord n, Ord la) => Ord (LinkSample n la) Source # | |
Defined in NetSpider.Unify compare :: LinkSample n la -> LinkSample n la -> Ordering # (<) :: LinkSample n la -> LinkSample n la -> Bool # (<=) :: LinkSample n la -> LinkSample n la -> Bool # (>) :: LinkSample n la -> LinkSample n la -> Bool # (>=) :: LinkSample n la -> LinkSample n la -> Bool # max :: LinkSample n la -> LinkSample n la -> LinkSample n la # min :: LinkSample n la -> LinkSample n la -> LinkSample n la # | |
(Show n, Show la) => Show (LinkSample n la) Source # | |
Defined in NetSpider.Unify showsPrec :: Int -> LinkSample n la -> ShowS # show :: LinkSample n la -> String # showList :: [LinkSample n la] -> ShowS # |
type LinkSampleID n = Pair n Source #
Link ID of the LinkSample
. It's the Pair
of lsSubjectNode
and lsTargetNode
.
linkSampleId :: LinkSample n la -> LinkSampleID n Source #
Get LinkSampleID
of the LinkSample
.
toLinkSamples :: FoundNode n na la -> [LinkSample n la] Source #
Make LinkSample
s from FoundLink
s in FoundNode
.
Since: 0.4.2.0
Standard unifiers
unifyToOne :: (Eq n, Show n) => LinkSampleUnifier n na la la Source #
Unify LinkSample
s to one. This is the sensible unifier if there
is at most one physical link for a given pair of nodes.
:: (Eq n, Show n, Ord lsid) | |
=> (LinkSample n fla -> lsid) | Getter of the link sub-ID |
-> LinkSampleUnifier n na fla fla |
Unify LinkSample
s to possibly multiple samples. The input
samples are partitioned to groups based on the link sub-ID, defined
by the given getter function. Each group represents one of the
final samples.
unifyStd :: (Eq n, Show n, Ord lsid) => UnifyStdConfig n na fla sla lsid -> LinkSampleUnifier n na fla sla Source #
The standard unifier. This unifier does the following.
- It partitions
LinkSample
s based on their link sub-IDs. The link sub-ID is defined bymakeLinkSubId
function. Each link sub-ID corresponds to a physical link. - For each partition,
LinkSample
s are merged to one usingmergeSamples
function. - After merge, the link is checked against its end nodes. If
negatesLinkSample
returnsTrue
for either of the end nodes, the link is removed from the final result.
data UnifyStdConfig n na fla sla lsid Source #
UnifyStdConfig | |
|
defUnifyStdConfig :: Eq n => UnifyStdConfig n na fla fla () Source #
Default of UnifyStdConfig
.
Building blocks
latestLinkSample :: [LinkSample n la] -> Maybe (LinkSample n la) Source #
Get the LinkSample
that has the latest (biggest) timestamp.
defNegatesLinkSample :: Eq n => SnapshotNode n na -> LinkSample n la -> Bool Source #
Default of negatesLinkSample
. This function returns True
if
all of the following conditions are met.
- The
SnapshotNode
hasnodeTimestamp
. - The
nodeTimestamp
is greater (newer) than the link's timestamp. - The
lsSubjectNode
is not the node ID of theSnapshotNode
.
If the above conditions are met, it implies that the LinkSample
is found by the other end node, but the given SnapshotNode
does
not find it. This is possibly because the link has just
disappeared, so the link should be negated.