diff options
| author | Eduardo Julian | 2018-05-20 21:04:03 -0400 | 
|---|---|---|
| committer | Eduardo Julian | 2018-05-20 21:04:03 -0400 | 
| commit | 14e96f5e5dad439383d63e60a52169cc2e7aaa5c (patch) | |
| tree | 606398bbf6742a476a2599d9b25c184c71eae5c7 /stdlib/source/lux/lang | |
| parent | 19d38211c33faf6d5fe01665982d696643f60051 (diff) | |
- Re-named "Top" to "Any", and "Bottom" to "Nothing".
- Removed some modules that should have been deleted before.
Diffstat (limited to '')
| -rw-r--r-- | stdlib/source/lux/lang.lux | 2 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/analysis/case.lux | 2 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/analysis/primitive.lux | 2 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/analysis/structure.lux | 2 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/analysis/type.lux | 2 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/init.lux | 6 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/module.lux | 12 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/syntax.lux | 2 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/type.lux | 4 | ||||
| -rw-r--r-- | stdlib/source/lux/lang/type/check.lux | 16 | 
10 files changed, 25 insertions, 25 deletions
| diff --git a/stdlib/source/lux/lang.lux b/stdlib/source/lux/lang.lux index 9f164b719..4c467c7fb 100644 --- a/stdlib/source/lux/lang.lux +++ b/stdlib/source/lux/lang.lux @@ -10,7 +10,7 @@         (macro ["s" syntax #+ syntax:])))  (type: #export Eval -  (-> Type Code (Meta Top))) +  (-> Type Code (Meta Any)))  (def: #export (fail message)    (All [a] (-> Text (Meta a))) diff --git a/stdlib/source/lux/lang/analysis/case.lux b/stdlib/source/lux/lang/analysis/case.lux index 3140a9d7e..744d3cf24 100644 --- a/stdlib/source/lux/lang/analysis/case.lux +++ b/stdlib/source/lux/lang/analysis/case.lux @@ -168,7 +168,7 @@       [Deg  (#.Deg pattern-value)  (#analysisL.Deg pattern-value)]       [Frac (#.Frac pattern-value) (#analysisL.Frac pattern-value)]       [Text (#.Text pattern-value) (#analysisL.Text pattern-value)] -     [Top  (#.Tuple #.Nil)        #analysisL.Unit]) +     [Any  (#.Tuple #.Nil)        #analysisL.Unit])      (^ [cursor (#.Tuple (list singleton))])      (analyse-pattern #.None inputT singleton next) diff --git a/stdlib/source/lux/lang/analysis/primitive.lux b/stdlib/source/lux/lang/analysis/primitive.lux index f154932e6..74596fba2 100644 --- a/stdlib/source/lux/lang/analysis/primitive.lux +++ b/stdlib/source/lux/lang/analysis/primitive.lux @@ -24,5 +24,5 @@  (def: #export unit    (Meta Analysis)    (do macro.Monad<Meta> -    [_ (typeA.infer Top)] +    [_ (typeA.infer Any)]      (wrap (#//.Primitive #//.Unit)))) diff --git a/stdlib/source/lux/lang/analysis/structure.lux b/stdlib/source/lux/lang/analysis/structure.lux index 8e3611e67..4e91baad7 100644 --- a/stdlib/source/lux/lang/analysis/structure.lux +++ b/stdlib/source/lux/lang/analysis/structure.lux @@ -299,7 +299,7 @@    (case record      ## empty-record = empty-tuple = unit = []      #.Nil -    (:: macro.Monad<Meta> wrap [(list) Top]) +    (:: macro.Monad<Meta> wrap [(list) Any])      (#.Cons [head-k head-v] _)      (do macro.Monad<Meta> diff --git a/stdlib/source/lux/lang/analysis/type.lux b/stdlib/source/lux/lang/analysis/type.lux index 6d06d5cff..a7f9b3b29 100644 --- a/stdlib/source/lux/lang/analysis/type.lux +++ b/stdlib/source/lux/lang/analysis/type.lux @@ -42,7 +42,7 @@          output))))  (def: #export (infer actualT) -  (-> Type (Meta Top)) +  (-> Type (Meta Any))    (do macro.Monad<Meta>      [expectedT macro.expected-type]      (with-env diff --git a/stdlib/source/lux/lang/init.lux b/stdlib/source/lux/lang/init.lux index a1ef4ffb8..80e6d4740 100644 --- a/stdlib/source/lux/lang/init.lux +++ b/stdlib/source/lux/lang/init.lux @@ -35,7 +35,7 @@     #.mode    #.Build})  (def: #export (compiler host) -  (-> Top Lux) +  (-> Any Lux)    {#.info            ..info     #.source          dummy-source     #.cursor          .dummy-cursor @@ -46,11 +46,11 @@     #.expected        #.None     #.seed            +0     #.scope-type-vars (list) -   #.extensions      (:! Bottom +   #.extensions      (:! Nothing                           []                           ## {#extensionL.analysis analysisE.defaults                           ##  #extensionL.synthesis synthesisE.defaults                           ##  #extensionL.translation translationE.defaults                           ##  #extensionL.statement statementE.defaults}                           ) -   #.host            (:! Bottom host)}) +   #.host            (:! Nothing host)}) diff --git a/stdlib/source/lux/lang/module.lux b/stdlib/source/lux/lang/module.lux index d5efb1d7e..161fd073a 100644 --- a/stdlib/source/lux/lang/module.lux +++ b/stdlib/source/lux/lang/module.lux @@ -56,7 +56,7 @@     #.module-state       #.Active})  (def: #export (set-annotations annotations) -  (-> Code (Meta Top)) +  (-> Code (Meta Any))    (do macro.Monad<Meta>      [self-name macro.current-module-name       self macro.current-module] @@ -72,7 +72,7 @@        (//.throw cannot-set-module-annotations-more-than-once [self-name old annotations]))))  (def: #export (import module) -  (-> Text (Meta Top)) +  (-> Text (Meta Any))    (do macro.Monad<Meta>      [self-name macro.current-module-name]      (function (_ compiler) @@ -82,7 +82,7 @@                     []]))))  (def: #export (alias alias module) -  (-> Text Text (Meta Top)) +  (-> Text Text (Meta Any))    (do macro.Monad<Meta>      [self-name macro.current-module-name]      (function (_ compiler) @@ -141,7 +141,7 @@  (do-template [<setter> <asker> <tag>]    [(def: #export (<setter> module-name) -     (-> Text (Meta Top)) +     (-> Text (Meta Any))       (function (_ compiler)         (case (|> compiler (get@ #.modules) (plist.get module-name))           (#.Some module) @@ -194,7 +194,7 @@    )  (def: (ensure-undeclared-tags module-name tags) -  (-> Text (List Tag) (Meta Top)) +  (-> Text (List Tag) (Meta Any))    (do macro.Monad<Meta>      [bindings (..tags module-name)       _ (monad.map @ @@ -209,7 +209,7 @@      (wrap [])))  (def: #export (declare-tags tags exported? type) -  (-> (List Tag) Bool Type (Meta Top)) +  (-> (List Tag) Bool Type (Meta Any))    (do macro.Monad<Meta>      [self-name macro.current-module-name       [type-module type-name] (case type diff --git a/stdlib/source/lux/lang/syntax.lux b/stdlib/source/lux/lang/syntax.lux index bc1543cac..8029b5975 100644 --- a/stdlib/source/lux/lang/syntax.lux +++ b/stdlib/source/lux/lang/syntax.lux @@ -81,7 +81,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 Top) +  (l.Lexer Any)    ($_ 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 1bfea13d6..36e6a74a8 100644 --- a/stdlib/source/lux/lang/type.lux +++ b/stdlib/source/lux/lang/type.lux @@ -274,8 +274,8 @@         (#.Cons type types')         (<ctor> type (<name> types'))))] -  [variant Bottom #.Sum] -  [tuple   Top #.Product] +  [variant Nothing #.Sum] +  [tuple   Any #.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 4537ae38d..61001d8be 100644 --- a/stdlib/source/lux/lang/type/check.lux +++ b/stdlib/source/lux/lang/type/check.lux @@ -203,7 +203,7 @@        (ex.throw unknown-type-var id))))  (def: #export (write type id) -  (-> Type Var (Check Top)) +  (-> Type Var (Check Any))    (function (_ context)      (case (|> context (get@ #.var-bindings) (var::get id))        (#.Some (#.Some bound)) @@ -217,7 +217,7 @@        (ex.throw unknown-type-var id))))  (def: (update type id) -  (-> Type Var (Check Top)) +  (-> Type Var (Check Any))    (function (_ context)      (case (|> context (get@ #.var-bindings) (var::get id))        (#.Some _) @@ -243,7 +243,7 @@                   (get@ #.var-bindings context)])))  (def: (set-bindings value) -  (-> (List [Var (Maybe Type)]) (Check Top)) +  (-> (List [Var (Maybe Type)]) (Check Any))    (function (_ context)      (#e.Success [(set@ #.var-bindings value context)                   []]))) @@ -319,7 +319,7 @@      (#e.Error message)))  (def: #export (assert message test) -  (-> Text Bool (Check Top)) +  (-> Text Bool (Check Any))    (function (_ context)      (if test        (#e.Success [context []]) @@ -365,13 +365,13 @@          (else (maybe.default (#.Var id) ?bound)))))  (def: (link-2 left right) -  (-> Var Var (Check Top)) +  (-> Var Var (Check Any))    (do Monad<Check>      [_ (write (#.Var right) left)]      (write (#.Var left) right)))  (def: (link-3 interpose to from) -  (-> Var Var Var (Check Top)) +  (-> Var Var Var (Check Any))    (do Monad<Check>      [_ (update (#.Var interpose) from)]      (update (#.Var to) interpose))) @@ -449,7 +449,7 @@            (check' etype atype assumptions))))))  (def: (with-error-stack on-error check) -  (All [a] (-> (-> Top Text) (Check a) (Check a))) +  (All [a] (-> (-> Any Text) (Check a) (Check a)))    (function (_ context)      (case (check context)        (#e.Error error) @@ -625,7 +625,7 @@  (def: #export (check expected actual)    {#.doc "Type-check to ensure that the 'expected' type subsumes the 'actual' type."} -  (-> Type Type (Check Top)) +  (-> Type Type (Check Any))    (do Monad<Check>      [assumptions (check' expected actual (list))]      (wrap []))) | 
