Skip to content

Commit

Permalink
Bumped bookhound to 0.1.7
Browse files Browse the repository at this point in the history
  • Loading branch information
albertprz committed Nov 21, 2023
1 parent 3a77207 commit 7070d0a
Show file tree
Hide file tree
Showing 9 changed files with 39 additions and 41 deletions.
4 changes: 2 additions & 2 deletions packages.dhall
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
let upstream =
https://github.com/purescript/package-sets/releases/download/psc-0.15.12-20231109/packages.dhall
sha256:f91a6a26ed0ad8402db57aa9e7e21d20224bf56018e7ba1728bcdbee584a9628
https://github.com/purescript/package-sets/releases/download/psc-0.15.12-20231120/packages.dhall
sha256:4c066f08ee174c39f5a65f7899f8e3dafdf75c416747eda8a6c6f47e4ac4faaa

let overrides =
{ spec-discovery.version = "v8.2.0"
Expand Down
6 changes: 3 additions & 3 deletions src/Components/Table/SyntaxAtom.purs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Bookhound.ParserCombinators (is, noneOf, oneOf, (->>-), (|*), (|+), (||*)
import Bookhound.Parsers.Char (alpha, alphaNum, lower, quote, underscore)
import Bookhound.Parsers.Char as Parsers
import Bookhound.Parsers.Number (double, int)
import Bookhound.Parsers.String (withinDoubleQuotes, withinQuotes)
import Bookhound.Parsers.String (betweenDoubleQuotes, betweenQuotes)
import Data.String.CodeUnits (singleton) as String
import Data.String.Unsafe (char) as String
import Web.HTML.Common (ClassName)
Expand Down Expand Up @@ -55,9 +55,9 @@ syntaxAtomParser = (|+) atom
<|> (OtherText <<< String.singleton <$> Parsers.anyChar)

char = wrapQuotes <<< String.singleton
<$> withinQuotes (charLit <|> charLitEscaped)
<$> betweenQuotes (charLit <|> charLitEscaped)
string = wrapDoubleQuotes
<$> withinDoubleQuotes ((||*) (stringLit <|> charLitEscaped))
<$> betweenDoubleQuotes ((||*) (stringLit <|> charLitEscaped))
charLit = noneOf [ '\'', '\\' ]
charLitEscaped = String.char <<< wrapQuotes <$> (is '\\' ->>- alpha)
<|> (is '\\' *> Parsers.anyChar)
Expand Down
4 changes: 2 additions & 2 deletions src/FatPrelude.purs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ import Control.Monad.State (class MonadState, StateT(..), evalState, evalStateT,
import Control.Monad.Trans.Class (class MonadTrans, lift) as X
import Control.MonadPlus (class Alt, class Alternative, class MonadPlus, class Plus, alt, empty, guard, (<|>)) as X
import Data.Array (length) as X
import Data.Array.NonEmpty (NonEmptyArray, alterAt, appendArray, concat, concatMap, cons, cons', delete, deleteAt, deleteBy, difference, difference', drop, dropEnd, dropWhile, elemIndex, elemLastIndex, filterA, findIndex, findLastIndex, foldRecM, fromArray, group, groupAll, groupAllBy, groupBy, head, index, init, insert, insertAt, insertBy, intersect, intersect', intersectBy, intersectBy', intersperse, last, modifyAt, modifyAtIndices, nub, nubBy, nubByEq, nubEq, prependArray, replicate, reverse, singleton, slice, snoc, snoc', some, sort, sortBy, sortWith, span, splitAt, tail, take, takeEnd, takeWhile, toArray, transpose, transpose', uncons, union, union', unionBy, unionBy', unsafeIndex, unsnoc, unzip, updateAt, updateAtIndices, zip, zipWith, zipWithA, (!!), (\\)) as X
import Data.Array.NonEmpty (NonEmptyArray, alterAt, appendArray, concat, concatMap, cons, cons', delete, deleteAt, deleteBy, difference, difference', drop, dropEnd, dropWhile, elemIndex, elemLastIndex, filterA, findIndex, findLastIndex, foldRecM, fromArray, group, groupAll, groupAllBy, groupBy, head, index, init, insert, insertAt, insertBy, intersect, intersect', intersectBy, intersectBy', intersperse, last, modifyAt, modifyAtIndices, nub, nubBy, nubByEq, nubEq, prependArray, replicate, reverse, singleton, slice, snoc, snoc', sort, sortBy, sortWith, span, splitAt, tail, take, takeEnd, takeWhile, toArray, transpose, transpose', uncons, union, union', unionBy, unionBy', unsafeIndex, unsnoc, unzip, updateAt, updateAtIndices, zip, zipWith, zipWithA, (!!), (\\)) as X
import Data.Bifunctor (class Bifunctor, bimap, lmap, rmap) as X
import Data.Bitraversable (class Bifoldable, class Bitraversable, biall, biany, bifold, bifoldMap, bifoldl, bifoldr, bifor, bifor_, bisequence, bisequence_, bitraverse, bitraverse_, lfor, ltraverse, rfor, rtraverse) as X
import Data.Char (fromCharCode, toCharCode) as X
Expand Down Expand Up @@ -52,5 +52,5 @@ import Effect.Class (class MonadEffect, liftEffect) as X
import Effect.Exception (Error, error, throw) as X
import PSCI.Support (class Eval) as X
import PointFree ((#~), (#~~), (#~~~), (...>), (..>), (.>), (<.), (<..), (<...), (<~.), (<~..), (<~...), (<~~.), (<~~..), (<~~~.), (~$), (~...>), (~..>), (~.>), (~~$), (~~..>), (~~.>), (~~~$), (~~~.>)) as X
import Prelude (class Applicative, class Apply, class Bind, class BooleanAlgebra, class Bounded, class Category, class CommutativeRing, class Discard, class DivisionRing, class Eq, class EuclideanRing, class Field, class Functor, class HeytingAlgebra, class Monad, class Monoid, class Ord, class Ring, class Semigroup, class Semigroupoid, class Semiring, class Show, type (~>), Ordering(..), Unit, Void, absurd, add, ap, append, apply, between, bind, bottom, clamp, compare, comparing, compose, conj, const, degree, discard, disj, div, eq, flap, flip, gcd, identity, ifM, join, lcm, liftA1, liftM1, map, max, mempty, min, mod, mul, negate, not, notEq, one, otherwise, pure, recip, show, sub, top, unit, unless, unlessM, void, when, whenM, zero, (#), ($), ($>), (&&), (*), (*>), (+), (-), (/), (/=), (<), (<#>), (<$), (<$>), (<*), (<*>), (<<<), (<=), (<=<), (<>), (<@>), (=<<), (==), (>), (>=), (>=>), (>>=), (>>>), (||)) as X
import Prelude (class Applicative, class Apply, class Bind, class BooleanAlgebra, class Bounded, class Category, class CommutativeRing, class Discard, class DivisionRing, class Eq, class EuclideanRing, class Field, class Functor, class HeytingAlgebra, class Monad, class Monoid, class Ord, class Ring, class Semigroup, class Semigroupoid, class Semiring, class Show, type (~>), Ordering(..), Unit, Void, absurd, add, ap, append, apply, bind, bottom, clamp, compare, comparing, compose, conj, const, degree, discard, disj, div, eq, flap, flip, gcd, identity, ifM, join, lcm, liftA1, liftM1, map, max, mempty, min, mod, mul, negate, not, notEq, one, otherwise, pure, recip, show, sub, top, unit, unless, unlessM, void, when, whenM, zero, (#), ($), ($>), (&&), (*), (*>), (+), (-), (/), (/=), (<), (<#>), (<$), (<$>), (<*), (<*>), (<<<), (<=), (<=<), (<>), (<@>), (=<<), (==), (>), (>=), (>=>), (>>=), (>>>), (||)) as X
import Type.Prelude (Proxy(..)) as X
16 changes: 8 additions & 8 deletions src/Parser/Common.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,20 +5,20 @@ import FatPrelude
import App.Components.Table.Cell (CellValue(..))
import App.SyntaxTree.Common (Module(..), QVar(..), QVarOp(..), Var(..), VarOp(..))
import Bookhound.Parser (Parser, satisfy, withTransform)
import Bookhound.ParserCombinators (class IsMatch, is, maybeWithin, noneOf, oneOf, someSepBy, within, (->>-), (</\>), (|*), (|?), (||*))
import Bookhound.ParserCombinators (class IsMatch, is, noneOf, oneOf, someSepBy, surroundedBy, (->>-), (</\>), (|*), (|?), (||*))
import Bookhound.Parsers.Char (alpha, alphaNum, anyChar, comma, dot, lower, upper)
import Bookhound.Parsers.Number (double, int)
import Bookhound.Parsers.String (spacing, withinDoubleQuotes, withinParens, withinQuotes)
import Bookhound.Parsers.String (betweenDoubleQuotes, betweenParens, betweenQuotes, maybeBetweenSpacing)
import Data.String.Unsafe (char) as String

cellValue :: Parser CellValue
cellValue = token
$ (FloatVal <$> double)
<|> (IntVal <$> int)
<|> (BoolVal <$> (true <$ isToken "true" <|> false <$ isToken "false"))
<|> (CharVal <$> withinQuotes (charLit <|> charLitEscaped))
<|> (CharVal <$> betweenQuotes (charLit <|> charLitEscaped))
<|>
( StringVal <$> withinDoubleQuotes
( StringVal <$> betweenDoubleQuotes
((||*) (stringLit <|> charLitEscaped))
)
where
Expand Down Expand Up @@ -49,7 +49,7 @@ qVarOp = uncurry QVarOp <$> qTerm
extractVar (Var x) = x

argListOf :: forall a. Parser a -> Parser (Array a)
argListOf = withinParens <<< someSepBy comma
argListOf = betweenParens <<< someSepBy comma

ident :: Parser Char -> Parser String
ident start = token $ start ->>- (|*) alphaNum
Expand All @@ -67,7 +67,7 @@ opSymbol :: Parser Char
opSymbol = oneOf opSymbolChars

token :: forall a. Parser a -> Parser a
token = withTransform (maybeWithin spacing)
token = withTransform maybeBetweenSpacing

isToken :: forall a. IsMatch a => a -> Parser a
isToken = token <<< is
Expand All @@ -83,8 +83,8 @@ notReservedSymbol = satisfy $ flip notElem reservedSymbols
notReservedKeyword :: Parser String -> Parser String
notReservedKeyword = satisfy $ flip notElem reservedKeywords

withinBackQuotes :: forall b. Parser b -> Parser b
withinBackQuotes = within $ isToken '`'
betweenBackQuotes :: forall b. Parser b -> Parser b
betweenBackQuotes = surroundedBy $ isToken '`'

opSymbolChars :: Array Char
opSymbolChars =
Expand Down
28 changes: 14 additions & 14 deletions src/Parser/FnDef.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,11 +8,11 @@ import App.Parser.Pattern (pattern')
import App.Parser.Type (type')
import App.SyntaxTree.FnDef (Associativity(..), CaseBinding(..), FnBody(..), FnDef(..), Guard(..), GuardedFnBody(..), MaybeGuardedFnBody(..), OpDef(..), PatternGuard(..))
import Bookhound.Parser (Parser, withError)
import Bookhound.ParserCombinators (is, sepByOps, someSepBy, within, (</\>), (|+), (|?))
import Bookhound.ParserCombinators (is, sepByOps, someSepBy, surroundedBy, (</\>), (|+), (|?))
import Bookhound.Parsers.Char (comma, quote)
import Bookhound.Parsers.Collections (listOf)
import Bookhound.Parsers.Number (unsignedInt)
import Bookhound.Parsers.String (withinCurlyBrackets, withinParens, withinSquareBrackets)
import Bookhound.Parsers.String (betweenCurly, betweenParens, betweenSquare)
import Control.Lazy (defer)

opDef :: Parser OpDef
Expand Down Expand Up @@ -57,23 +57,23 @@ fnBody = whereExpr <|> topLevelExpr

whereExpr = defer \_ -> WhereExpr
<$> topLevelExpr
<*> (isToken "where" *> withinContext "|" fnDef)
<*> (isToken "where" *> betweenContext "|" fnDef)

condExpr = defer \_ -> CondExpr <$>
( isToken "cond" *> withinCurlyBrackets
( isToken "cond" *> betweenCurly
((|+) (guardedFnBody (isToken "=>")))
)
switchExpr = defer \_ -> SwitchExpr
<$> (isToken "switch" *> withinParens openForm)
<*> withinContext "|" caseBinding
<$> (isToken "switch" *> betweenParens openForm)
<*> betweenContext "|" caseBinding

cellMatrixRange = defer \_ -> withinSquareBrackets
$ within (isToken "||")
cellMatrixRange = defer \_ -> betweenSquare
$ surroundedBy (isToken "||")
(CellMatrixRange <$> (cell <* isToken "..") <*> cell)
cellArrayRange = defer \_ -> withinSquareBrackets
$ within (isToken "|")
cellArrayRange = defer \_ -> betweenSquare
$ surroundedBy (isToken "|")
(CellArrayRange <$> (cell <* isToken "..") <*> cell)
arrayRange = defer \_ -> withinSquareBrackets
arrayRange = defer \_ -> betweenSquare
(ArrayRange <$> (openForm <* isToken "..") <*> openForm)

array = defer \_ -> Array' <$> (token (listOf openForm))
Expand All @@ -98,7 +98,7 @@ fnBody = whereExpr <|> topLevelExpr
<|> fnVar

complexForm = defer \_ -> lambdaFn <|> opSection <|> infixFnApply
complexInfixForm = defer \_ -> withinParens complexForm
complexInfixForm = defer \_ -> betweenParens complexForm

caseBinding :: Parser CaseBinding
caseBinding = defer \_ -> CaseBinding
Expand Down Expand Up @@ -127,8 +127,8 @@ patternGuard = defer \_ ->
statements :: forall a. String -> Parser a -> Parser (Array a)
statements sep parser = (|+) (isToken sep *> parser)

withinContext :: forall a. String -> Parser a -> Parser (Array a)
withinContext sep = withinCurlyBrackets <<< statements sep
betweenContext :: forall a. String -> Parser a -> Parser (Array a)
betweenContext sep = betweenCurly <<< statements sep

mandatory :: forall a. Parser (Maybe a) -> Parser a
mandatory maybeP =
Expand Down
8 changes: 4 additions & 4 deletions src/Parser/Pattern.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ import App.SyntaxTree.Pattern (Pattern(..))
import Bookhound.Parser (Parser)
import Bookhound.Parsers.Char (underscore)
import Bookhound.Parsers.Collections (listOf)
import Bookhound.Parsers.String (withinParens)
import Bookhound.Parsers.String (betweenParens)
import Control.Lazy (defer)

pattern' :: Parser Pattern
Expand All @@ -27,10 +27,10 @@ pattern' = openForm
<|> var'
complexForm = defer \_ -> alias <|> complexInfixForm
complexInfixForm = defer \_ ->
withinParens alias
betweenParens alias
infixArgForm = defer \_ ->
complexInfixForm
<|> withinParens complexInfixForm
<|> betweenParens complexInfixForm
<|> singleForm
openForm = defer \_ -> complexForm <|> singleForm
<|> withinParens (complexForm <|> singleForm)
<|> betweenParens (complexForm <|> singleForm)
8 changes: 4 additions & 4 deletions src/Parser/Type.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import App.SyntaxTree.Type (Type(..), TypeParam(..), TypeVar(..))
import Bookhound.Parser (Parser, satisfy)
import Bookhound.ParserCombinators (multipleSepBy)
import Bookhound.Parsers.Char (upper)
import Bookhound.Parsers.String (withinParens, withinSquareBrackets)
import Bookhound.Parsers.String (betweenParens, betweenSquare)
import Control.Lazy (defer)
import Data.String as String

Expand All @@ -27,12 +27,12 @@ type' = defer \_ -> arrow <|> union <|> atom
<|> (ParamTypeApply <$> typeParam <*> argListOf type')

arrow = defer \_ -> ArrowTypeApply <$> multipleSepBy (isToken "->")
(atom <|> union <|> withinParens arrow)
(atom <|> union <|> betweenParens arrow)

union = defer \_ -> UnionTypeApply <$> multipleSepBy (isToken "|")
(atom <|> arrow <|> withinParens union)
(atom <|> arrow <|> betweenParens union)

array = defer \_ -> ArrayTypeApply <$> withinSquareBrackets type'
array = defer \_ -> ArrayTypeApply <$> betweenSquare type'

typeVar' = TypeVar' <$> typeVar
typeParam' = TypeParam' <$> typeParam
Expand Down
3 changes: 1 addition & 2 deletions src/Utils/Bounded.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,9 @@ import Prelude

import App.Utils.Maybe (whenMaybe')
import App.Utils.Number (inc)
import Bookhound.FatPrelude (class Newtype)
import Data.Enum (class BoundedEnum, Cardinality, enumFromTo)
import Data.Maybe (Maybe)
import Data.Newtype (unwrap, wrap)
import Data.Newtype (class Newtype, unwrap, wrap)
import Data.Unfoldable1 (class Unfoldable1)

infixr 8 enumFromTo as ..
Expand Down
3 changes: 1 addition & 2 deletions src/Utils/Maybe.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,7 @@ module App.Utils.Maybe where

import Prelude

import Bookhound.FatPrelude (fromJust)
import Data.Maybe (Maybe(..))
import Data.Maybe (Maybe(..), fromJust)
import Partial.Unsafe (unsafePartial)

whenMaybe :: forall a. Boolean -> a -> Maybe a
Expand Down

0 comments on commit 7070d0a

Please sign in to comment.