Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
AOC.Common
Description
Common functions for solutions
Synopsis
- trace' :: String -> a -> a
- iterateMaybe :: (a -> Maybe a) -> a -> [a]
- loopMaybe :: (a -> Maybe a) -> a -> a
- loopMaybeM :: Monad m => (a -> m (Maybe a)) -> a -> m a
- loopEither :: (a -> Either r a) -> a -> r
- firstJust :: Foldable t => (a -> Maybe b) -> t a -> Maybe b
- (!!!) :: [a] -> Int -> a
- strictIterate :: (a -> a) -> a -> [a]
- (!?) :: [a] -> Int -> Maybe a
- drop' :: Int -> [a] -> [a]
- dup :: a -> (a, a)
- scanlT :: Traversable t => (b -> a -> b) -> b -> t a -> t b
- scanrT :: Traversable t => (a -> b -> b) -> b -> t a -> t b
- firstRepeated :: Ord a => [a] -> Maybe a
- firstRepeatedBy :: Ord a => (b -> a) -> [b] -> Maybe b
- fixedPoint :: Eq a => (a -> a) -> a -> a
- floodFill :: Ord a => (a -> Set a) -> Set a -> Set a
- floodFillCount :: Ord a => (a -> Set a) -> Set a -> (Int, Set a)
- countTrue :: Foldable f => (a -> Bool) -> f a -> Int
- pickUnique :: (Ord k, Ord a) => [(k, Set a)] -> [Map k a]
- freqs :: (Foldable f, Ord a) => f a -> Map a Int
- lookupFreq :: Ord a => a -> Map a Int -> Int
- freqList :: (Foldable f, Ord a) => f a -> [(Int, a)]
- revFreq :: (Foldable f, Ord a) => f a -> IntMap (NESet a)
- perturbations :: Traversable f => (a -> [a]) -> f a -> [f a]
- perturbationsBy :: Conjoined p => Over p (Bazaar p a a) s t a a -> (a -> [a]) -> s -> [t]
- select :: [a] -> [(a, [a])]
- slidingWindows :: Int -> [a] -> [Seq a]
- sortedSlidingWindows :: forall k v. Ord k => Int -> [(k, v)] -> [OrdPSQ k Int v]
- sortedSlidingWindowsInt :: forall v. Int -> [(Int, v)] -> [IntPSQ Int v]
- clearOut :: (Char -> Bool) -> String -> String
- foldMapPar :: Monoid b => (a -> b) -> [a] -> b
- foldMapPar1 :: Semigroup b => (a -> b) -> NonEmpty a -> b
- foldMapParChunk :: forall a m. (NFData m, Monoid m) => Int -> (a -> m) -> [a] -> m
- meanVar :: Fractional a => Fold a (a, a)
- maximumVal :: Ord b => Map a b -> Maybe (a, b)
- maximumValBy :: (b -> b -> Ordering) -> Map a b -> Maybe (a, b)
- minimumVal :: Ord b => Map a b -> Maybe (a, b)
- minimumValBy :: (b -> b -> Ordering) -> Map a b -> Maybe (a, b)
- maximumValNE :: Ord b => NEMap a b -> (a, b)
- maximumValByNE :: (b -> b -> Ordering) -> NEMap a b -> (a, b)
- minimumValNE :: Ord b => NEMap a b -> (a, b)
- minimumValByNE :: (b -> b -> Ordering) -> NEMap a b -> (a, b)
- listTup :: [a] -> Maybe (a, a)
- _ListTup :: Prism' [a] (a, a)
- listTup3 :: [a] -> Maybe (a, a, a)
- _ListTup3 :: Prism' [a] (a, a, a)
- listTup4 :: [a] -> Maybe (a, a, a, a)
- _ListTup4 :: Prism' [a] (a, a, a, a)
- sortSizedBy :: Vector v a => (a -> a -> Ordering) -> Vector v n a -> Vector v n a
- withAllSized :: Vector v a => NonEmpty [a] -> (forall n. KnownNat n => NonEmpty (Vector v n a) -> Maybe r) -> Maybe r
- binaryFold :: Monoid m => Int -> (a -> m) -> [a] -> m
- binaryFoldPar :: Monoid m => Int -> (a -> m) -> [a] -> m
- deleteFinite :: KnownNat n => Finite (n + 1) -> Finite (n + 1) -> Maybe (Finite n)
- type Letter = Finite 26
- charFinite :: Char -> Maybe (Bool, Finite 26)
- _CharFinite :: Prism' Char (Bool, Finite 26)
- hexDigit :: Prism' Char (Finite 16)
- decimalDigit :: Prism' Char (Finite 10)
- splitWord :: Word8 -> (Finite 16, Finite 16)
- digitToIntSafe :: Char -> Maybe Int
- caeser :: Finite 26 -> Char -> Char
- eitherItem :: Lens' (Either a a) a
- toNatural :: Integral a => a -> Maybe Natural
- factorial :: Int -> Int
- integerFactorial :: Integer -> Integer
- mapMaybeSet :: Ord b => (a -> Maybe b) -> Set a -> Set b
- symDiff :: Ord a => Set a -> Set a -> Set a
- unfoldedIterate :: forall n a proxy. SNatI n => proxy n -> (a -> a) -> a -> a
- memo4 :: Memo a -> Memo b -> Memo c -> Memo d -> (a -> b -> c -> d -> r) -> a -> b -> c -> d -> r
- newtype TokStream a = TokStream {
- getTokStream :: [a]
- parseTokStream :: Foldable t => Parsec e (TokStream s) a -> t s -> Either (ParseErrorBundle (TokStream s) e) a
- parseTokStream_ :: (Alternative m, Foldable t) => Parsec e (TokStream s) a -> t s -> m a
- parseTokStreamT :: (Foldable t, Monad m) => ParsecT e (TokStream s) m a -> t s -> m (Either (ParseErrorBundle (TokStream s) e) a)
- parseTokStreamT_ :: (Alternative f, Foldable t, Monad m) => ParsecT e (TokStream s) m a -> t s -> m (f a)
- type TokParser s = Parsec Void (TokStream s)
- parseWords :: Parsec Void (TokStream String) a -> String -> Maybe a
- nextMatch :: MonadParsec e s m => m a -> m a
- parseMaybeLenient :: Parsec Void s a -> s -> Maybe a
- parseOrFail :: (ShowErrorComponent e, VisualStream s, TraversableStream s) => Parsec e s a -> s -> a
- type CharParser = Parsec Void String
- pWord :: (Stream s, Token s ~ Char, Ord e) => Parsec e s String
- pHWord :: (Stream s, Token s ~ Char, Ord e) => Parsec e s String
- pDecimal :: (Stream s, Token s ~ Char, Ord e, Num a) => Parsec e s a
- pTok :: (Stream s, Token s ~ Char, Ord e) => Parsec e s a -> Parsec e s a
- pSpace :: (Stream s, Token s ~ Char, Ord e) => Parsec e s ()
- parseLines :: Parsec Void String a -> String -> Maybe [a]
- type Graph v e = Map v (Map v e)
- toFGL :: (Graph gr, Ord v) => Graph v e -> (gr v e, Set v)
- anaM :: (Monad m, Corecursive t, Traversable (Base t)) => (a -> m (Base t a)) -> a -> m t
Documentation
Loops and searches
iterateMaybe :: (a -> Maybe a) -> a -> [a] Source #
Iterate until a Nothing
is produced
loopMaybe :: (a -> Maybe a) -> a -> a Source #
Apply function until Nothing
is produced, and return last produced
value.
loopMaybeM :: Monad m => (a -> m (Maybe a)) -> a -> m a Source #
Apply monadic function until Nothing
is produced, and return last produced
value.
loopEither :: (a -> Either r a) -> a -> r Source #
Apply function until a Left
.
firstJust :: Foldable t => (a -> Maybe b) -> t a -> Maybe b Source #
Like find
, but instead of taking an a -> Bool
, takes an a ->
Maybe b
and returns the first success.
strictIterate :: (a -> a) -> a -> [a] Source #
scanlT :: Traversable t => (b -> a -> b) -> b -> t a -> t b Source #
scanl
generalized to all Traversable
.
scanrT :: Traversable t => (a -> b -> b) -> b -> t a -> t b Source #
scanr
generalized to all Traversable
.
firstRepeated :: Ord a => [a] -> Maybe a Source #
Lazily find the first repeated item.
firstRepeatedBy :: Ord a => (b -> a) -> [b] -> Maybe b Source #
Lazily find the first repeated projection.
fixedPoint :: Eq a => (a -> a) -> a -> a Source #
Repeat a function until you get the same result twice.
Arguments
:: Ord a | |
=> (a -> Set a) | Expansion (be sure to limit allowed points) |
-> Set a | Start points |
-> Set a | Flood filled |
Flood fill from a starting set
Arguments
:: Ord a | |
=> (a -> Set a) | Expansion (be sure to limit allowed points) |
-> Set a | Start points |
-> (Int, Set a) | Flood filled, with count of number of steps |
Flood fill from a starting set, counting the number of steps
countTrue :: Foldable f => (a -> Bool) -> f a -> Int Source #
Count the number of items in a container where the predicate is true.
pickUnique :: (Ord k, Ord a) => [(k, Set a)] -> [Map k a] Source #
Given a map of k
to possible a
s for that k
, find possible
configurations where each k
is given its own unique a
.
Lists
lookupFreq :: Ord a => a -> Map a Int -> Int Source #
Look up a count from a frequency map, defaulting to zero if item is not foudn
freqList :: (Foldable f, Ord a) => f a -> [(Int, a)] Source #
Build a list of descending frequencies. Ties are sorted.
perturbations :: Traversable f => (a -> [a]) -> f a -> [f a] Source #
Collect all possible single-item perturbations from a given perturbing function.
perturbations (\i -> [i - 1, i + 1]) [0,10,100]
[ [-1,10,100]
, [ 1,10,100] , [ 0, 9,100] , [ 0,11,100] , [ 0,10, 99] , [ 0,10,101] ]
perturbationsBy :: Conjoined p => Over p (Bazaar p a a) s t a a -> (a -> [a]) -> s -> [t] Source #
Collect all possible single-item perturbations from a given perturbing function.
perturbations (\i -> [i - 1, i + 1]) [0,10,100]
[ [-1,10,100]
, [ 1,10,100] , [ 0, 9,100] , [ 0,11,100] , [ 0,10, 99] , [ 0,10,101] ]
slidingWindows :: Int -> [a] -> [Seq a] Source #
sliding windows of a given length
sortedSlidingWindows :: forall k v. Ord k => Int -> [(k, v)] -> [OrdPSQ k Int v] Source #
sorted windows of a given length
sortedSlidingWindowsInt :: forall v. Int -> [(Int, v)] -> [IntPSQ Int v] Source #
sorted windows of a given length
clearOut :: (Char -> Bool) -> String -> String Source #
Clear out characters not matching a predicate
foldMapPar :: Monoid b => (a -> b) -> [a] -> b Source #
foldMap
, but in parallel.
foldMapPar1 :: Semigroup b => (a -> b) -> NonEmpty a -> b Source #
foldMap1
, but in parallel.
meanVar :: Fractional a => Fold a (a, a) Source #
Fold
for computing mean and variance
maximumVal :: Ord b => Map a b -> Maybe (a, b) Source #
Get the key-value pair corresponding to the maximum value in the map
maximumValBy :: (b -> b -> Ordering) -> Map a b -> Maybe (a, b) Source #
Get the key-value pair corresponding to the maximum value in the map, with a custom comparing function.
'maximumVal' == 'maximumValBy' 'compare'
minimumVal :: Ord b => Map a b -> Maybe (a, b) Source #
Get the key-value pair corresponding to the minimum value in the map
minimumValBy :: (b -> b -> Ordering) -> Map a b -> Maybe (a, b) Source #
Get the key-value pair corresponding to the minimum value in the map, with a custom comparing function.
'minimumVal' == 'minimumValBy' 'compare'
maximumValNE :: Ord b => NEMap a b -> (a, b) Source #
Version of maximumVal
for nonempty maps.
maximumValByNE :: (b -> b -> Ordering) -> NEMap a b -> (a, b) Source #
Version of maximumValBy
for nonempty maps.
minimumValNE :: Ord b => NEMap a b -> (a, b) Source #
Version of minimumVal
for nonempty maps.
minimumValByNE :: (b -> b -> Ordering) -> NEMap a b -> (a, b) Source #
Version of minimumValBy
for nonempty maps.
sortSizedBy :: Vector v a => (a -> a -> Ordering) -> Vector v n a -> Vector v n a Source #
withAllSized :: Vector v a => NonEmpty [a] -> (forall n. KnownNat n => NonEmpty (Vector v n a) -> Maybe r) -> Maybe r Source #
Simple type util
deleteFinite :: KnownNat n => Finite (n + 1) -> Finite (n + 1) -> Maybe (Finite n) Source #
Delete a potential value from a Finite
.
eitherItem :: Lens' (Either a a) a Source #
integerFactorial :: Integer -> Integer Source #
unfoldedIterate :: forall n a proxy. SNatI n => proxy n -> (a -> a) -> a -> a Source #
memo4 :: Memo a -> Memo b -> Memo c -> Memo d -> (a -> b -> c -> d -> r) -> a -> b -> c -> d -> r Source #
Parsers
Use a stream of tokens a
as the underlying parser stream. Note that
error messages for parser errors are going necessarily to be wonky.
Constructors
TokStream | |
Fields
|
Instances
parseTokStream :: Foldable t => Parsec e (TokStream s) a -> t s -> Either (ParseErrorBundle (TokStream s) e) a Source #
Parse a stream of tokens s
purely, returning Either
parseTokStream_ :: (Alternative m, Foldable t) => Parsec e (TokStream s) a -> t s -> m a Source #
Parse a stream of tokens s
purely
parseTokStreamT :: (Foldable t, Monad m) => ParsecT e (TokStream s) m a -> t s -> m (Either (ParseErrorBundle (TokStream s) e) a) Source #
Parse a stream of tokens s
over an underlying monad, returning Either
parseTokStreamT_ :: (Alternative f, Foldable t, Monad m) => ParsecT e (TokStream s) m a -> t s -> m (f a) Source #
Parse a stream of tokens s
over an underlying monad
parseOrFail :: (ShowErrorComponent e, VisualStream s, TraversableStream s) => Parsec e s a -> s -> a Source #
Graph
Recursion Schemes
anaM :: (Monad m, Corecursive t, Traversable (Base t)) => (a -> m (Base t a)) -> a -> m t Source #
Orphan instances
FoldableWithIndex k (NEMap k) Source # | |
FunctorWithIndex k (NEMap k) Source # | |
TraversableWithIndex k (NEMap k) Source # | |
Methods itraverse :: Applicative f => (k -> a -> f b) -> NEMap k a -> f (NEMap k b) # | |
(KnownNat n, forall a. Vector v a, 1 <= n) => R1 (Vector v n) Source # | |
(KnownNat n, forall a. Vector v a, 2 <= n) => R2 (Vector v n) Source # | |
(KnownNat n, forall a. Vector v a, 3 <= n) => R3 (Vector v n) Source # | |
(KnownNat n, forall a. Vector v a, 4 <= n) => R4 (Vector v n) Source # | |
(Ixed (v a), Index (v a) ~ Int, IxValue (v a) ~ a) => Ixed (Vector v n a) Source # | |
Methods ix :: Index (Vector v n a) -> Traversal' (Vector v n a) (IxValue (Vector v n a)) # | |
(Ord k, Ord p) => Ixed (OrdPSQ k p v) Source # | |
Methods ix :: Index (OrdPSQ k p v) -> Traversal' (OrdPSQ k p v) (IxValue (OrdPSQ k p v)) # |