Skip to content
This repository was archived by the owner on Jun 15, 2023. It is now read-only.

removed argonaut encode/decode, updated for PS@0.12 #45

Merged
merged 1 commit into from
Jun 28, 2018
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
20 changes: 8 additions & 12 deletions bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -15,19 +15,15 @@
"package.json"
],
"dependencies": {
"purescript-prelude": "^3.1.0",
"purescript-matryoshka": "^0.3.0",
"purescript-pathy": "^5.0.0",
"purescript-profunctor": "^3.2.0",
"purescript-profunctor-lenses": "^3.2.0",
"purescript-ejson": "^10.0.1",
"purescript-argonaut-codecs": "^3.1.0"
"purescript-prelude": "^4.0.1",
"purescript-matryoshka": "^0.4.0",
"purescript-pathy": "^6.0.0",
"purescript-profunctor-lenses": "^4.0.0",
"purescript-ejson": "^11.0.0"
},
"devDependencies": {
"purescript-argonaut": "^3.0.0",
"purescript-debug": "^3.0.0",
"purescript-quickcheck": "^4.4.0",
"purescript-search": "^3.0.0",
"purescript-test-unit": "^11.0.0"
"purescript-quickcheck": "^5.0.0",
"purescript-test-unit": "^14.0.0",
"purescript-argonaut": "^4.0.1"
}
}
6 changes: 3 additions & 3 deletions package.json
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@
"test": "pulp test"
},
"dependencies": {
"pulp": "^11.0.0",
"purescript": "^0.11.4",
"purescript-psa": "^0.5.1"
"pulp": "^12.2.0",
"purescript": "^0.12.0",
"purescript-psa": "^0.6.0"
}
}
34 changes: 4 additions & 30 deletions src/SqlSquared.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,12 +5,6 @@ module SqlSquared
, print
, printQuery
, printModule
, encodeJson
, encodeJsonQuery
, encodeJsonModule
, decodeJson
, decodeJsonQuery
, decodeJsonModule
, genSql
, genSqlQuery
, genSqlModule
Expand All @@ -24,16 +18,14 @@ import Prelude

import Control.Monad.Gen as Gen
import Control.Monad.Rec.Class (class MonadRec)
import Data.Argonaut as J
import Data.Either (Either)
import Data.Functor.Mu (Mu)
import Data.Json.Extended as EJ
import Data.Traversable (traverse)
import Matryoshka (cata, anaM)
import SqlSquared.Constructors as Constructors
import SqlSquared.Lenses as Lenses
import SqlSquared.Parser as Parser
import SqlSquared.Signature as Sig
import SqlSquared.Constructors (array, as, binop, bool, buildSelect, groupBy, having, hugeNum, ident, int, invokeFunction, let_, map_, match, null, num, pars, projection, select, set, splice, string, switch, then_, unop, vari, when) as Constructors
import SqlSquared.Lenses (_ArrayLiteral, _Binop, _BoolLiteral, _Case, _DecimalLiteral, _ExprRelation, _GroupBy, _Ident, _IntLiteral, _InvokeFunction, _JoinRelation, _Let, _Literal, _MapLiteral, _Match, _NullLiteral, _OrderBy, _Parens, _Projection, _Select, _SetLiteral, _Splice, _StringLiteral, _Switch, _TableRelation, _Unop, _Vari, _VariRelation, _alias, _aliasName, _args, _bindTo, _cases, _clause, _cond, _else, _expr, _filter, _groupBy, _having, _ident, _in, _isDistinct, _joinType, _keys, _left, _lhs, _name, _op, _orderBy, _projections, _relations, _rhs, _right, _tablePath) as Lenses
import SqlSquared.Parser (Literal(..), PositionedToken, Token(..), TokenStream, parse, parseModule, parseQuery, prettyParse, printToken, tokenize) as Parser
import SqlSquared.Signature (type (×), BinaryOperator(..), BinopR, Case(..), ExprRelR, FunctionDeclR, GroupBy(..), InvokeFunctionR, JoinRelR, JoinType(..), LetR, MatchR, OrderBy(..), OrderType(..), Projection(..), Relation(..), SelectR, SqlDeclF(..), SqlF(..), SqlModuleF(..), SqlQueryF(..), SwitchR, TableRelR, UnaryOperator(..), UnopR, VariRelR, binopFromString, binopToString, genBinaryOperator, genCase, genGroupBy, genJoinType, genOrderBy, genOrderType, genProjection, genRelation, genSqlDeclF, genSqlF, genSqlModuleF, genSqlQueryF, genUnaryOperator, joinTypeFromString, orderTypeFromString, printBinaryOperator, printCase, printGroupBy, printIdent, printJoinType, printOrderBy, printOrderType, printProjection, printRelation, printSqlDeclF, printSqlF, printSqlModuleF, printSqlQueryF, printUnaryOperator, unopFromString, unopToString, (×), (∘), (⋙)) as Sig

type Sql = Mu (Sig.SqlF EJ.EJsonF)

Expand All @@ -50,24 +42,6 @@ printQuery = Sig.printSqlQueryF <<< map print
printModule ∷ SqlModule → String
printModule = Sig.printSqlModuleF <<< map print

