2017-04-21 23:12:56 +03:00
{- # LANGUAGE DataKinds # -}
2017-04-07 19:21:45 +03:00
module Data.Syntax.Assignment.Spec where
2017-04-06 17:09:12 +03:00
2017-04-21 23:12:56 +03:00
import Data.ByteString.Char8 as B ( words , length )
2017-06-25 00:30:57 +03:00
import Data.Source
2017-04-07 19:21:45 +03:00
import Data.Syntax.Assignment
2017-04-21 23:12:56 +03:00
import Info
2017-07-22 23:13:42 +03:00
import Prologue hiding ( State )
2017-04-06 17:09:12 +03:00
import Test.Hspec
2017-04-18 18:06:24 +03:00
import Text.Parser.TreeSitter.Language ( Symbol ( .. ) , SymbolType ( .. ) )
2017-04-06 17:09:12 +03:00
spec :: Spec
2017-04-06 20:36:54 +03:00
spec = do
2017-05-12 19:45:07 +03:00
describe " Applicative " $
2017-04-07 16:45:23 +03:00
it " matches in sequence " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " helloworld " ( ( , ) <$> red <*> red ) ( makeState [ node Red 0 5 [] , node Red 5 10 [] ] )
2017-07-18 00:34:28 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right ( Out " hello " , Out " world " )
2017-04-07 16:14:03 +03:00
2017-04-07 21:47:23 +03:00
describe " Alternative " $ do
it " attempts multiple alternatives " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " hello " ( green <|> red ) ( makeState [ node Red 0 5 [] ] )
2017-07-18 00:34:28 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right ( Out " hello " )
2017-04-07 21:47:23 +03:00
2017-04-07 16:45:23 +03:00
it " matches repetitions " $
2017-04-21 23:12:56 +03:00
let s = " colourless green ideas sleep furiously "
w = words s
2017-06-07 21:26:21 +03:00
( _ , nodes ) = foldl ( \ ( i , prev ) word -> ( i + B . length word + 1 , prev <> [ node Red i ( i + B . length word ) [] ] ) ) ( 0 , [] ) w in
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF ( fromBytes s ) ( many red ) ( makeState nodes )
2017-07-18 00:34:28 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right ( Out <$> w )
2017-04-07 16:44:13 +03:00
2017-04-07 16:48:21 +03:00
it " matches one-or-more repetitions against one or more input nodes " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " hello " ( some red ) ( makeState [ node Red 0 5 [] ] )
2017-07-18 00:34:28 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right [ Out " hello " ]
2017-04-07 16:48:21 +03:00
2017-07-26 18:09:52 +03:00
it " distributes through overlapping committed choices, matching the left alternative " $
fst <$> runAssignment headF " (red (green)) " ( symbol Red *> children green <|> symbol Red *> children blue ) ( makeState [ node Red 0 13 [ node Green 5 12 [] ] ] )
` shouldBe `
Right ( Out " (green) " )
2017-07-26 18:11:15 +03:00
it " distributes through overlapping committed choices, matching the right alternative " $
fst <$> runAssignment headF " (red (blue)) " ( symbol Red *> children green <|> symbol Red *> children blue ) ( makeState [ node Red 0 12 [ node Blue 5 11 [] ] ] )
` shouldBe `
Right ( Out " (blue) " )
2017-07-27 01:41:24 +03:00
it " distributes through overlapping committed choices, matching the left alternatives " $
fst <$> runAssignment headF " magenta green green " ( symbol Magenta *> many green <|> symbol Magenta *> many blue ) ( makeState [ node Magenta 0 7 [] , node Green 8 13 [] , node Green 14 19 [] ] )
` shouldBe `
Right [ Out " green " , Out " green " ]
it " distributes through overlapping committed choices, matching the right alternatives " $
fst <$> runAssignment headF " magenta blue blue " ( symbol Magenta *> many green <|> symbol Magenta *> many blue ) ( makeState [ node Magenta 0 7 [] , node Blue 8 12 [] , node Blue 13 17 [] ] )
` shouldBe `
Right [ Out " blue " , Out " blue " ]
2017-07-27 01:42:18 +03:00
it " distributes through overlapping committed choices, dropping anonymous nodes & matching the left alternative " $
fst <$> runAssignment headF " magenta green " ( symbol Magenta *> green <|> symbol Magenta *> blue ) ( makeState [ node Magenta 0 7 [] , node Green 8 13 [] ] )
` shouldBe `
Right ( Out " green " )
it " distributes through overlapping committed choices, dropping anonymous nodes & matching the right alternative " $
fst <$> runAssignment headF " magenta blue " ( symbol Magenta *> green <|> symbol Magenta *> blue ) ( makeState [ node Magenta 0 7 [] , node Blue 8 12 [] ] )
` shouldBe `
Right ( Out " blue " )
2017-07-27 00:43:39 +03:00
it " alternates repetitions, matching the left alternative " $
fst <$> runAssignment headF " green green " ( many green <|> many blue ) ( makeState [ node Green 0 5 [] , node Green 6 11 [] ] )
` shouldBe `
Right [ Out " green " , Out " green " ]
it " alternates repetitions, matching the right alternative " $
2017-07-26 19:02:18 +03:00
fst <$> runAssignment headF " blue blue " ( many green <|> many blue ) ( makeState [ node Blue 0 4 [] , node Blue 5 9 [] ] )
` shouldBe `
Right [ Out " blue " , Out " blue " ]
2017-07-27 01:40:19 +03:00
it " alternates repetitions, matching at the end of input " $
fst <$> runAssignment headF " " ( many green <|> many blue ) ( makeState [] )
` shouldBe `
Right []
2017-07-26 19:14:12 +03:00
it " distributes through children rules " $
fst <$> runAssignment headF " (red (blue)) " ( children ( many green ) <|> children ( many blue ) ) ( makeState [ node Red 0 12 [ node Blue 5 11 [] ] ] )
` shouldBe `
Right [ Out " (blue) " ]
2017-04-19 20:11:09 +03:00
describe " symbol " $ do
2017-04-07 21:50:57 +03:00
it " matches nodes with the same symbol " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " hello " red ( makeState [ node Red 0 5 [] ] ) ` shouldBe ` Right ( Out " hello " )
2017-04-07 21:50:57 +03:00
2017-04-07 21:59:13 +03:00
it " does not advance past the current node " $
2017-07-22 22:43:48 +03:00
runAssignment headF " hi " ( symbol Red ) ( makeState [ node Red 0 2 [] ] ) ` shouldBe ` Left ( Error ( Info . Pos 1 1 ) [] ( Just Red ) )
2017-04-07 21:59:13 +03:00
2017-07-20 00:02:07 +03:00
describe " without catchError " $ do
2017-07-22 22:43:48 +03:00
it " assignment returns unexpected symbol error " $
2017-07-22 21:04:52 +03:00
runAssignment headF " A "
2017-07-20 00:02:07 +03:00
red
2017-07-20 20:23:21 +03:00
( makeState [ node Green 0 1 [] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-22 22:43:48 +03:00
Left ( Error ( Info . Pos 1 1 ) [ Red ] ( Just Green ) )
2017-07-20 00:02:07 +03:00
2017-07-22 22:43:48 +03:00
it " assignment returns unexpected end of input " $
2017-07-22 21:04:52 +03:00
runAssignment headF " A "
2017-07-20 00:02:07 +03:00
( symbol Green *> children ( some red ) )
2017-07-20 20:23:21 +03:00
( makeState [ node Green 0 1 [] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-22 22:43:48 +03:00
Left ( Error ( Info . Pos 1 1 ) [ Red ] Nothing )
2017-07-20 00:02:07 +03:00
describe " catchError " $ do
it " handler that always matches " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " A "
2017-07-20 00:02:07 +03:00
( red ` catchError ` ( \ _ -> OutError <$ location <*> source ) )
2017-07-20 20:23:21 +03:00
( makeState [ node Green 0 1 [] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right ( OutError " A " )
2017-07-20 00:02:07 +03:00
it " handler that matches " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " A "
2017-07-20 00:02:07 +03:00
( red ` catchError ` const green )
2017-07-20 20:23:21 +03:00
( makeState [ node Green 0 1 [] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right ( Out " A " )
2017-07-20 00:02:07 +03:00
it " handler that doesn't match produces error " $
2017-07-22 21:04:52 +03:00
runAssignment headF " A "
2017-07-20 00:02:07 +03:00
( red ` catchError ` const blue )
2017-07-20 20:23:21 +03:00
( makeState [ node Green 0 1 [] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-22 22:43:48 +03:00
Left ( Error ( Info . Pos 1 1 ) [ Blue ] ( Just Green ) )
2017-07-20 00:02:07 +03:00
describe " in many " $ do
it " handler that always matches " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " PG "
2017-07-21 19:00:30 +03:00
( symbol Palette *> children (
2017-07-20 00:02:07 +03:00
many ( red ` catchError ` ( \ _ -> OutError <$ location <*> source ) )
) )
2017-07-21 19:07:33 +03:00
( makeState [ node Palette 0 1 [ node Green 1 2 [] ] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right [ OutError " G " ]
2017-07-20 00:02:07 +03:00
it " handler that matches " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " PG "
2017-07-21 19:00:30 +03:00
( symbol Palette *> children ( many ( red ` catchError ` const green ) ) )
2017-07-21 19:07:33 +03:00
( makeState [ node Palette 0 1 [ node Green 1 2 [] ] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right [ Out " G " ]
2017-07-20 00:02:07 +03:00
it " handler that doesn't match produces error " $
2017-07-22 21:04:52 +03:00
runAssignment headF " PG "
2017-07-21 19:00:30 +03:00
( symbol Palette *> children ( many ( red ` catchError ` const blue ) ) )
2017-07-21 19:07:33 +03:00
( makeState [ node Palette 0 1 [ node Green 1 2 [] ] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-22 22:43:48 +03:00
Left ( Error ( Info . Pos 1 2 ) [ Blue ] ( Just Green ) )
2017-07-20 00:02:07 +03:00
it " handler that always matches with apply consumes and then errors " $
2017-07-22 21:04:52 +03:00
runAssignment headF " PG "
2017-07-21 19:00:30 +03:00
( symbol Palette *> children (
2017-07-20 00:02:07 +03:00
( , ) <$> many ( red ` catchError ` ( \ _ -> OutError <$ location <*> source ) ) <*> green
) )
2017-07-21 19:07:33 +03:00
( makeState [ node Palette 0 1 [ node Green 1 2 [] ] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-22 22:43:48 +03:00
Left ( Error ( Info . Pos 1 3 ) [ Green ] Nothing )
2017-07-20 00:02:07 +03:00
it " handler that doesn't match with apply " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " PG "
2017-07-21 19:00:30 +03:00
( symbol Palette *> children (
2017-07-20 00:20:03 +03:00
( , ) <$> many ( red ` catchError ` const blue ) <*> green
2017-07-20 00:02:07 +03:00
) )
2017-07-21 19:07:33 +03:00
( makeState [ node Palette 0 1 [ node Green 1 2 [] ] ] )
2017-07-20 00:02:07 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right ( [] , Out " G " )
2017-07-20 00:02:07 +03:00
2017-07-20 00:20:17 +03:00
describe " many " $ do
2017-07-20 19:32:09 +03:00
it " takes ones and only one zero width repetition " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " PGG "
2017-07-21 19:00:30 +03:00
( symbol Palette *> children ( many ( green <|> pure ( Out " always " ) ) ) )
2017-07-21 19:07:33 +03:00
( makeState [ node Palette 0 1 [ node Green 1 2 [] , node Green 2 3 [] ] ] )
2017-07-20 00:20:17 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right [ Out " G " , Out " G " , Out " always " ]
2017-07-20 00:20:17 +03:00
2017-04-19 23:00:44 +03:00
describe " source " $ do
it " produces the node’ s source " $
2017-07-22 21:06:07 +03:00
assignBy headF " hi " source ( node Red 0 2 [] ) ` shouldBe ` Right " hi "
2017-04-07 21:57:00 +03:00
2017-04-07 21:57:44 +03:00
it " advances past the current node " $
2017-07-22 21:04:52 +03:00
snd <$> runAssignment headF " hi " source ( makeState [ node Red 0 2 [] ] )
2017-07-20 20:23:21 +03:00
` shouldBe `
2017-07-22 23:13:42 +03:00
Right ( State 2 ( Info . Pos 1 3 ) Nothing 1 [] )
2017-04-07 21:57:44 +03:00
2017-04-07 21:39:13 +03:00
describe " children " $ do
it " advances past the current node " $
2017-07-22 21:04:52 +03:00
snd <$> runAssignment headF " a " ( children ( pure ( Out " " ) ) ) ( makeState [ node Red 0 1 [] ] )
2017-07-20 20:23:21 +03:00
` shouldBe `
2017-07-22 23:13:42 +03:00
Right ( State 1 ( Info . Pos 1 2 ) Nothing 1 [] )
2017-04-07 21:39:13 +03:00
2017-04-07 21:42:25 +03:00
it " matches if its subrule matches " $
2017-07-22 21:04:52 +03:00
() <$ runAssignment headF " a " ( children red ) ( makeState [ node Blue 0 1 [ node Red 0 1 [] ] ] )
2017-07-20 20:23:21 +03:00
` shouldBe `
Right ()
2017-04-07 21:42:25 +03:00
2017-04-07 21:43:53 +03:00
it " does not match if its subrule does not match " $
2017-07-22 21:04:52 +03:00
runAssignment headF " a " ( children red ) ( makeState [ node Blue 0 1 [ node Green 0 1 [] ] ] )
2017-07-20 20:23:21 +03:00
` shouldBe `
2017-07-22 22:43:48 +03:00
Left ( Error ( Info . Pos 1 1 ) [ Red ] ( Just Green ) )
2017-04-07 21:43:53 +03:00
2017-05-12 19:45:07 +03:00
it " matches nested children " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " 1 "
2017-04-19 23:00:44 +03:00
( symbol Red *> children ( symbol Green *> children ( symbol Blue *> source ) ) )
2017-07-20 20:23:21 +03:00
( makeState [ node Red 0 1 [ node Green 0 1 [ node Blue 0 1 [] ] ] ] )
2017-04-10 17:35:39 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right " 1 "
2017-04-10 17:35:39 +03:00
2017-05-12 19:45:07 +03:00
it " continues after children " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " BC "
2017-04-19 23:00:44 +03:00
( many ( symbol Red *> children ( symbol Green *> source )
<|> symbol Blue *> source ) )
2017-07-20 20:23:21 +03:00
( makeState [ node Red 0 1 [ node Green 0 1 [] ]
, node Blue 1 2 [] ] )
2017-04-10 17:52:12 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right [ " B " , " C " ]
2017-04-10 17:52:12 +03:00
2017-05-12 19:45:07 +03:00
it " matches multiple nested children " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " 12 "
2017-04-19 23:00:44 +03:00
( symbol Red *> children ( many ( symbol Green *> children ( symbol Blue *> source ) ) ) )
2017-07-20 20:23:21 +03:00
( makeState [ node Red 0 2 [ node Green 0 1 [ node Blue 0 1 [] ]
2017-07-21 19:08:57 +03:00
, node Green 1 2 [ node Blue 1 2 [] ] ] ] )
2017-04-10 18:24:30 +03:00
` shouldBe `
2017-07-20 19:32:09 +03:00
Right [ " 1 " , " 2 " ]
2017-04-10 18:24:30 +03:00
2017-05-03 17:07:53 +03:00
describe " runAssignment " $ do
2017-05-03 18:23:31 +03:00
it " drops anonymous nodes before matching symbols " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " magenta red " red ( makeState [ node Magenta 0 7 [] , node Red 8 11 [] ] )
2017-07-20 19:32:09 +03:00
` shouldBe `
Right ( Out " red " )
2017-05-03 17:07:53 +03:00
2017-05-03 17:09:31 +03:00
it " does not drop anonymous nodes after matching " $
2017-07-22 21:04:52 +03:00
stateNodes . snd <$> runAssignment headF " red magenta " red ( makeState [ node Red 0 3 [] , node Magenta 4 11 [] ] )
2017-07-20 19:32:09 +03:00
` shouldBe `
Right [ node Magenta 4 11 [] ]
2017-05-03 17:09:31 +03:00
2017-05-03 17:56:01 +03:00
it " does not drop anonymous nodes when requested " $
2017-07-22 21:04:52 +03:00
fst <$> runAssignment headF " magenta red " ( ( , ) <$> magenta <*> red ) ( makeState [ node Magenta 0 7 [] , node Red 8 11 [] ] )
2017-07-20 19:32:09 +03:00
` shouldBe `
Right ( Out " magenta " , Out " red " )
2017-05-03 17:13:40 +03:00
2017-06-07 21:26:21 +03:00
node :: symbol -> Int -> Int -> [ AST symbol ] -> AST symbol
2017-07-18 00:34:28 +03:00
node symbol start end children = cofree $ Node symbol ( Range start end ) ( Info . Span ( Info . Pos 1 ( succ start ) ) ( Info . Pos 1 ( succ end ) ) ) :< children
2017-04-24 17:27:45 +03:00
2017-07-21 19:00:30 +03:00
data Grammar = Palette | Red | Green | Blue | Magenta
2017-04-26 18:29:13 +03:00
deriving ( Enum , Eq , Show )
2017-04-07 19:36:14 +03:00
2017-04-18 18:06:24 +03:00
instance Symbol Grammar where
2017-05-03 17:07:53 +03:00
symbolType Magenta = Anonymous
2017-04-18 18:06:24 +03:00
symbolType _ = Regular
2017-07-20 00:02:07 +03:00
data Out = Out ByteString | OutError ByteString
2017-04-07 19:36:14 +03:00
deriving ( Eq , Show )
2017-06-08 03:17:14 +03:00
red :: Assignment ( AST Grammar ) Grammar Out
2017-04-19 23:00:44 +03:00
red = Out <$ symbol Red <*> source
2017-04-07 19:36:14 +03:00
2017-06-08 03:17:14 +03:00
green :: Assignment ( AST Grammar ) Grammar Out
2017-04-19 23:00:44 +03:00
green = Out <$ symbol Green <*> source
2017-04-07 19:36:14 +03:00
2017-06-08 03:17:14 +03:00
blue :: Assignment ( AST Grammar ) Grammar Out
2017-04-19 23:00:44 +03:00
blue = Out <$ symbol Blue <*> source
2017-05-03 17:13:40 +03:00
2017-06-08 03:17:14 +03:00
magenta :: Assignment ( AST Grammar ) Grammar Out
2017-05-03 17:13:40 +03:00
magenta = Out <$ symbol Magenta <*> source