swarm-0.5.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Util

Description

A random collection of small, useful functions that are (or could be) used throughout the code base.

Synopsis

Miscellaneous utilities

(?) :: Maybe a -> a -> a infixr 1 Source #

A convenient infix flipped version of fromMaybe: Just a ? b = a, and Nothing ? b = b. It can also be chained, as in x ? y ? z ? def, which takes the value inside the first Just, defaulting to def as a last resort.

sortPair :: Ord b => (b, b) -> (b, b) Source #

Ensure the smaller value in a pair is the first element.

maxOn :: Ord b => (a -> b) -> a -> a -> a Source #

Find the maximum of two values, comparing them according to a custom projection function.

maximum0 :: (Num a, Ord a) => [a] -> a Source #

Find the maximum of a list of numbers, defaulting to 0 if the list is empty.

cycleEnum :: (Eq e, Enum e, Bounded e) => e -> e Source #

Take the successor of an Enum type, wrapping around when it reaches the end.

listEnums :: (Enum e, Bounded e) => [e] Source #

listEnumsNonempty :: (Enum e, Bounded e) => NonEmpty e Source #

Members of the Bounded class are guaranteed to have at least one element.

showEnum :: (Show e, Enum e) => e -> NonEmpty Char Source #

We know by the syntax rules of Haskell that constructor names must consist of one or more symbols!

indexWrapNonEmpty Source #

Arguments

:: Integral b 
=> NonEmpty a 
-> b

index

-> a 

Guaranteed to yield an element of the list.

