Skip to content

Commit

Permalink
Few naming updates
Browse files Browse the repository at this point in the history
  • Loading branch information
albertprz committed Nov 19, 2023
1 parent b412a43 commit 9fc342b
Show file tree
Hide file tree
Showing 8 changed files with 67 additions and 64 deletions.
1 change: 0 additions & 1 deletion bookhound.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,6 @@ library
Bookhound.Parsers.DateTime
Bookhound.Parsers.Number
Bookhound.Parsers.Text
Bookhound.Utils.Applicative
Bookhound.Utils.DateTime
Bookhound.Utils.Foldable
Bookhound.Utils.List
Expand Down
26 changes: 11 additions & 15 deletions src/Bookhound/ParserCombinators.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,13 @@
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}

module Bookhound.ParserCombinators (IsMatch(..), satisfy, char, string, times, many, some, multiple,
between, maybeBetween, surroundedBy, maybeSurroundedBy,
manySepBy, someSepBy, multipleSepBy, sepByOps, sepByOp, manyEndBy, someEndBy, multipleEndBy,
(<?>), (<#>), (</\>), (<:>), (->>-), (|?), (|*), (|+), (|++), (||?), (||*), (||+), (||++)) where
import Bookhound.Parser (Parser, allOf, anyChar, anyOf, except, satisfy,
withError)

import Bookhound.Utils.Applicative (extract)
import Bookhound.Utils.List (hasMultiple, hasSome)
import Bookhound.Utils.Text (ToString (..))
import Control.Applicative (liftA2, optional, (<|>))
import Bookhound.Utils.List (hasMultiple, hasSome)
import Bookhound.Utils.Text (ToString (..))
import Control.Applicative (liftA2, optional, (<|>))

import qualified Data.Foldable as Foldable
import Data.Text (Text, pack, unpack)
Expand Down Expand Up @@ -71,17 +67,17 @@ times n p


-- Between combinators
surroundedBy :: Parser a -> Parser b -> Parser c -> Parser c
surroundedBy = extract
between :: Parser a -> Parser b -> Parser c -> Parser c
between start end p = start *> p <* end

maybeSurroundedBy :: Parser a -> Parser b -> Parser c -> Parser c
maybeSurroundedBy p1 p2 = surroundedBy (p1 |?) (p2 |?)
maybeBetween :: Parser a -> Parser b -> Parser c -> Parser c
maybeBetween p1 p2 = between (p1 |?) (p2 |?)

between :: Parser a -> Parser b -> Parser b
between p = surroundedBy p p
surroundedBy :: Parser a -> Parser b -> Parser b
surroundedBy p = between p p

maybeBetween :: Parser a -> Parser b -> Parser b
maybeBetween p = between (p |?)
maybeSurroundedBy :: Parser a -> Parser b -> Parser b
maybeSurroundedBy p = surroundedBy (p |?)


-- Sep by combinators
Expand Down
41 changes: 28 additions & 13 deletions src/Bookhound/Parsers/Char.hs
Original file line number Diff line number Diff line change
@@ -1,29 +1,34 @@
module Bookhound.Parsers.Char where
module Bookhound.Parsers.Char (module AnyChar, digit, hexDigit, octDigit, upper, lower, alpha, alphaNum, space, tab, newLine, spaceOrTab, whiteSpace, comma, dot, colon, quote, doubleQuote, dash, plus, equal, underscore, hashTag, question, openParens, closeParens, openSquare, closeSquare, openCurly, closeCurly, openAngle, closeAngle) where

import Bookhound.ParserCombinators (IsMatch (..))
import qualified Bookhound.Parser as AnyChar (anyChar)
import qualified Bookhound.Parser as Parser
import Bookhound.ParserCombinators (IsMatch (..))

import Bookhound.Parser (Parser)
import Bookhound.Parser (Parser, anyChar)
import Control.Applicative

import Data.Char (isAsciiLower, isAsciiUpper, isDigit, isHexDigit,
isOctDigit)

digit :: Parser Char
digit = oneOf ['0' .. '9']
digit = satisfy isDigit

hexDigit :: Parser Char
hexDigit = satisfy isHexDigit

octDigit :: Parser Char
octDigit = satisfy isOctDigit

upper :: Parser Char
upper = oneOf ['A' .. 'Z']
upper = satisfy isAsciiUpper

lower :: Parser Char
lower = oneOf ['a' .. 'z']

letter :: Parser Char
letter = upper <|> lower
lower = satisfy isAsciiLower

alpha :: Parser Char
alpha = letter
alpha = satisfy isAlpha

alphaNum :: Parser Char
alphaNum = alpha <|> digit

alphaNum = satisfy isAlphaNum


space :: Parser Char
Expand Down Expand Up @@ -99,3 +104,13 @@ openAngle = is '<'

closeAngle :: Parser Char
closeAngle = is '>'


isAlpha :: Char -> Bool
isAlpha x = isAsciiLower x || isAsciiUpper x

isAlphaNum :: Char -> Bool
isAlphaNum x = isAlpha x || isDigit x

satisfy :: (Char -> Bool) -> Parser Char
satisfy = flip Parser.satisfy anyChar
6 changes: 3 additions & 3 deletions src/Bookhound/Parsers/Collections.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Bookhound.Parsers.Collections (collOf, listOf, tupleOf, mapOf) where

import Bookhound.Parser (Parser, satisfy, withErrorN)
import Bookhound.ParserCombinators (manySepBy, maybeBetween)
import Bookhound.ParserCombinators (manySepBy, maybeSurroundedBy)
import Bookhound.Parsers.Char (closeCurly, closeParens, closeSquare, comma,
openCurly, openParens, openSquare)
import Bookhound.Parsers.Text (spacing)
Expand All @@ -15,7 +15,7 @@ collOf :: Parser a -> Parser b -> Parser c -> Parser d -> Parser [d]
collOf start end sep elemParser =
start *> elemsParser <* end
where
elemsParser = manySepBy sep $ maybeBetween spacing elemParser
elemsParser = manySepBy sep $ maybeSurroundedBy spacing elemParser


listOf :: Parser a -> Parser [a]
Expand All @@ -33,4 +33,4 @@ mapOf :: Ord b => Parser a -> Parser b -> Parser c -> Parser (Map b c)
mapOf sep p1 p2 = withErrorN (-1) "Map" $
Map.fromList <$> collOf openCurly closeCurly comma mapEntry
where
mapEntry = (,) <$> p1 <* maybeBetween spacing sep <*> p2
mapEntry = (,) <$> p1 <* maybeSurroundedBy spacing sep <*> p2
5 changes: 3 additions & 2 deletions src/Bookhound/Parsers/DateTime.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
module Bookhound.Parsers.DateTime (date, time, timeZoneOffset, localDateTime, offsetDateTime, dateTime, year, day, month, hour, minute, second) where

import Bookhound.Parser (Parser, satisfy, withErrorN)
import Bookhound.ParserCombinators (IsMatch (..), between, (<#>), (|+), (|?))
import Bookhound.ParserCombinators (IsMatch (..), surroundedBy, (<#>), (|+),
(|?))
import Bookhound.Parsers.Char (colon, dash, digit, dot, plus)
import Control.Applicative

Expand All @@ -12,7 +13,7 @@ import Data.Time (Day, LocalTime (..), TimeOfDay (..), TimeZone,

date :: Parser Day
date = withErrorN (-1) "Date" $
fromGregorian <$> year <*> between dash month <*> day
fromGregorian <$> year <*> surroundedBy dash month <*> day


time :: Parser TimeOfDay
Expand Down
31 changes: 14 additions & 17 deletions src/Bookhound/Parsers/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Bookhound.ParserCombinators (IsMatch (..), between,
import Bookhound.Parsers.Char (alpha, alphaNum, closeAngle,
closeCurly, closeParens,
closeSquare, digit, doubleQuote,
letter, lower, newLine, openAngle,
lower, newLine, openAngle,
openCurly, openParens, openSquare,
quote, space, spaceOrTab, tab,
upper, whiteSpace)
Expand All @@ -31,9 +31,6 @@ uppers = (upper ||+)
lowers :: Parser Text
lowers = (lower ||+)

letters :: Parser Text
letters = (letter ||+)

alphas :: Parser Text
alphas = (alpha ||+)

Expand Down Expand Up @@ -66,39 +63,39 @@ blankLines = fmap Text.concat (blankLine |+)


betweenQuotes :: Parser b -> Parser b
betweenQuotes = between quote
betweenQuotes = surroundedBy quote

betweenDoubleQuotes :: Parser b -> Parser b
betweenDoubleQuotes = between doubleQuote
betweenDoubleQuotes = surroundedBy doubleQuote

betweenParens :: Parser b -> Parser b
betweenParens = surroundedBy openParens closeParens
betweenParens = between openParens closeParens

betweenSquareBrackets :: Parser b -> Parser b
betweenSquareBrackets = surroundedBy openSquare closeSquare
betweenSquare :: Parser b -> Parser b
betweenSquare = between openSquare closeSquare

betweenCurlyBrackets :: Parser b -> Parser b
betweenCurlyBrackets = surroundedBy openCurly closeCurly
betweenCurlyBrackets = between openCurly closeCurly

betweenAngleBrackets :: Parser b -> Parser b
betweenAngleBrackets = surroundedBy openAngle closeAngle
betweenAngleBrackets = between openAngle closeAngle



maybeBetweenQuotes :: Parser b -> Parser b
maybeBetweenQuotes = maybeBetween quote
maybeBetweenQuotes = maybeSurroundedBy quote

maybeBetweenDoubleQuotes :: Parser b -> Parser b
maybeBetweenDoubleQuotes = maybeBetween doubleQuote
maybeBetweenDoubleQuotes = maybeSurroundedBy doubleQuote

maybeBetweenParens :: Parser b -> Parser b
maybeBetweenParens = maybeSurroundedBy openParens closeParens
maybeBetweenParens = maybeBetween openParens closeParens

maybeBetweenSquareBrackets :: Parser b -> Parser b
maybeBetweenSquareBrackets = maybeSurroundedBy openSquare closeSquare
maybeBetweenSquareBrackets = maybeBetween openSquare closeSquare

maybeBetweenCurlyBrackets :: Parser b -> Parser b
maybeBetweenCurlyBrackets = maybeSurroundedBy openCurly closeCurly
maybeBetweenCurlyBrackets = maybeBetween openCurly closeCurly

maybeBetweenAngleBrackets :: Parser b -> Parser b
maybeBetweenAngleBrackets = maybeSurroundedBy openAngle closeAngle
maybeBetweenAngleBrackets = maybeBetween openAngle closeAngle
5 changes: 0 additions & 5 deletions src/Bookhound/Utils/Applicative.hs

This file was deleted.

16 changes: 8 additions & 8 deletions test/Bookhound/ParserCombinatorsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,35 +55,35 @@ spec = do
===
parseTimes anyChar [2 .. Text.length x + 10] x

describe "surroundedBy" $
describe "between" $

prop "applies a parser surrounded by 2 parsers" $
\x (y :: Char) (z :: Char) ->
parse (surroundedBy (is y) (is z) anyChar) x
parse (between (is y) (is z) anyChar) x
===
parse (is y *> anyChar <* is z) x

describe "maybeSurroundedBy" $
describe "maybeBetween" $

prop "applies a parser surrounded by 2 optional parsers" $
\x (y :: Char) (z :: Char) ->
parse (maybeSurroundedBy (is y) (is z) anyChar) x
parse (maybeBetween (is y) (is z) anyChar) x
===
parse ((is y |?) *> anyChar <* (is z |?)) x

describe "between" $
describe "surroundedBy" $

prop "applies a parser surrounded by a parser" $
\x (y :: Char) ->
parse (between (is y) anyChar) x
parse (surroundedBy (is y) anyChar) x
===
parse (is y *> anyChar <* is y) x

describe "maybeBetween" $
describe "maybeSurroundedBy" $

prop "applies a parser surrounded by a optional parsers" $
\x (y :: Char) ->
parse (maybeBetween (is y) anyChar) x
parse (maybeSurroundedBy (is y) anyChar) x
===
parse ((is y |?) *> anyChar <* (is y |?)) x

Expand Down

0 comments on commit 9fc342b

Please sign in to comment.