advent-of-code-ocr-0.1.2.1: Parse Advent of Code ASCII art letters
Copyright(c) Justin Le 2020
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Advent.OCR

Description

Library to parse "ASCII Art" letters from <https://adventofcode.com Advent of Code> puzzles. Compatible with all puzzles from 2015 to 2019.

Synopsis

Parse

parseLetters Source #

Arguments

:: Set (Int, Int)

set of points

-> Maybe String

result, with unknown letters replaced with "?"

The go-to default: given a set of point coordinates, parse it into the string it represents. Should be compatible with any Advent of Code challenge from 2015 to 2019.

parseLetters defaultLetterMap myPoints

-- or, using Data.Default
parseLetters def myPoints

A Nothing means that there were no recognized letters found. A Just means that least 50% of letter forms are recognized. Unrecognized characters will be replaced with "?"; for more information, use parseLettersEither.

This function is robust to changes in orientation or flipping, but will be fastest if the coordinates are oriented with (0,0) on the upper left corner. However, because of this, it might return the wrong answer if your coordinates are not oriented this way and your result is symmetrical: it'll always prioritize the interpretaion against (0,0) upper-left orientation first.

parseLettersWith Source #

Arguments

:: (a -> Int)

get X

-> (a -> Int)

get Y

-> Set a 
-> Maybe String 

A version of parseLetters that takes a set of any type of value, as long as you provide functions to access the X and Y coordinates.

parseLettersEither :: Set (Int, Int) -> Maybe [Either (Set (Int, Int)) Char] Source #

A version of parseLetters returning a list of characters that were either recognized or unrecognized; in the case of unrecognized characters, returns the set of their coordinates but shifted to (0, 0) as its upper left corner.

unsafeParseLetters :: Set (Int, Int) -> String Source #

A version of parseLetters that will be undefined (error) when no parse is found.

parseAsciiMap Source #

Arguments

:: Set Char

characters to use as "on"/included

-> String

raw ASCII art

-> Set (Int, Int) 

Parse raw ASCII art into a set of points, usable with parseLetters.

asciiMapToLetters Source #

Arguments

:: Set Char

characters to use as "on"/included in ASCII art

-> String

raw ASCII art

-> Maybe String 

Convenient all-in-one utility function combining parseAsciiMap and parseLetters, to directly parse ASCII art into its letters.

Letter Map

data LetterMap Source #

A database associating a set of "on" points to the letter they represent.

See defaultLetterMap for a database compatible with Advent of Code 2015-2019.

Instances

Instances details
Data LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LetterMap -> c LetterMap #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LetterMap #

toConstr :: LetterMap -> Constr #

dataTypeOf :: LetterMap -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LetterMap) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LetterMap) #

gmapT :: (forall b. Data b => b -> b) -> LetterMap -> LetterMap #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LetterMap -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LetterMap -> r #

gmapQ :: (forall d. Data d => d -> u) -> LetterMap -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LetterMap -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LetterMap -> m LetterMap #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LetterMap -> m LetterMap #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LetterMap -> m LetterMap #

Monoid LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Semigroup LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Generic LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Associated Types

type Rep LetterMap :: Type -> Type #

Show LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Default LetterMap Source #

Default is compatible with all challenges in Advent of Code 2015 to 2019.

Instance details

Defined in Advent.OCR.Internal

Methods

def :: LetterMap #

Eq LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Ord LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Lift LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

Methods

lift :: Quote m => LetterMap -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => LetterMap -> Code m LetterMap #

type Rep LetterMap Source # 
Instance details

Defined in Advent.OCR.LetterMap

type Rep LetterMap = D1 ('MetaData "LetterMap" "Advent.OCR.LetterMap" "advent-of-code-ocr-0.1.2.1-Lh8la7tptHeJXsL9QW6ry6" 'True) (C1 ('MetaCons "LetterMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLetterMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Set Point) Char))))

defaultLetterMap :: LetterMap Source #

The default lettermap compatible all challenges in Advent of Code 2015 - 2019.

Custom Letter Map

parseLetters' Source #

Arguments

:: LetterMap

database of letterforms

-> Set (Int, Int)

set of points

-> Maybe String

result, with unknown letters replaced with "?"

A version of parseLetters' accepting a custom LetterMap letterform database.

parseLettersWith' Source #

Arguments

:: LetterMap

database of letterforms

-> (a -> Int)

get X

-> (a -> Int)

get Y

-> Set a 
-> Maybe String 

A version of parseLettersWith' accepting a custom LetterMap letterform database.

parseLettersEither' Source #

Arguments

:: LetterMap

database of letterforms

-> Set (Int, Int) 
-> Maybe [Either (Set (Int, Int)) Char] 

A version of parseLettersEither' accepting a custom LetterMap letterform database.

unsafeParseLetters' :: LetterMap -> Set (Int, Int) -> String Source #

A version of unsafeParseLetters' accepting a custom LetterMap letterform database.

asciiMapToLetters' Source #

Arguments

:: Set Char

characters to use as "on"/included in ASCII art

-> LetterMap

database of letterforms

-> String

raw ASCII art

-> Maybe String 

A version of asciiMapToLetters' accepting a custom LetterMap letterform database.