Text.WordSearchSolver
Description
A word search solver library
This solver is case sensitive, but users can still map data consistently to one case before using this library.
- data WordSearch a
- ws_grid :: forall a[a1Fh]. :-> (WordSearch a[a1Fh]) (Grid a[a1Fh])
- ws_search :: forall a[a1Fh]. :-> (WordSearch a[a1Fh]) (Search a[a1Fh])
- data Grid a
- data Search a
- newtype Pos = Pos (PosIndex, PosIndex)
- type PosIndex = Integer
- data Match
- readWordSearch :: String -> Maybe (WordSearch Char)
- wordSearch :: Grid a -> Search a -> WordSearch a
- readGrid :: [String] -> Grid Char
- arrayToGrid :: Ord a => Array Pos a -> Grid a
- setToSearch :: Set [a] -> Search a
- solveWordSearch :: forall a. Ord a => WordSearch a -> Set Match
- fillMatches :: forall e t. (Foldable t, Ord e) => e -> Grid e -> t Match -> Grid e
- showGridInsert :: forall a. a -> Grid a -> [a]
Documentation
data WordSearch a Source
Abstract container of a word search puzzle
This can be created either from a Search
and a Grid
by the
wordSearch
function or from a properly formatted String
by the
readWordSearch
function.
Instances
Typeable1 WordSearch | |
Eq a => Eq (WordSearch a) | |
Ord a => Ord (WordSearch a) |
ws_grid :: forall a[a1Fh]. :-> (WordSearch a[a1Fh]) (Grid a[a1Fh])Source
ws_search :: forall a[a1Fh]. :-> (WordSearch a[a1Fh]) (Search a[a1Fh])Source
A grid in which to search
Constructors of this container usually assume that the grid is rectangular and properly sized; this precondition is not checked.
A set of words or lists to search
A position of a grid
readWordSearch :: String -> Maybe (WordSearch Char)Source
Constructs a WordSearch
container from a properly formatted String
The String
should contain two sections, separated by at least one empty
line. The first section represents the grid, and thus is formatted as the
String that readGrid
expects. The second section represents the search
words; it contains each word on its own separate line. In the case that
is ill-formed, Nothing is returned. The precondition that each grid row
has equal length is not checked.
wordSearch :: Grid a -> Search a -> WordSearch aSource
Constructs a WordSearch
container from a Grid
and a Search
setToSearch :: Set [a] -> Search aSource
Constructs a Search
from a set of lists
solveWordSearch :: forall a. Ord a => WordSearch a -> Set MatchSource
Solves a WordSearch
and returns a set of matches
fillMatches :: forall e t. (Foldable t, Ord e) => e -> Grid e -> t Match -> Grid eSource
Creates a Grid
in which every cell that does not match is set to a default value
showGridInsert :: forall a. a -> Grid a -> [a]Source
Renders a Grid
, appending a cell, usually a newline character, after every row