Skip to content

Commit f49d0fe

Browse files
authored
Allow multiple annotation/extension fields (#8)
* Allow multiple annotation/extension fields * Move lambda abstraction for type params * Remove ConAnn and use Maybe instead * Add multi-field example * Replace example in docs with λ-calculus AST with records
1 parent b438b73 commit f49d0fe

File tree

14 files changed

+370
-247
lines changed

14 files changed

+370
-247
lines changed

examples/basic/Basic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ import BasicBase
33

44
data NoExt
55

6-
extendA "A" [] [t|NoExt|] defaultExtA
6+
extendA "A" [] [t|NoExt|] $ \_ -> defaultExtA
77

88
deriving instance Show a => Show (A a)
99

examples/deriv/Deriv.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,12 @@ import DerivBase
33

44
data T
55

6-
extendA "A" [] [t|T|] $ defaultExtA {
7-
typeA = Ann $ \a -> [t| [$a] |]
6+
extendA "A" [] [t|T|] $
7+
\a -> defaultExtA {
8+
typeA = Just [[t| [$a] |]]
89
}
910

10-
extendB "B" [] [t|T|] $ defaultExtB
11+
extendB "B" [] [t|T|] $ \_ -> defaultExtB
1112

1213
main :: IO ()
1314
main = print $

examples/lam/DeBruijn.hs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
module DeBruijn where
2+
import LamBase
3+
4+
data DeBruijn
5+
6+
extendLam "DBTerm" [] [t|DeBruijn|] $
7+
\a p -> defaultExtLam {
8+
typeVar = Nothing, -- replaced with Free and Bound
9+
typeAbs = Nothing, -- replaced with a version without absVar
10+
typeLamX =
11+
[("Free", [("freeVar", a)]),
12+
("Bound", [("boundVar", [t|Int|])]),
13+
("Abs", [("absBody", [t|Lam' DeBruijn $a $p|])])]
14+
}

examples/lam/Lam.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
import LamBase ()
2+
import Typed ()
3+
import DeBruijn ()
4+
5+
main :: IO ()
6+
main = pure ()

examples/lam/LamBase.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
module LamBase where
2+
import Extensible
3+
4+
extensible [d|
5+
data Lam a p =
6+
Var {varVar :: a}
7+
| Prim {primVal :: p}
8+
| App {appFun, appArg :: Lam a p}
9+
| Abs {absVar :: a, absBody :: Lam a p}
10+
deriving (Eq, Show)
11+
|]

examples/lam/Typed.hs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
module Typed where
2+
import LamBase
3+
import Extensible
4+
5+
data NoExt
6+
7+
data Type t =
8+
Base t
9+
| Arr (Type t) (Type t)
10+
11+
data Typed t
12+
13+
do t' <- newName "t"; let t = varT t'
14+
extendLam "TypedLam" [t'] [t|Typed $t|] $
15+
\a p -> defaultExtLam {
16+
typeVar = Just [("varType", [t|Type $t|])],
17+
typeAbs = Just [("absArg", [t|Type $t|])],
18+
typeLamX = [("TypeAnn",
19+
[("annTerm", [t|Lam' (Typed $t) $a $p|]),
20+
("annType", [t|Type $t|])])]
21+
}
22+
23+
main :: IO ()
24+
main = pure ()

examples/multifield/MultiField.hs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
{-# OPTIONS_GHC -Werror=incomplete-patterns #-}
2+
import MultiFieldBase
3+
4+
extendA "A" [] [t|Int|] $
5+
\a -> defaultExtA {
6+
typeA = Just [[t|Int|], [t|$a|]],
7+
typeB = Nothing,
8+
typeAX = [("C", [[t|Bool|], [t|Char|]])]
9+
}
10+
11+
foo :: A () -> ()
12+
foo (A u₁ i u₂) = () where _ = (u₁ :: (), i :: Int, u:: ())
13+
foo (C b c) = () where _ = (b :: Bool, c :: Char)
14+
15+
main :: IO ()
16+
main = pure ()
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module MultiFieldBase where
2+
import Extensible
3+
4+
extensible [d| data A a = A a | B (A a) (A Int) |]

examples/mutual/Mutual.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,11 @@ import MutualBase
44
data Ext
55

66
extendA "A" [] [t|Ext|] defaultExtA {
7-
typeAX = [("AI", [t|Int|])]
7+
typeAX = [("AI", [[t|Int|]])]
88
}
99

1010
extendB "B" [] [t|Ext|] defaultExtB {
11-
typeBA = Ann [t|String|]
11+
typeBA = Just [[t|String|]]
1212
}
1313

1414
main :: IO ()

examples/param/Param.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ data With a
66
do an <- newName "a"
77
let a = varT an
88
extendT "T" [an] [t|With $a|] $ defaultExtT {
9-
typeTX = [("Extra", a)]
9+
typeTX = [("Extra", [a])]
1010
}
1111

1212
main :: IO ()

0 commit comments

Comments
 (0)