wordsearch-1.0.1: A word search solver library and executable

Text.WordSearchSolver

Contents

Description

A word search solver library

This solver is case sensitive; users should map data consistently to one case before using this library when such behavior is desired.

Synopsis

Types and containers

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) 
(Data a, Ord a) => Data (WordSearch a) 
Ord a => Ord (WordSearch a) 
(Ord a, Read a) => Read (WordSearch a) 
Show a => Show (WordSearch a) 

ws_grid :: forall a[a1Pa]. :-> (WordSearch a[a1Pa]) (Grid a[a1Pa])Source

ws_search :: forall a[a1Pa]. :-> (WordSearch a[a1Pa]) (Search a[a1Pa])Source

data Grid a 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.

Instances

Typeable1 Grid 
Eq a => Eq (Grid a) 
(Data a, Ord a) => Data (Grid a) 
Ord a => Ord (Grid a) 
(Ord a, Read a) => Read (Grid a) 
Show a => Show (Grid a) 

data Search a Source

A set of words or lists to search

Instances

Typeable1 Search 
Eq a => Eq (Search a) 
(Data a, Ord a) => Data (Search a) 
Ord a => Ord (Search a) 
(Ord a, Read a) => Read (Search a) 
Show a => Show (Search a) 

newtype Pos Source

A position of a grid

Constructors

Pos (PosIndex, PosIndex) 

type PosIndex = IntegerSource

The integral type used for Pos

data Match Source

An individual value describing a match

Constructors

Match 

Fields

_m_dir :: Dir
 
_m_len :: Integer
 
_m_pos :: Pos
 

data Dir Source

Constructors

N 
NW 
W 
SW 
S 
SE 
E 
NE 

WordSearch puzzles

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

solveWordSearch :: (Eq a, Ord a) => WordSearch a -> (Set Match, Search a)Source

Solves a WordSearch and returns a set of matches together with a set of search terms for which a match was not found in a tuple

This algorithm solves word search puzzles by looking at the first cell of each search term, and looking for a match by checking each direction from each position whose cell contains the starting cell of the search term until a match is found. The dictionary of individual cell values and sets of positions is part of the Grid container; arrayToGrid creates this dictionary automatically.

search :: Eq a => Grid a -> [a] -> Pos -> Maybe MatchSource

Determines whether a given Search term can be matched at a given position of a grid

This is done by trying each direction for a match from the given location.

tryMatch :: Eq a => Grid a -> [a] -> Pos -> Dir -> Maybe MatchSource

If the location and the direction matches the Search term, returns the Match; otherwise, returns Nothing

Grid and Search containers

readGrid :: [String] -> Grid CharSource

Constructs a Grid from a formatted list of Strings

The String should be formatted as expected:

["aoaoenxrcoedxncd",
 "aoesnitdaoeusntd",
 "itenohtneahuoteh"]

The precondition that each row has equal length is not checked.

arrayToGrid :: Ord a => Array Pos a -> Grid aSource

Constructs a Grid from an Array

A grid array is indexed by (column, row) or (x, y), so users should be careful that a list is in the proper order if listArray is used.

setToSearch :: Set [a] -> Search aSource

Constructs a Search from a set of lists

searchToSet :: Search a -> Set [a]Source

Returns the set of search terms from a Search container

Operations on solutions and rendering Grids

fillMatches :: (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 :: a -> Grid a -> [a]Source

Renders a Grid, appending a cell, usually a newline character, after every row

Dirs

dirs :: [Dir]Source

Complete set of possible Grid Match directions

dirs' :: Set DirSource

More efficient (and real, unordered) Set of dirs

dirsPos :: Map Dir PosSource

Map of directions and Pos offsets

dirsOpposite :: Map Dir DirSource

Bidirectional Map of opposite directions

dirToOffset :: Dir -> PosSource

Returns the appropriate offset of a direction

dirOpposite :: Dir -> DirSource

Returns the opposite direction

dirUpdatePos :: Dir -> Pos -> PosSource

Updates a position by one step in the given direction

Helper functions

inRangeOf :: Ix a => a -> Array a e -> BoolSource

Determines whether an index is within the range of the bounds of an array

posPlus :: Pos -> Pos -> PosSource

Adds two positions