swarm-0.1.0.0: 2D resource gathering game with programmable robots
CopyrightBrent Yorgey
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
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.

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.

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"

getElemsInArea :: V2 Int64 -> Int64 -> Map (V2 Int64) e -> [e] Source #

Get elements that are in manhattan distance from location.

>>> v2s i = [(v, manhattan (V2 0 0) v) | x <- [-i..i], y <- [-i..i], let v = V2 x y]
>>> v2s 0
[(V2 0 0,0)]
>>> map (\i -> length (getElemsInArea (V2 0 0) i (M.fromList $ v2s i))) [0..8]
[1,5,13,25,41,61,85,113,145]

The last test is the sequence "Centered square numbers": https://oeis.org/A001844

manhattan :: V2 Int64 -> V2 Int64 -> Int64 Source #

Manhattan distance between world locations.

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.

getSwarmDataPath :: Bool -> IO FilePath Source #

Get path to swarm data, optionally creating necessary directories.

getSwarmSavePath :: Bool -> IO FilePath Source #

Get path to swarm saves, optionally creating necessary directories.

getSwarmHistoryPath :: Bool -> IO FilePath Source #

Get path to swarm history, optionally creating necessary directories. This could fail if user has bad permissions on his own $HOME or $XDG_DATA_HOME which is unlikely.

readAppData :: IO (Map Text Text) Source #

Read all the .txt files in the data/ directory.

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"

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.

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 #

Utilities for NP-hard approximation

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