| Safe Haskell | None | 
|---|
LogicGrowsOnTrees.Location
Description
- class MonadPlus m => MonadLocatable m  where- getLocation :: m Location
 
- data Location
- data Solution α = Solution {}
- newtype  LocatableT m α = LocatableT {- unwrapLocatableT :: ReaderT Location m α
 
- type LocatableTree = LocatableTreeT Identity
- type LocatableTreeIO = LocatableTreeT IO
- newtype  LocatableTreeT m α = LocatableTreeT {- unwrapLocatableTreeT :: LocatableT (TreeT m) α
 
- applyCheckpointCursorToLocation :: CheckpointCursor -> Location -> Location
- applyContextToLocation :: Context m α -> Location -> Location
- applyPathToLocation :: Path -> Location -> Location
- branchingFromLocation :: Location -> [BranchChoice]
- labelFromBranching :: Foldable t => t BranchChoice -> Location
- labelFromContext :: Context m α -> Location
- labelFromPath :: Path -> Location
- leftBranchOf :: Location -> Location
- locationTransformerForBranchChoice :: BranchChoice -> Location -> Location
- normalizeLocatableTree :: LocatableTree α -> Tree α
- normalizeLocatableTreeT :: LocatableTreeT m α -> TreeT m α
- rightBranchOf :: Location -> Location
- rootLocation :: Location
- runLocatableT :: LocatableT m α -> m α
- sendTreeDownLocation :: Location -> Tree α -> Tree α
- sendTreeTDownLocation :: Monad m => Location -> TreeT m α -> m (TreeT m α)
- solutionsToMap :: Foldable t => t (Solution α) -> Map Location α
- exploreLocatableTree :: Monoid α => LocatableTree α -> α
- exploreLocatableTreeT :: (Monoid α, Monad m) => LocatableTreeT m α -> m α
- exploreLocatableTreeTAndIgnoreResults :: Monad m => LocatableTreeT m α -> m ()
- exploreTreeWithLocations :: Tree α -> [Solution α]
- exploreTreeTWithLocations :: Monad m => TreeT m α -> m [Solution α]
- exploreTreeWithLocationsStartingAt :: Location -> Tree α -> [Solution α]
- exploreTreeTWithLocationsStartingAt :: Monad m => Location -> TreeT m α -> m [Solution α]
- exploreLocatableTreeUntilFirst :: LocatableTree α -> Maybe α
- exploreLocatableTreeUntilFirstT :: Monad m => LocatableTreeT m α -> m (Maybe α)
- exploreTreeUntilFirstWithLocation :: Tree α -> Maybe (Solution α)
- exploreTreeTUntilFirstWithLocation :: Monad m => TreeT m α -> m (Maybe (Solution α))
- exploreTreeUntilFirstWithLocationStartingAt :: Location -> Tree α -> Maybe (Solution α)
- exploreTreeTUntilFirstWithLocationStartingAt :: Monad m => Location -> TreeT m α -> m (Maybe (Solution α))
Type-classes
class MonadPlus m => MonadLocatable m whereSource
The class MonadLocatable allows you to get your current location within a tree. 
Methods
Instances
| Monad m => MonadLocatable (LocatableTreeT m) | |
| MonadPlus m => MonadLocatable (LocatableT m) | 
Types
A Location identifies a location in a tree;  unlike Path it only
    contains information about the list of branches that have been taken, and
    not information about the cached values encounted along the way.
Instances
| Eq Location | |
| Ord Location | The  | 
| Show Location | |
| Monoid Location | The  | 
A Solution is a result tagged with the location of the leaf at which it
    was found.
Constructors
| Solution | |
| Fields 
 | |
newtype LocatableT m α Source
LocatableT is a monad transformer that allows you to take any MonadPlus
    and add to it the ability to tell where you are in the tree created by the
    mpluss.
Constructors
| LocatableT | |
| Fields 
 | |
Instances
| MonadTrans LocatableT | |
| Monad m => Monad (LocatableT m) | |
| Functor m => Functor (LocatableT m) | |
| MonadPlus m => MonadPlus (LocatableT m) | |
| Applicative m => Applicative (LocatableT m) | |
| (Alternative m, Monad m) => Alternative (LocatableT m) | |
| MonadIO m => MonadIO (LocatableT m) | |
| MonadExplorableTrans m => MonadExplorableTrans (LocatableT m) | |
| MonadPlus m => MonadLocatable (LocatableT m) | |
| MonadPlus m => Monoid (LocatableT m α) | 
type LocatableTree = LocatableTreeT IdentitySource
A Tree augmented with the ability to get the current location 
type LocatableTreeIO = LocatableTreeT IOSource
Like LocatableTree, but running in the IO monad. 
newtype LocatableTreeT m α Source
Like LocatableTree, but running in an arbitrary monad. 
Constructors
| LocatableTreeT | |
| Fields 
 | |
Instances
| MonadTrans LocatableTreeT | |
| Monad m => Monad (LocatableTreeT m) | |
| Monad m => Functor (LocatableTreeT m) | |
| Monad m => MonadPlus (LocatableTreeT m) | |
| Monad m => Applicative (LocatableTreeT m) | |
| Monad m => Alternative (LocatableTreeT m) | |
| MonadIO m => MonadIO (LocatableTreeT m) | |
| Monad m => MonadExplorableTrans (LocatableTreeT m) | |
| Monad m => MonadLocatable (LocatableTreeT m) | |
| Monad m => Monoid (LocatableTreeT m α) | 
Utility functions
applyCheckpointCursorToLocationSource
Arguments
| :: CheckpointCursor | a path within the subtree | 
| -> Location | the location of the subtree | 
| -> Location | the location within the full tree obtained by following the path to the subtree and then the path indicated by the checkpoint cursor | 
Append the path indicated by a checkpoint cursor to the given location's path.
Arguments
| :: Context m α | the path within the subtree | 
| -> Location | the location of the subtree | 
| -> Location | the location within the full tree obtained by following the path to the subtree and then the path indicated by the context | 
Append the path indicated by a context to the given location's path.
Arguments
| :: Path | a path within the subtree | 
| -> Location | the location of the subtree | 
| -> Location | the location within the full tree obtained by following the path to the subtree and then the given path | 
Append a path to a location's path.
branchingFromLocation :: Location -> [BranchChoice]Source
Converts a location to a list of branch choices.
labelFromBranching :: Foldable t => t BranchChoice -> LocationSource
Converts a list (or other Foldable) of branch choices to a location. 
labelFromContext :: Context m α -> LocationSource
labelFromPath :: Path -> LocationSource
leftBranchOf :: Location -> LocationSource
Returns the Location at the left branch of the given location. 
locationTransformerForBranchChoice :: BranchChoice -> Location -> LocationSource
Convenience function takes a branch choice and returns a location transformer that appends the branch choice to the given location.
normalizeLocatableTree :: LocatableTree α -> Tree αSource
Converts a LocatableTree to a Tree. 
normalizeLocatableTreeT :: LocatableTreeT m α -> TreeT m αSource
Converts a LocatableTreeT to a TreeT. 
rightBranchOf :: Location -> LocationSource
Returns the Location at the right branch of the given location. 
rootLocation :: LocationSource
The location at the root of the tree.
runLocatableT :: LocatableT m α -> m αSource
Runs a LocatableT to obtain the nested monad. 
sendTreeDownLocation :: Location -> Tree α -> Tree αSource
Walks down a Tree to the subtree at the given Location. This function is
    analogous to sendTreeDownPath, and shares the
    same caveats.
sendTreeTDownLocation :: Monad m => Location -> TreeT m α -> m (TreeT m α)Source
Like sendTreeDownLocation, but for impure trees. 
Exploration functions
exploreLocatableTree :: Monoid α => LocatableTree α -> αSource
Explore all the nodes in a LocatableTree and sum over all the results in the
    leaves.
exploreLocatableTreeT :: (Monoid α, Monad m) => LocatableTreeT m α -> m αSource
Same as exploreLocatableTree, but for an impure tree. 
exploreLocatableTreeTAndIgnoreResults :: Monad m => LocatableTreeT m α -> m ()Source
Same as exploreLocatableTree, but the results are discarded so the tree is
    only explored for its side-effects.
exploreTreeWithLocations :: Tree α -> [Solution α]Source
Explores all of the nodes of a tree, returning a list of solutions each tagged with the location at which it was found.
exploreTreeTWithLocations :: Monad m => TreeT m α -> m [Solution α]Source
Like exploreTreeWithLocations but for an impure tree. 
exploreTreeWithLocationsStartingAt :: Location -> Tree α -> [Solution α]Source
Like exploreTreeWithLocations, but for a subtree whose location is given by
    the first argument;  the solutions are labeled by the absolute location
    within the full tree (as opposed to their relative location within the
    subtree).
exploreTreeTWithLocationsStartingAt :: Monad m => Location -> TreeT m α -> m [Solution α]Source
Like exploreTreeWithLocationsStartingAt but for an impure trees. 
exploreLocatableTreeUntilFirst :: LocatableTree α -> Maybe αSource
Explores all the nodes in a LocatableTree until a result (i.e., a leaf) has
    been found; if a result has been found then it is returned wrapped in
    Just, otherwise Nothing is returned.
exploreLocatableTreeUntilFirstT :: Monad m => LocatableTreeT m α -> m (Maybe α)Source
Like exploreLocatableTreeUntilFirst but for an impure tree. 
exploreTreeUntilFirstWithLocation :: Tree α -> Maybe (Solution α)Source
exploreTreeTUntilFirstWithLocation :: Monad m => TreeT m α -> m (Maybe (Solution α))Source
Like exploreTreeUntilFirstWithLocation but for an impure tree. 
exploreTreeUntilFirstWithLocationStartingAt :: Location -> Tree α -> Maybe (Solution α)Source
Like exploreTreeUntilFirstWithLocation, but for a subtree whose location is
    given by the first argument; the solution (if present) is labeled by the
    absolute location within the full tree (as opposed to its relative
    location within the subtree).
exploreTreeTUntilFirstWithLocationStartingAt :: Monad m => Location -> TreeT m α -> m (Maybe (Solution α))Source
Like exploreTreeUntilFirstWithLocationStartingAt but for an impure tree.