aoc2020-0.1.0.0: Development environment for Advent of Code challenges
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

AOC.Common

Description

Common functions for solutions

Synopsis

Documentation

trace' :: String -> a -> a Source #

trace but only after something has evaluated to WHNF

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.

(!!!) :: [a] -> Int -> a Source #

Strict (!!)

strictIterate :: (a -> a) -> a -> [a] Source #

(!?) :: [a] -> Int -> Maybe a Source #

drop' :: Int -> [a] -> [a] Source #

Strict drop

dup :: a -> (a, a) Source #

A tuple of the same item twice

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.

floodFill Source #

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

floodFillCount Source #

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 as for that k, find possible configurations where each k is given its own unique a.

Lists

freqs :: (Foldable f, Ord a) => f a -> Map a Int Source #

Build a frequency map

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.

revFreq :: (Foldable f, Ord a) => f a -> IntMap (NESet a) Source #

Build a reverse frequency map

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] ]

select :: [a] -> [(a, [a])] Source #

each item paired with the list not including that item

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.

foldMapParChunk Source #

Arguments

:: forall a m. (NFData m, Monoid m) 
=> Int

chunk size

-> (a -> m) 
-> [a] 
-> m 

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.

listTup :: [a] -> Maybe (a, a) Source #

_ListTup :: Prism' [a] (a, a) Source #

listTup3 :: [a] -> Maybe (a, a, a) Source #

_ListTup3 :: Prism' [a] (a, a, a) Source #

listTup4 :: [a] -> Maybe (a, a, a, a) Source #

_ListTup4 :: Prism' [a] (a, a, a, a) Source #

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 #

binaryFold Source #

Arguments

:: Monoid m 
=> Int

minimum size list

-> (a -> m) 
-> [a] 
-> m 

binaryFoldPar Source #

Arguments

:: Monoid m 
=> Int

minimum size list

-> (a -> m) 
-> [a] 
-> m 

Simple type util

deleteFinite :: KnownNat n => Finite (n + 1) -> Finite (n + 1) -> Maybe (Finite n) Source #

Delete a potential value from a Finite.

type Letter = Finite 26 Source #

charFinite :: Char -> Maybe (Bool, Finite 26) Source #

Parse a letter into a number 0 to 25. Returns False if lowercase and True if uppercase.

_CharFinite :: Prism' Char (Bool, Finite 26) Source #

Prism for a Char as (Bool, Finite 26), where the Finite is the letter parsed as a number from 0 to 25, and the Bool is lowercase (False) or uppercase (True).

caeser :: Finite 26 -> Char -> Char Source #

Caeser shift, preserving case. If you have an Int or Integer, convert into Finite using modulo.

mapMaybeSet :: Ord b => (a -> Maybe b) -> Set a -> Set b Source #

symDiff :: Ord a => Set a -> Set a -> Set a 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

newtype TokStream a Source #

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

Instances details
Functor TokStream Source # 
Instance details

Defined in AOC.Common

Methods

fmap :: (a -> b) -> TokStream a -> TokStream b #

(<$) :: a -> TokStream b -> TokStream a #

Eq a => Eq (TokStream a) Source # 
Instance details

Defined in AOC.Common

Methods

(==) :: TokStream a -> TokStream a -> Bool #

(/=) :: TokStream a -> TokStream a -> Bool #

Ord a => Ord (TokStream a) Source # 
Instance details

Defined in AOC.Common

Show a => Show (TokStream a) Source # 
Instance details

Defined in AOC.Common

Generic (TokStream a) Source # 
Instance details

Defined in AOC.Common

Associated Types

type Rep (TokStream a) :: Type -> Type #

Methods

from :: TokStream a -> Rep (TokStream a) x #

to :: Rep (TokStream a) x -> TokStream a #

NFData a => NFData (TokStream a) Source # 
Instance details

Defined in AOC.Common

Methods

rnf :: TokStream a -> () #

Hashable a => Hashable (TokStream a) Source # 
Instance details

Defined in AOC.Common

Methods

hashWithSalt :: Int -> TokStream a -> Int

hash :: TokStream a -> Int

(Ord a, Show a) => Stream (TokStream a) Source # 
Instance details

Defined in AOC.Common

Associated Types

type Token (TokStream a)

type Tokens (TokStream a)

