| Copyright | 2021 Dominik Schrempf | 
|---|---|
| License | GPL-3.0-or-later | 
| Maintainer | dominik.schrempf@gmail.com | 
| Stability | unstable | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
ELynx.Topology.Rooted
Description
Creation date: Sat Jul 11 10:28:28 2020.
A rooted Topology differs from a classical rooted rose Tree in
 that it does not have internal node labels. The leaves have labels.
For rooted trees with branch labels, see ELynx.Tree.Rooted.
Synopsis
- data Topology a
- type Forest a = NonEmpty (Topology a)
- fromRoseTree :: Tree a -> Topology a
- fromBranchLabelTree :: Tree e a -> Topology a
- toBranchLabelTreeWith :: e -> a -> Topology a -> Tree e a
- leaves :: Topology a -> [a]
- duplicateLeaves :: Ord a => Topology a -> Bool
- setLeaves :: Traversable t => [b] -> t a -> Maybe (t b)
- identify :: Traversable t => t a -> t Int
- degree :: Topology a -> Int
- depth :: Topology a -> Int
- prune :: Topology a -> Topology a
- dropLeavesWith :: (a -> Bool) -> Topology a -> Maybe (Topology a)
- zipTopologiesWith :: (a1 -> a2 -> a) -> Topology a1 -> Topology a2 -> Maybe (Topology a)
- zipTopologies :: Topology a1 -> Topology a2 -> Maybe (Topology (a1, a2))
Data type
Rooted topologies with leaf labels.
Instances
| Foldable Topology Source # | |
| Defined in ELynx.Topology.Rooted Methods fold :: Monoid m => Topology m -> m # foldMap :: Monoid m => (a -> m) -> Topology a -> m # foldMap' :: Monoid m => (a -> m) -> Topology a -> m # foldr :: (a -> b -> b) -> b -> Topology a -> b # foldr' :: (a -> b -> b) -> b -> Topology a -> b # foldl :: (b -> a -> b) -> b -> Topology a -> b # foldl' :: (b -> a -> b) -> b -> Topology a -> b # foldr1 :: (a -> a -> a) -> Topology a -> a # foldl1 :: (a -> a -> a) -> Topology a -> a # elem :: Eq a => a -> Topology a -> Bool # maximum :: Ord a => Topology a -> a # minimum :: Ord a => Topology a -> a # | |
| Traversable Topology Source # | |
| Applicative Topology Source # | |
| Functor Topology Source # | |
| Monad Topology Source # | |
| FromJSON a => FromJSON (Topology a) Source # | |
| ToJSON a => ToJSON (Topology a) Source # | |
| Defined in ELynx.Topology.Rooted | |
| Data a => Data (Topology a) Source # | |
| Defined in ELynx.Topology.Rooted Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Topology a -> c (Topology a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Topology a) # toConstr :: Topology a -> Constr # dataTypeOf :: Topology a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Topology a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Topology a)) # gmapT :: (forall b. Data b => b -> b) -> Topology a -> Topology a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Topology a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Topology a -> r # gmapQ :: (forall d. Data d => d -> u) -> Topology a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Topology a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Topology a -> m (Topology a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Topology a -> m (Topology a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Topology a -> m (Topology a) # | |
| Generic (Topology a) Source # | |
| Read a => Read (Topology a) Source # | |
| Show a => Show (Topology a) Source # | |
| NFData a => NFData (Topology a) Source # | |
| Defined in ELynx.Topology.Rooted | |
| Eq a => Eq (Topology a) Source # | |
| type Rep (Topology a) Source # | |
| Defined in ELynx.Topology.Rooted type Rep (Topology a) = D1 ('MetaData "Topology" "ELynx.Topology.Rooted" "elynx-tree-0.7.2.0-FugeR2xtEP11xtp9Btivbd" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "forest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Forest a))) :+: C1 ('MetaCons "Leaf" 'PrefixI 'True) (S1 ('MetaSel ('Just "label") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |
fromRoseTree :: Tree a -> Topology a Source #
Convert a rooted rose tree to a rooted topology. Internal node labels are lost.
fromBranchLabelTree :: Tree e a -> Topology a Source #
Convert a rooted, branch-label tree to a rooted topology. Branch labels and internal node labels are lost.
toBranchLabelTreeWith :: e -> a -> Topology a -> Tree e a Source #
Convert a rooted topology to a rooted, branch-label tree. Use the given node label at internal nodes.
Access leaves, branches and labels
setLeaves :: Traversable t => [b] -> t a -> Maybe (t b) Source #
Set leaf labels in pre-order.
Return Nothing if the provided list of leaf labels is too short.
identify :: Traversable t => t a -> t Int Source #
Label the leaves in pre-order with unique indices starting at 0.
Structure
dropLeavesWith :: (a -> Bool) -> Topology a -> Maybe (Topology a) Source #
Drop leaves satisfying predicate.
See dropNodesWith.
zipTopologiesWith :: (a1 -> a2 -> a) -> Topology a1 -> Topology a2 -> Maybe (Topology a) Source #
Zip leaves of two equal topologies.
See zipTreesWith.
zipTopologies :: Topology a1 -> Topology a2 -> Maybe (Topology (a1, a2)) Source #
See zipTopologiesWith.