encodeJson ∷ Sql → J.Json
encodeJson = cata $ Sig.encodeJsonSqlF EJ.encodeJsonEJsonF

encodeJsonQuery ∷ SqlQuery → J.Json
encodeJsonQuery = Sig.encodeJsonSqlQueryF <<< map encodeJson

encodeJsonModule ∷ SqlModule → J.Json
encodeJsonModule = Sig.encodeJsonSqlModuleF <<< map encodeJson

decodeJson ∷ J.Json → Either String Sql
decodeJson = anaM $ Sig.decodeJsonSqlF EJ.decodeJsonEJsonF

decodeJsonQuery ∷ J.Json → Either String SqlQuery
decodeJsonQuery = traverse decodeJson <=< Sig.decodeJsonSqlQueryF

decodeJsonModule ∷ J.Json → Either String SqlModule
decodeJsonModule = traverse decodeJson <=< Sig.decodeJsonSqlModuleF

genSql ∷ ∀ m. Gen.MonadGen m ⇒ MonadRec m ⇒ m Sql
genSql = Gen.sized $ anaM (Sig.genSqlF EJ.arbitraryEJsonF)

Expand Down
18 changes: 8 additions & 10 deletions src/SqlSquared/Parser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,26 +13,24 @@ import Control.Lazy (defer)
import Control.Monad.Error.Class (catchError)
import Control.Monad.State (get, put)
import Control.MonadZero (guard)

import Data.Array as A
import Data.Bifunctor (lmap)
import Data.Either as E
import Data.Foldable as F
import Data.Json.Extended as EJ
import Data.List ((:))
import Data.List as L
import Data.Maybe (Maybe(..), fromMaybe, isJust)
import Data.NonEmpty ((:|))
import Data.Json.Extended as EJ
import Data.Tuple (Tuple(..), uncurry)
import SqlSquared.Path as Pt
import Data.String as S

import Data.String.CodeUnits as SCU
import Data.Tuple (Tuple(..), uncurry)
import Matryoshka (class Corecursive, embed)
import SqlSquared.Constructors as C
import SqlSquared.Parser.Tokenizer (Token(..), TokenStream, PositionedToken, tokenize, Literal(..), printToken)
import SqlSquared.Path as Pt
import SqlSquared.Signature as Sig
import SqlSquared.Utils ((∘), type (×), (×))
import Matryoshka (class Corecursive, embed)

import Text.Parsing.Parser as P
import Text.Parsing.Parser.Combinators as PC
import Text.Parsing.Parser.Pos as PP
Expand Down Expand Up @@ -75,7 +73,7 @@ prettyParse parser input =
lmap printError (parser input)
where
padLeft n s =
S.fromCharArray (A.replicate (n - S.length s) ' ') <> s
SCU.fromCharArray (A.replicate (n - S.length s) ' ') <> s

printError parseError =
let
Expand All @@ -86,7 +84,7 @@ prettyParse parser input =
line = A.take 1 $ A.drop (pos.line - 1) lines
post = A.take 3 $ A.drop pos.line lines
nums = A.mapWithIndex (\n l → padLeft 4 (show (n + pos.line - (A.length pre))) <> " | " <> l) (pre <> line <> post)
pointer = pure $ S.fromCharArray (A.replicate (pos.column - 1 + 7) '-') <> "^ " <> message
pointer = pure $ SCU.fromCharArray (A.replicate (pos.column - 1 + 7) '-') <> "^ " <> message
in
S.joinWith "\n" $ A.take (A.length pre + 1) nums <> pointer <> A.drop 3 nums

Expand Down Expand Up @@ -471,7 +469,7 @@ negatableSuffix = do
n ← PC.optionMaybe $ keyword "not"
pure $ isJust n
suffix ← betweenSuffix <|> inSuffix <|> likeSuffix
pure \e → (if inv then _NOT else id) $ suffix e
pure \e → (if inv then _NOT else identity) $ suffix e

betweenSuffix ∷ ∀ m t. SqlParser m t (t → t)
betweenSuffix = do
Expand Down
7 changes: 4 additions & 3 deletions src/SqlSquared/Parser/Tokenizer.purs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,8 @@ import Data.Int as Int
import Data.Json.Extended.Signature.Parse as EJP
import Data.Maybe (Maybe(..))
import Data.Set as Set
import Data.String as S
import Data.String (length, toUpper, toLower) as S
import Data.String.CodeUnits (fromCharArray, drop, singleton) as S
import Data.Traversable (sequence)
import SqlSquared.Utils ((∘))
import Text.Parsing.Parser as P
Expand Down Expand Up @@ -259,9 +260,9 @@ charLit = PS.char '\'' *> charAtom <* PS.char '\''

hexEscape = do
hex ← S.fromCharArray <$> sequence (A.replicate 4 PT.hexDigit)
case Int.fromStringAs Int.hexadecimal hex of
case Int.fromStringAs Int.hexadecimal hex >>= Char.fromCharCode of
Nothing → P.fail "Expected character escape sequence"
Just i → pure $ Char.fromCharCode i
Just i → pure i

positioned ∷ ∀ m. Monad m ⇒ P.ParserT String m Token → P.ParserT String m PositionedToken
positioned m = do
Expand Down
Loading