Methods

tokenToChunk :: Proxy (TokStream a) -> Token (TokStream a) -> Tokens (TokStream a)

tokensToChunk :: Proxy (TokStream a) -> [Token (TokStream a)] -> Tokens (TokStream a)

chunkToTokens :: Proxy (TokStream a) -> Tokens (TokStream a) -> [Token (TokStream a)]

chunkLength :: Proxy (TokStream a) -> Tokens (TokStream a) -> Int

chunkEmpty :: Proxy (TokStream a) -> Tokens (TokStream a) -> Bool

take1_ :: TokStream a -> Maybe (Token (TokStream a), TokStream a)

takeN_ :: Int -> TokStream a -> Maybe (Tokens (TokStream a), TokStream a)

takeWhile_ :: (Token (TokStream a) -> Bool) -> TokStream a -> (Tokens (TokStream a), TokStream a)

type Rep (TokStream a) Source # 
Instance details

Defined in AOC.Common

type Rep (TokStream a) = D1 ('MetaData "TokStream" "AOC.Common" "aoc2020-0.1.0.0-FyPlSv9LBbs5G4MoObRXVm" 'True) (C1 ('MetaCons "TokStream" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTokStream") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])))
type Token (TokStream a) Source # 
Instance details

Defined in AOC.Common

type Token (TokStream a) = a
type Tokens (TokStream a) Source # 
Instance details

Defined in AOC.Common

type Tokens (TokStream a) = Seq a

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

nextMatch :: MonadParsec e s m => m a -> m a Source #

Skip every result until this token matches

parseOrFail :: (ShowErrorComponent e, VisualStream s, TraversableStream s) => Parsec e s a -> s -> a Source #

pWord :: (Stream s, Token s ~ Char, Ord e) => Parsec e s String Source #

pHWord :: (Stream s, Token s ~ Char, Ord e) => Parsec e s String Source #

pDecimal :: (Stream s, Token s ~ Char, Ord e, Num a) => Parsec e s a Source #

pTok :: (Stream s, Token s ~ Char, Ord e) => Parsec e s a -> Parsec e s a Source #

pSpace :: (Stream s, Token s ~ Char, Ord e) => Parsec e s () Source #

Graph

type Graph v e = Map v (Map v e) Source #

toFGL :: (Graph gr, Ord v) => Graph v e -> (gr v e, Set v) Source #

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 # 
Instance details

Methods

ifoldMap :: Monoid m => (k -> a -> m) -> NEMap k a -> m #

ifoldMap' :: Monoid m => (k -> a -> m) -> NEMap k a -> m #

ifoldr :: (k -> a -> b -> b) -> b -> NEMap k a -> b #

ifoldl :: (k -> b -> a -> b) -> b -> NEMap k a -> b #

ifoldr' :: (k -> a -> b -> b) -> b -> NEMap k a -> b #

ifoldl' :: (k -> b -> a -> b) -> b -> NEMap k a -> b #

FunctorWithIndex k (NEMap k) Source # 
Instance details

Methods

imap :: (k -> a -> b) -> NEMap k a -> NEMap k b #

TraversableWithIndex k (NEMap k) Source # 
Instance details

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 # 
Instance details

Methods

_x :: Lens' (Vector v n a) a #

(KnownNat n, forall a. Vector v a, 2 <= n) => R2 (Vector v n) Source # 
Instance details

Methods

_y :: Lens' (Vector v n a) a #

_xy :: Lens' (Vector v n a) (V2 a) #

(KnownNat n, forall a. Vector v a, 3 <= n) => R3 (Vector v n) Source # 
Instance details

Methods

_z :: Lens' (Vector v n a) a #

_xyz :: Lens' (Vector v n a) (V3 a) #

(KnownNat n, forall a. Vector v a, 4 <= n) => R4 (Vector v n) Source # 
Instance details

Methods

_w :: Lens' (Vector v n a) a #

_xyzw :: Lens' (Vector v n a) (V4 a) #

(Ixed (v a), Index (v a) ~ Int, IxValue (v a) ~ a) => Ixed (Vector v n a) Source # 
Instance details

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 # 
Instance details

Methods

ix :: Index (OrdPSQ k p v) -> Traversal' (OrdPSQ k p v) (IxValue (OrdPSQ k p v)) #