Copyright | (c) M1n3c4rt 2025 |
---|---|
License | BSD-3-Clause |
Maintainer | vedicbits@gmail.com |
Stability | stable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Utility.AOC
Description
Synopsis
- shortestDistance :: (Foldable t, Hashable n, Ord a, Num a) => HashMap n (t (n, a)) -> n -> n -> Maybe a
- shortestPaths :: (Foldable t, Hashable n, Ord a, Num a) => HashMap n (t (n, a)) -> n -> n -> (Maybe a, [[n]])
- shortestDistanceOnMagma :: (Foldable t, Hashable n, Ord a, Num a) => [HashMap n (t (n, a))] -> n -> n -> Maybe a
- shortestPathsOnMagma :: (Foldable t, Hashable n, Ord a, Num a) => [HashMap n (t (n, a))] -> n -> n -> (Maybe a, [[n]])
- neighbours4 :: (Num a, Num b) => (a, b) -> [(a, b)]
- neighbours8 :: (Enum a, Enum b, Eq a, Eq b, Num a, Num b) => (a, b) -> [(a, b)]
- neighbours6 :: (Num a, Num b, Num c) => (a, b, c) -> [(a, b, c)]
- neighbours26 :: (Enum a, Enum b, Enum c, Eq a, Eq b, Eq c, Num a, Num b, Num c) => (a, b, c) -> [(a, b, c)]
- taxicab2 :: Num a => (a, a) -> (a, a) -> a
- taxicab3 :: Num a => (a, a, a) -> (a, a, a) -> a
- enumerate :: (Num y, Num x, Enum y, Enum x) => String -> [(x, y, Char)]
- enumerateRead :: (Read c, Num y, Num x, Enum y, Enum x) => String -> [(x, y, c)]
- enumerateHM :: (Num x, Num y, Enum x, Enum y, Hashable x, Hashable y) => String -> HashMap (x, y) Char
- enumerateReadHM :: (Num x, Num y, Enum x, Enum y, Hashable x, Hashable y, Read c) => String -> HashMap (x, y) c
- enumerateFilter :: (Num y, Num x, Enum y, Enum x) => (Char -> Bool) -> String -> [(x, y)]
- enumerateFilterSet :: (Ord x, Ord y, Num y, Num x, Enum y, Enum x) => (Char -> Bool) -> String -> Set (x, y)
- floodFill :: Ord a => (a -> [a]) -> Set a -> Set a -> Set a
- floodFillWith :: Ord a => (a -> a -> Bool) -> (a -> [a]) -> Set a -> Set a
- choose :: (Num n, Eq n) => n -> [a] -> [[a]]
- permute :: (Num n, Eq n) => n -> [a] -> [[a]]
- extrapolate :: (Integral b, Ord a) => b -> [a] -> a
- range :: (Ord a, Enum a) => a -> a -> [a]
- rangeIntersect :: Ord b => (b, b) -> (b, b) -> Maybe (b, b)
- binToDec :: Num a => [Bool] -> a
- class Eq a => Hashable a
- data HashMap k v
- data Set a
Pathfinding algorithms
All of the following functions return distances as a Maybe Int
, where Nothing
is returned if no path is found.
The graph is a HashMap
mapping each node to a sequence of (neighbour, edge weight) pairs.
Arguments
:: (Foldable t, Hashable n, Ord a, Num a) | |
=> HashMap n (t (n, a)) | Graph |
-> n | Start node |
-> n | End node |
-> Maybe a |
Returns the shortest distance between two nodes in a graph.
Arguments
:: (Foldable t, Hashable n, Ord a, Num a) | |
=> HashMap n (t (n, a)) | Graph |
-> n | Start node |
-> n | End node |
-> (Maybe a, [[n]]) |
Returns the shortest distance between two nodes in a graph and a list of all possible paths from the ending node to the starting node. The starting node is not included in each path.
shortestDistanceOnMagma Source #
Arguments
:: (Foldable t, Hashable n, Ord a, Num a) | |
=> [HashMap n (t (n, a))] | Graphs |
-> n | Start node |
-> n | End node |
-> Maybe a |
Returns the shortest distance between two nodes in a list of graphs where the neighbours of a node in any given graph all lie in the succeeding graph. The ending node must be present in each graph. This precondition is not checked.
Arguments
:: (Foldable t, Hashable n, Ord a, Num a) | |
=> [HashMap n (t (n, a))] | Graphs |
-> n | Start node |
-> n | End node |
-> (Maybe a, [[n]]) |
Returns the shortest distance between two nodes in a list of graphs and a list of all possible paths from the ending node to the starting node. The ending node must be present in each graph. This precondition is not checked. The starting node is not included in each path.
Neighbour functions
neighbours4 :: (Num a, Num b) => (a, b) -> [(a, b)] Source #
Returns the 4 points orthogonally adjacent to the given point.
neighbours8 :: (Enum a, Enum b, Eq a, Eq b, Num a, Num b) => (a, b) -> [(a, b)] Source #
Returns the 8 points orthogonally or diagonally adjacent to the given point.
neighbours6 :: (Num a, Num b, Num c) => (a, b, c) -> [(a, b, c)] Source #
Returns the 6 points orthogonally adjacent to the given point in 3D space.
neighbours26 :: (Enum a, Enum b, Enum c, Eq a, Eq b, Eq c, Num a, Num b, Num c) => (a, b, c) -> [(a, b, c)] Source #
Returns the 26 points orthogonally or diagonally adjacent to the given point in 3D space.
Taxicab (Manhattan) distance
taxicab2 :: Num a => (a, a) -> (a, a) -> a Source #
Returns the Taxicab/Manhattan distance between two points in 2D space.
taxicab3 :: Num a => (a, a, a) -> (a, a, a) -> a Source #
Returns the Taxicab/Manhattan distance between two points in 3D space.
Grid enumeration
The following functions operate on a grid of characters as a string with a newline after each row (as seen in several Advent of Code puzzle inputs).
enumerate :: (Num y, Num x, Enum y, Enum x) => String -> [(x, y, Char)] Source #
Converts a grid to a list of triples (x,y,c)
representing xy coordinates and the character at that location.
enumerateRead :: (Read c, Num y, Num x, Enum y, Enum x) => String -> [(x, y, c)] Source #
Enumerates a grid along with reading the characters (usually as integers).
enumerateHM :: (Num x, Num y, Enum x, Enum y, Hashable x, Hashable y) => String -> HashMap (x, y) Char Source #
Enumerates a grid and stores it in a HashMap
where points are mapped to the character at that location.
enumerateReadHM :: (Num x, Num y, Enum x, Enum y, Hashable x, Hashable y, Read c) => String -> HashMap (x, y) c Source #
Enumerates a grid and stores it in a HashMap
along with reading the characters (usually as integers).
enumerateFilter :: (Num y, Num x, Enum y, Enum x) => (Char -> Bool) -> String -> [(x, y)] Source #
Returns a list of points on a grid for which a certain condition is met.
enumerateFilterSet :: (Ord x, Ord y, Num y, Num x, Enum y, Enum x) => (Char -> Bool) -> String -> Set (x, y) Source #
Returns a set of points on a grid for which a certain condition is met.
Flood fill
Arguments
:: Ord a | |
=> (a -> [a]) | Neighbour function |
-> Set a | Initial set of points |
-> Set a | Set of points to avoid |
-> Set a |
Applies a flood fill algorithm given a function to generate a point's neighbours, a starting set of points, and a set of points to avoid. Returns a set of all points covered.
Arguments
:: Ord a | |
=> (a -> a -> Bool) | Condition |
-> (a -> [a]) | Neighbour function |
-> Set a | Initial set of points |
-> Set a |
Applies a flood fill algorithm given a function to generate a point's neighbours, a condition that filters out points generated by said function, and a starting set of points. Returns a set of all points covered.
The condition is of the form a -> a -> Bool
, which returns True
if the second point is a valid neighbour of the first point and False
otherwise.
List selection
choose :: (Num n, Eq n) => n -> [a] -> [[a]] Source #
Generates a list of all possible lists of length n by taking elements from the provided list of length l. Relative order is maintained, and the length of the returned list is \(_{n}C_{l}\).
permute :: (Num n, Eq n) => n -> [a] -> [[a]] Source #
Generates a list of all possible lists of length n by taking elements from the provided list of length l. The length of the returned list is \(_{n}P_{l}\).
Extrapolation
extrapolate :: (Integral b, Ord a) => b -> [a] -> a Source #
Gets the nth element of an infinite list, assuming that each element in the list can be generated using the previous element, for example, a list generated with iterate
.
Miscellaneous
range :: (Ord a, Enum a) => a -> a -> [a] Source #
Generates a range with [x..y]
, but reverses the list instead of returning an empty range if x > y.
rangeIntersect :: Ord b => (b, b) -> (b, b) -> Maybe (b, b) Source #
Takes (a,b) and (c,d) as arguments and returns the intersection of the ranges [a..b] and [c..d] as another pair if it is not empty.
binToDec :: Num a => [Bool] -> a Source #
Converts a list of booleans (parsed as a binary number) to an integer.
The class of types that can be converted to a hash value.
Minimal implementation: hashWithSalt
.
Hashable
is intended exclusively for use in in-memory data structures.
.
Hashable
does not have a fixed standard.
This allows it to improve over time.
.
Because it does not have a fixed standard, different computers or computers on different versions of the code will observe different hash values.
As such, Hashable
is not recommended for use other than in-memory datastructures.
Specifically, Hashable
is not intended for network use or in applications which persist hashed values.
For stable hashing use named hashes: sha256, crc32, xxhash etc.
If you are looking for Hashable
instance in time
package,
check time-compat
Instances
A map from keys to values. A map cannot contain duplicate keys; each key can map to at most one value.
Instances
Bifoldable HashMap | Since: unordered-containers-0.2.11 | ||||
Eq2 HashMap | |||||
Ord2 HashMap | |||||
Defined in Data.HashMap.Internal | |||||
Show2 HashMap | |||||
NFData2 HashMap | Since: unordered-containers-0.2.14.0 | ||||
Defined in Data.HashMap.Internal | |||||
Hashable2 HashMap | |||||
Defined in Data.HashMap.Internal | |||||
(Lift k, Lift v) => Lift (HashMap k v :: Type) | Since: unordered-containers-0.2.17.0 | ||||
Foldable (HashMap k) | |||||
Defined in Data.HashMap.Internal Methods fold :: Monoid m => HashMap k m -> m # foldMap :: Monoid m => (a -> m) -> HashMap k a -> m # foldMap' :: Monoid m => (a -> m) -> HashMap k a -> m # foldr :: (a -> b -> b) -> b -> HashMap k a -> b # foldr' :: (a -> b -> b) -> b -> HashMap k a -> b # foldl :: (b -> a -> b) -> b -> HashMap k a -> b # foldl' :: (b -> a -> b) -> b -> HashMap k a -> b # foldr1 :: (a -> a -> a) -> HashMap k a -> a # foldl1 :: (a -> a -> a) -> HashMap k a -> a # toList :: HashMap k a -> [a] # length :: HashMap k a -> Int # elem :: Eq a => a -> HashMap k a -> Bool # maximum :: Ord a => HashMap k a -> a # minimum :: Ord a => HashMap k a -> a # | |||||
Eq k => Eq1 (HashMap k) | |||||
Ord k => Ord1 (HashMap k) | |||||
Defined in Data.HashMap.Internal | |||||
(Eq k, Hashable k, Read k) => Read1 (HashMap k) | |||||
Defined in Data.HashMap.Internal | |||||
Show k => Show1 (HashMap k) | |||||
Traversable (HashMap k) | |||||
Defined in Data.HashMap.Internal | |||||
Functor (HashMap k) | |||||
NFData k => NFData1 (HashMap k) | Since: unordered-containers-0.2.14.0 | ||||
Defined in Data.HashMap.Internal | |||||
Hashable k => Hashable1 (HashMap k) | |||||
Defined in Data.HashMap.Internal | |||||
(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) | |||||
Defined in Data.HashMap.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashMap k v -> c (HashMap k v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashMap k v) # toConstr :: HashMap k v -> Constr # dataTypeOf :: HashMap k v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashMap k v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashMap k v)) # gmapT :: (forall b. Data b => b -> b) -> HashMap k v -> HashMap k v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQ :: (forall d. Data d => d -> u) -> HashMap k v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashMap k v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # | |||||
(Eq k, Hashable k) => Monoid (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
| ||||
(Eq k, Hashable k) => Semigroup (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
| ||||
(Eq k, Hashable k) => IsList (HashMap k v) | |||||
Defined in Data.HashMap.Internal Associated Types
| |||||
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |||||
(Show k, Show v) => Show (HashMap k v) | |||||
(NFData k, NFData v) => NFData (HashMap k v) | |||||
Defined in Data.HashMap.Internal | |||||
(Eq k, Eq v) => Eq (HashMap k v) | Note that, in the presence of hash collisions, equal
In general, the lack of extensionality can be observed with any function that depends on the key ordering, such as folds and traversals. | ||||
(Ord k, Ord v) => Ord (HashMap k v) | The ordering is total and consistent with the | ||||
Defined in Data.HashMap.Internal | |||||
(Hashable k, Hashable v) => Hashable (HashMap k v) | |||||
Defined in Data.HashMap.Internal | |||||
type Item (HashMap k v) | |||||
Defined in Data.HashMap.Internal |
A set of values a
.
Instances
Foldable Set | Folds in order of increasing key. |
Defined in Data.Set.Internal Methods fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Eq1 Set | Since: containers-0.5.9 |
Ord1 Set | Since: containers-0.5.9 |
Defined in Data.Set.Internal | |
Show1 Set | Since: containers-0.5.9 |
Hashable1 Set | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Lift a => Lift (Set a :: Type) | Since: containers-0.6.6 |
(Data a, Ord a) => Data (Set a) | |
Defined in Data.Set.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |
Ord a => Monoid (Set a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Ord a => IsList (Set a) | Since: containers-0.5.6.2 |
(Read a, Ord a) => Read (Set a) | |
Show a => Show (Set a) | |
NFData a => NFData (Set a) | |
Defined in Data.Set.Internal | |
Eq a => Eq (Set a) | |
Ord a => Ord (Set a) | |
Hashable v => Hashable (Set v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
type Item (Set a) | |
Defined in Data.Set.Internal |