Skip to content

Commit

Permalink
better row syntax tests to help vladimir debug
Browse files Browse the repository at this point in the history
  • Loading branch information
gnumonik committed May 25, 2024
1 parent ceb7ddb commit 7f10e5a
Show file tree
Hide file tree
Showing 8 changed files with 12 additions and 9 deletions.
2 changes: 1 addition & 1 deletion tests/TestPurus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,7 @@ shouldPass = map (prefix </>) paths
"ResolvableScopeConflict",
"ResolvableScopeConflict2",
"ResolvableScopeConflict3",
-- "RowSyntax",
"RowSyntax",
"ShadowedModuleName",
"TransitiveImport"
]
Expand Down
5 changes: 4 additions & 1 deletion tests/purus/passing/RowSyntax/RowSyntax.purs
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
module RowSyntax where

class IsARow (r :: Row Type)
instance IsARow (r :: Row Type)
instance IsARow [hello :: String]

class IsARow' (r :: Row Type)
instance IsARow' (r :: Row Type)

data RowProxy (r :: Row Type) = RowProxy

Expand Down
2 changes: 1 addition & 1 deletion tests/purus/passing/TransitiveImport/Test.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,5 +5,5 @@ data Unit = Unit
class TestCls (a :: Type) where
test :: a -> a

