aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/lang
diff options
context:
space:
mode:
authorEduardo Julian2018-05-05 20:42:41 -0400
committerEduardo Julian2018-05-05 20:42:41 -0400
commit3c93d7a3aabaa49c67f9a498bc0d70f0af7f09d0 (patch)
tree33aea74291323d5084ff70797337150b947962a8 /stdlib/source/lux/lang
parent88e2aee41d91deed941acc1ef650ccd3dd0334a2 (diff)
- Removed Void and Unit as kinds of types.
- Changed the value of "unit" in the old LuxC to match the one in new-luxc.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/lang/syntax.lux2
-rw-r--r--stdlib/source/lux/lang/type.lux20
-rw-r--r--stdlib/source/lux/lang/type/check.lux27
3 files changed, 15 insertions, 34 deletions
diff --git a/stdlib/source/lux/lang/syntax.lux b/stdlib/source/lux/lang/syntax.lux
index 0fefc1929..d30436533 100644
--- a/stdlib/source/lux/lang/syntax.lux
+++ b/stdlib/source/lux/lang/syntax.lux
@@ -82,7 +82,7 @@
## This is just a helper parser to find text which doesn't run into
## any special character sequences for multi-line comments.
(def: comment-bound^
- (l.Lexer Unit)
+ (l.Lexer Top)
($_ p.either
(l.this new-line)
(l.this ")#")
diff --git a/stdlib/source/lux/lang/type.lux b/stdlib/source/lux/lang/type.lux
index 35c2cd29c..48db0b928 100644
--- a/stdlib/source/lux/lang/type.lux
+++ b/stdlib/source/lux/lang/type.lux
@@ -54,11 +54,6 @@
(list.zip2 xparams yparams)))
(^template [<tag>]
- [<tag> <tag>]
- true)
- ([#.Void] [#.Unit])
-
- (^template [<tag>]
[(<tag> xid) (<tag> yid)]
(n/= yid xid))
([#.Var] [#.Ex] [#.Bound])
@@ -172,11 +167,6 @@
(.list (~+ (list/map to-code params)))))
(^template [<tag>]
- <tag>
- (` <tag>))
- ([#.Void] [#.Unit])
-
- (^template [<tag>]
(<tag> idx)
(` (<tag> (~ (code.nat idx)))))
([#.Var] [#.Ex] [#.Bound])
@@ -208,12 +198,6 @@
_
($_ text/compose "(primitive " name " " (|> params (list/map to-text) list.reverse (list.interpose " ") (list/fold text/compose "")) ")"))
- #.Void
- "Void"
-
- #.Unit
- "Unit"
-
(^template [<tag> <open> <close> <flatten>]
(<tag> _)
($_ text/compose <open>
@@ -290,8 +274,8 @@
(#.Cons type types')
(<ctor> type (<name> types'))))]
- [variant Void #.Sum]
- [tuple Unit #.Product]
+ [variant Bottom #.Sum]
+ [tuple Top #.Product]
)
(def: #export (function inputs output)
diff --git a/stdlib/source/lux/lang/type/check.lux b/stdlib/source/lux/lang/type/check.lux
index f71ac4150..1853f0931 100644
--- a/stdlib/source/lux/lang/type/check.lux
+++ b/stdlib/source/lux/lang/type/check.lux
@@ -199,7 +199,7 @@
(ex.throw unknown-type-var id))))
(def: #export (write type id)
- (-> Type Var (Check Unit))
+ (-> Type Var (Check Top))
(function (_ context)
(case (|> context (get@ #.var-bindings) (var::get id))
(#.Some (#.Some bound))
@@ -213,7 +213,7 @@
(ex.throw unknown-type-var id))))
(def: (update type id)
- (-> Type Var (Check Unit))
+ (-> Type Var (Check Top))
(function (_ context)
(case (|> context (get@ #.var-bindings) (var::get id))
(#.Some _)
@@ -239,7 +239,7 @@
(get@ #.var-bindings context)])))
(def: (set-bindings value)
- (-> (List [Var (Maybe Type)]) (Check Unit))
+ (-> (List [Var (Maybe Type)]) (Check Top))
(function (_ context)
(#e.Success [(set@ #.var-bindings value context)
[]])))
@@ -315,7 +315,7 @@
(#e.Error message)))
(def: #export (assert message test)
- (-> Text Bool (Check Unit))
+ (-> Text Bool (Check Top))
(function (_ context)
(if test
(#e.Success [context []])
@@ -361,13 +361,13 @@
(else (maybe.default (#.Var id) ?bound)))))
(def: (link-2 left right)
- (-> Var Var (Check Unit))
+ (-> Var Var (Check Top))
(do Monad<Check>
[_ (write (#.Var right) left)]
(write (#.Var left) right)))
(def: (link-3 interpose to from)
- (-> Var Var Var (Check Unit))
+ (-> Var Var Var (Check Top))
(do Monad<Check>
[_ (update (#.Var interpose) from)]
(update (#.Var to) interpose)))
@@ -445,7 +445,7 @@
(check' etype atype assumptions))))))
(def: (with-error-stack on-error check)
- (All [a] (-> (-> Unit Text) (Check a) (Check a)))
+ (All [a] (-> (-> Top Text) (Check a) (Check a)))
(function (_ context)
(case (check context)
(#e.Error error)
@@ -592,16 +592,13 @@
(check/wrap assumptions))
(fail ""))
- (^template [<identity> <compose>]
- [<identity> <identity>]
- (check/wrap assumptions)
-
+ (^template [<compose>]
[(<compose> eL eR) (<compose> aL aR)]
(do Monad<Check>
[assumptions (check' eL aL assumptions)]
(check' eR aR assumptions)))
- ([#.Void #.Sum]
- [#.Unit #.Product])
+ ([#.Sum]
+ [#.Product])
[(#.Function eI eO) (#.Function aI aO)]
(do Monad<Check>
@@ -624,7 +621,7 @@
(def: #export (check expected actual)
{#.doc "Type-check to ensure that the 'expected' type subsumes the 'actual' type."}
- (-> Type Type (Check Unit))
+ (-> Type Type (Check Top))
(do Monad<Check>
[assumptions (check' expected actual (list))]
(wrap [])))
@@ -652,7 +649,7 @@
[paramsT+' (monad.map @ clean paramsT+)]
(wrap (#.Primitive name paramsT+')))
- (^or #.Void #.Unit (#.Bound _) (#.Ex _) (#.Named _))
+ (^or (#.Bound _) (#.Ex _) (#.Named _))
(:: Monad<Check> wrap inputT)
(^template [<tag>]