This is true even if the supplied index is negative, since mod always satisfies 0 <= a mod b < b when b is positive (see https://github.com/swarm-game/swarm/pull/1181#discussion_r1151177735).

uniq :: Eq a => [a] -> [a] Source #

Drop repeated elements that are adjacent to each other.

>>> uniq []
[]
>>> uniq [1..5]
[1,2,3,4,5]
>>> uniq (replicate 10 'a')
"a"
>>> uniq "abbbccd"
"abcd"

binTuples :: (Foldable t, Ord a) => t (a, b) -> Map a (NonEmpty b) Source #

Place the second element of the tuples into bins by the value of the first element.

histogram :: (Foldable t, Ord a) => t a -> Map a Int Source #

Count occurrences of a value

findDup :: Ord a => [a] -> Maybe a Source #

Find a duplicate element within the list, if any exists.

both :: Bifunctor p => (a -> d) -> p a a -> p d d Source #

allEqual :: Ord a => [a] -> Bool Source #

surfaceEmpty :: Alternative f => (a -> Bool) -> a -> f a Source #

applyWhen :: Bool -> (a -> a) -> a -> a Source #

hoistMaybe :: Applicative m => Maybe b -> MaybeT m b Source #

Convert a Maybe computation to MaybeT.

TODO (#1151): Use implementation from "transformers" package v0.6.0.0

unsnocNE :: NonEmpty a -> ([a], a) Source #

Like unsnoc, but for NonEmpty so without the Maybe

Taken from Cabal-syntax Distribution.Utils.Generic.

Example: >>> import Data.List.NonEmpty (NonEmpty ((:|))) >>> unsnocNE (1 :| [2, 3]) ([1,2],3)

>>> unsnocNE (1 :| [])
([],1)

Directory utilities

readFileMay :: FilePath -> IO (Maybe String) Source #

Safely attempt to read a file.

readFileMayT :: FilePath -> IO (Maybe Text) Source #

Safely attempt to (efficiently) read a file.

acquireAllWithExt :: FilePath -> String -> IO [(FilePath, String)] Source #

Recursively acquire all files in the given directory with the given extension, and their contents.

Text utilities

isIdentChar :: Char -> Bool Source #

Predicate to test for characters which can be part of a valid identifier: alphanumeric, underscore, or single quote.

>>> isIdentChar 'A' && isIdentChar 'b' && isIdentChar '9'
True
>>> isIdentChar '_' && isIdentChar '\''
True
>>> isIdentChar '$' || isIdentChar '.' || isIdentChar ' '
False

replaceLast :: Text -> Text -> Text Source #

replaceLast r t replaces the last word of t with r.

>>> :set -XOverloadedStrings
>>> replaceLast "foo" "bar baz quux"
"bar baz foo"
>>> replaceLast "move" "(make"
"(move"

failT :: MonadFail m => [Text] -> m a Source #

Fail with a Text-based message, made out of phrases to be joined by spaces.

showT :: Show a => a -> Text Source #

Show a value, but as Text.

showLowT :: Show a => a -> Text Source #

Show a value in all lowercase, but as Text.

English language utilities

reflow :: Text -> Text Source #

Reflow text by removing newlines and condensing whitespace.

quote :: Text -> Text Source #

Surround some text in double quotes.

squote :: Text -> Text Source #

Surround some text in single quotes.

bquote :: Text -> Text Source #

Surround some text in backticks.

parens :: Text -> Text Source #

Surround some text in parentheses.

brackets :: Text -> Text Source #

Surround some text in square brackets.

commaList :: [Text] -> Text Source #

Make a list of things with commas and the word "and".

indefinite :: Text -> Text Source #

Prepend a noun with the proper indefinite article ("a" or "an").

indefiniteQ :: Text -> Text Source #

Prepend a noun with the proper indefinite article, and surround the noun in single quotes.

singularSubjectVerb :: Text -> Text -> Text Source #

Combine the subject word with the simple present tense of the verb.

Only some irregular verbs are handled, but it should be enough to scrap some error message boilerplate and have fun!

>>> :set -XOverloadedStrings
>>> singularSubjectVerb "I" "be"
"I am"
>>> singularSubjectVerb "he" "can"
"he can"
>>> singularSubjectVerb "The target robot" "do"
"The target robot does"

plural :: Text -> Text Source #

Pluralize a noun.

number :: Int -> Text -> Text Source #

Either pluralize a noun or not, depending on the value of the number.

Validation utilities

holdsOr :: Has (Throw e) sig m => Bool -> e -> m () Source #

Require that a Boolean value is True, or throw an exception.

isJustOr :: Has (Throw e) sig m => Maybe a -> e -> m a Source #

Require that a Maybe value is Just, or throw an exception.

isRightOr :: Has (Throw e) sig m => Either b a -> (b -> e) -> m a Source #

Require that an Either value is Right, or throw an exception based on the value in the Left.

isSuccessOr :: Has (Throw e) sig m => Validation b a -> (b -> e) -> m a Source #

Require that a Validation value is Success, or throw an exception based on the value in the Failure.

Template Haskell utilities

Lens utilities

(%%=) :: Has (State s) sig m => Over p ((,) r) s s a b -> p a (r, b) -> m r infix 4 Source #

(<%=) :: Has (State s) sig m => LensLike' ((,) a) s a -> (a -> a) -> m a infix 4 Source #

(<+=) :: (Has (State s) sig m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source #

(<<.=) :: Has (State s) sig m => LensLike ((,) a) s s a b -> b -> m a infix 4 Source #

(<>=) :: (Has (State s) sig m, Semigroup a) => ASetter' s a -> a -> m () infix 4 Source #

_NonEmpty :: Lens' (NonEmpty a) (a, [a]) Source #

Set utilities

removeSupersets :: Ord a => Set (Set a) -> Set (Set a) Source #

Remove any sets which are supersets of other sets. In other words, (1) no two sets in the output are in a subset relationship (2) every element in the input is a superset of some element in the output.

>>> import qualified Data.Set as S
>>> rss = map S.toList . S.toList . removeSupersets . S.fromList . map S.fromList
>>> rss [[1,2,3], [1]]
[[1]]
>>> rss [[1,2,3], [2,4], [2,3]]
[[2,3],[2,4]]
>>> rss [[], [1], [2,3]]
[[]]
>>> rss [[1,2], [1,3], [2,3]]
[[1,2],[1,3],[2,3]]

smallHittingSet :: Ord a => [Set a] -> Set a Source #

Given a list of nonempty sets, find a hitting set, that is, a set which has at least one element in common with each set in the list. It is not guaranteed to be the smallest possible such set, because that is NP-hard. Instead, we use a greedy algorithm that will give us a reasonably small hitting set: first, choose all elements in singleton sets, since those must necessarily be chosen. Now take any sets which are still not hit, and find an element which occurs in the largest possible number of remaining sets. Add this element to the set of chosen elements, and filter out all the sets it hits. Repeat, choosing a new element to hit the largest number of unhit sets at each step, until all sets are hit. This algorithm produces a hitting set which might be larger than optimal by a factor of lg(m), where m is the number of sets in the input.

>>> import qualified Data.Set as S
>>> shs = smallHittingSet . map S.fromList
>>> shs ["a"]
fromList "a"
>>> shs ["ab", "b"]
fromList "b"
>>> shs ["ab", "bc"]
fromList "b"
>>> shs ["acd", "c", "aef", "a"]
fromList "ac"
>>> shs ["abc", "abd", "acd", "bcd"]
fromList "cd"

Here is an example of an input for which smallHittingSet does not produce a minimal hitting set. "bc" is also a hitting set and is smaller. b, c, and d all occur in exactly two sets, but d is unluckily chosen first, leaving "be" and "ac" unhit and necessitating choosing one more element from each.

>>> shs ["bd", "be", "ac", "cd"]
fromList "cde"

Orphan instances