instance unitTestCls :: TestCls Unit where
instance TestCls Unit where
test _ = Unit
2 changes: 1 addition & 1 deletion tests/purus/passing/TransitiveImport/output/Main/index.cfn
Original file line number Diff line number Diff line change
@@ -1 +1 @@
{"builtWith":"0.0.1","comments":[],"dataTypes":{},"decls":[{"annotation":{"meta":null,"sourceSpan":{"end":[5,15],"start":[5,3]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":{"metaType":"IsForeign"},"sourceSpan":{"end":[6,18],"start":[6,12]}},"kind":"Var","type":{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,11]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":0,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Test"],"TestCls$Dict"],"tag":"TypeConstructor"},{"annotation":[{"end":[8,40],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,39]},[]],"contents":{"kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,44]},[]],"contents":[{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,44]},[]],"contents":[{"annotation":[{"end":[8,48],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,46]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[8,45],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,44]},[]],"contents":{"kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,49]},[]],"contents":{"kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"middle","moduleName":["Middle"]}},"annotation":{"meta":null,"sourceSpan":{"end":[6,23],"start":[6,12]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Test"],"TestCls$Dict"],"tag":"TypeConstructor"},{"annotation":[{"end":[8,37],"name":"tests/purus/passing/TransitiveImport/Test.purs","start":[8,33]},[]],"contents":[["Test"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"unitTestCls","moduleName":["Test"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[6,23],"start":[6,12]}},"argument":{"annotation":{"meta":{"metaType":"IsForeign"},"sourceSpan":{"end":[6,23],"start":[6,19]}},"kind":"Var","type":{"annotation":[{"end":[5,13],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[5,9]},[]],"contents":[["Test"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Middle"]}},"kind":"App"},"identifier":"main"}],"exports":["main"],"foreign":[],"imports":[{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Builtin"]},{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Middle"]},{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Prim"]},{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Test"]}],"moduleName":["Main"],"modulePath":"tests/purus/passing/TransitiveImport/TransitiveImport.purs","reExports":{},"sourceSpan":{"end":[6,24],"start":[1,1]}}
{"builtWith":"0.0.1","comments":[],"dataTypes":{},"decls":[{"annotation":{"meta":null,"sourceSpan":{"end":[5,15],"start":[5,3]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":{"metaType":"IsForeign"},"sourceSpan":{"end":[6,18],"start":[6,12]}},"kind":"Var","type":{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,11]},[]],"contents":{"identifier":"a","kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"skolem":0,"type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Test"],"TestCls$Dict"],"tag":"TypeConstructor"},{"annotation":[{"end":[8,40],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,39]},[]],"contents":{"kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,44]},[]],"contents":[{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,44]},[]],"contents":[{"annotation":[{"end":[8,48],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,46]},[]],"contents":[["Prim"],"Function"],"tag":"TypeConstructor"},{"annotation":[{"end":[8,45],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,44]},[]],"contents":{"kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"},{"annotation":[{"end":[8,50],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,49]},[]],"contents":{"kind":{"annotation":[{"end":[8,28],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[8,24]},[]],"contents":[["Prim"],"Type"],"tag":"TypeConstructor"},"var":"a"},"tag":"TypeVar"}],"tag":"TypeApp"}],"tag":"TypeApp"},"visibility":"TypeVarInvisible"},"tag":"ForAll"},"value":{"identifier":"middle","moduleName":["Middle"]}},"annotation":{"meta":null,"sourceSpan":{"end":[6,23],"start":[6,12]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"kind":"Var","type":{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[{"annotation":[{"end":[0,0],"name":"","start":[0,0]},[]],"contents":[["Test"],"TestCls$Dict"],"tag":"TypeConstructor"},{"annotation":[{"end":[8,22],"name":"tests/purus/passing/TransitiveImport/Test.purs","start":[8,18]},[]],"contents":[["Test"],"Unit"],"tag":"TypeConstructor"}],"tag":"TypeApp"},"value":{"identifier":"testClsUnit","moduleName":["Test"]}},"kind":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[6,23],"start":[6,12]}},"argument":{"annotation":{"meta":{"metaType":"IsForeign"},"sourceSpan":{"end":[6,23],"start":[6,19]}},"kind":"Var","type":{"annotation":[{"end":[5,13],"name":"tests/purus/passing/TransitiveImport/Middle.purs","start":[5,9]},[]],"contents":[["Test"],"Unit"],"tag":"TypeConstructor"},"value":{"identifier":"unit","moduleName":["Middle"]}},"kind":"App"},"identifier":"main"}],"exports":["main"],"foreign":[],"imports":[{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Builtin"]},{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Middle"]},{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Prim"]},{"annotation":{"meta":null,"sourceSpan":{"end":[6,24],"start":[1,1]}},"moduleName":["Test"]}],"moduleName":["Main"],"modulePath":"tests/purus/passing/TransitiveImport/TransitiveImport.purs","reExports":{},"sourceSpan":{"end":[6,24],"start":[1,1]}}
Original file line number Diff line number Diff line change
Expand Up @@ -15,5 +15,5 @@ main :: Test.Unit
main =
(middle: forall (a :: Prim.Type). Test.TestCls$Dict (a :: Prim.Type) ->
(a :: Prim.Type) -> (a :: Prim.Type))
(unitTestCls: Test.TestCls$Dict Test.Unit)
(testClsUnit: Test.TestCls$Dict Test.Unit)
(unit: Test.Unit)
Binary file modified tests/purus/passing/TransitiveImport/output/Test/externs.cbor
Binary file not shown.
2 changes: 1 addition & 1 deletion tests/purus/passing/TransitiveImport/output/Test/index.cfn

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ Imported Modules:
Exports:
test,
Unit,
unitTestCls
testClsUnit
Re-Exports:

Foreign:
Expand All @@ -20,8 +20,8 @@ TestCls$Dict =
\(x: { test :: (a :: Prim.Type) -> (a :: Prim.Type) }) ->
(x: { test :: (a :: Prim.Type) -> (a :: Prim.Type) })

unitTestCls :: Test.TestCls$Dict Test.Unit
unitTestCls =
testClsUnit :: Test.TestCls$Dict Test.Unit
testClsUnit =
(TestCls$Dict: { test :: Test.Unit -> Test.Unit } ->
Test.TestCls$Dict Test.Unit)
({ test: \(v: Test.Unit) -> (Unit: Test.Unit) }: {
Expand Down

0 comments on commit 7f10e5a

Please sign in to comment.