From 35b77d1ae1e0e4d59f8341089b12c0043abaddd8 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 21 Jul 2018 02:57:44 -0400 Subject: Re-named "Ident" to "Name". --- stdlib/source/lux.lux | 230 ++++++++++----------- stdlib/source/lux/compiler/default/name.lux | 6 +- .../lux/compiler/default/phase/analysis/module.lux | 12 +- .../compiler/default/phase/analysis/reference.lux | 10 +- .../compiler/default/phase/analysis/structure.lux | 16 +- .../lux/compiler/default/phase/translation.lux | 12 +- .../phase/translation/scheme/reference.jvm.lux | 4 +- stdlib/source/lux/compiler/default/reference.lux | 2 +- stdlib/source/lux/compiler/default/repl/type.lux | 4 +- stdlib/source/lux/compiler/default/syntax.lux | 66 +++--- stdlib/source/lux/compiler/meta/archive.lux | 8 +- stdlib/source/lux/compiler/meta/cache.lux | 2 +- stdlib/source/lux/concurrency/actor.lux | 14 +- stdlib/source/lux/data/format/binary.lux | 10 +- stdlib/source/lux/data/format/xml.lux | 30 +-- stdlib/source/lux/data/ident.lux | 53 ----- stdlib/source/lux/data/name.lux | 53 +++++ stdlib/source/lux/data/text/format.lux | 4 +- stdlib/source/lux/data/text/regex.lux | 28 +-- stdlib/source/lux/host.jvm.lux | 2 +- stdlib/source/lux/macro.lux | 75 ++++--- stdlib/source/lux/macro/code.lux | 16 +- stdlib/source/lux/macro/poly.lux | 6 +- stdlib/source/lux/macro/syntax.lux | 6 +- stdlib/source/lux/macro/syntax/common.lux | 2 +- stdlib/source/lux/macro/syntax/common/reader.lux | 8 +- stdlib/source/lux/test.lux | 2 +- stdlib/source/lux/type.lux | 12 +- stdlib/source/lux/type/abstract.lux | 2 +- stdlib/source/lux/type/implicit.lux | 30 +-- stdlib/source/lux/type/object/interface.lux | 46 ++--- stdlib/source/lux/type/resource.lux | 3 +- stdlib/source/lux/type/unit.lux | 2 +- 33 files changed, 385 insertions(+), 391 deletions(-) delete mode 100644 stdlib/source/lux/data/ident.lux create mode 100644 stdlib/source/lux/data/name.lux (limited to 'stdlib/source') diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index f96062238..e53709ce2 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -153,8 +153,8 @@ [dummy-cursor (+5 "Your standard, run-of-the-mill string values.")]] #Nil))))]) -("lux def" Ident - (+10 ["lux" "Ident"] +("lux def" Name + (+10 ["lux" "Name"] (+2 Text Text)) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] @@ -201,7 +201,7 @@ ## (#UnivQ (List Type) Type) ## (#ExQ (List Type) Type) ## (#Apply Type Type) -## (#Named Ident Type) +## (#Named Name Type) ## ) ("lux def" Type (+10 ["lux" "Type"] @@ -231,7 +231,7 @@ (+1 ## "lux.Apply" Type-Pair ## "lux.Named" - (+2 Ident Type)))))))))))))} + (+2 Name Type)))))))))))))} ("lux check type" (+2 Type Type)))} ("lux check type" (+9 Type List)))} ("lux check type" (+9 (+4 +1) (+4 +0))))) @@ -311,8 +311,8 @@ ## (#Rev Rev) ## (#Frac Frac) ## (#Text Text) -## (#Symbol Ident) -## (#Tag Ident) +## (#Symbol Name) +## (#Tag Name) ## (#Form (List (w (Code' w)))) ## (#Tuple (List (w (Code' w)))) ## (#Record (List [(w (Code' w)) (w (Code' w))]))) @@ -334,9 +334,9 @@ (#Sum ## "lux.Text" Text (#Sum ## "lux.Symbol" - Ident + Name (#Sum ## "lux.Tag" - Ident + Name (#Sum ## "lux.Form" Code-List (#Sum ## "lux.Tuple" @@ -426,18 +426,18 @@ [dummy-cursor (#Record #Nil)]) ("lux def" symbol$ - ("lux check" (#Function Ident Code) - ([_ ident] (_ann (#Symbol ident)))) + ("lux check" (#Function Name Code) + ([_ name] (_ann (#Symbol name)))) [dummy-cursor (#Record #Nil)]) ("lux def" local-symbol$ ("lux check" (#Function Text Code) - ([_ ident] (_ann (#Symbol ["" ident])))) + ([_ name] (_ann (#Symbol ["" name])))) [dummy-cursor (#Record #Nil)]) ("lux def" tag$ - ("lux check" (#Function Ident Code) - ([_ ident] (_ann (#Tag ident)))) + ("lux check" (#Function Name Code) + ([_ name] (_ann (#Tag name)))) [dummy-cursor (#Record #Nil)]) ("lux def" form$ @@ -584,8 +584,8 @@ ## #module-aliases (List [Text Text]) ## #definitions (List [Text Definition]) ## #imports (List Text) -## #tags (List [Text [Nat (List Ident) Bit Type]]) -## #types (List [Text [(List Ident) Bit Type]]) +## #tags (List [Text [Nat (List Name) Bit Type]]) +## #types (List [Text [(List Name) Bit Type]]) ## #module-annotations (Maybe Code) ## #module-state Module-State}) ("lux def" Module @@ -601,13 +601,13 @@ (#Product ## "lux.tags" (#Apply (#Product Text (#Product Nat - (#Product (#Apply Ident List) + (#Product (#Apply Name List) (#Product Bit Type)))) List) (#Product ## "lux.types" (#Apply (#Product Text - (#Product (#Apply Ident List) + (#Product (#Apply Name List) (#Product Bit Type))) List) @@ -865,7 +865,7 @@ (record$ #Nil)) ("lux def" meta-code - ("lux check" (#Function Ident (#Function Code Code)) + ("lux check" (#Function Name (#Function Code Code)) ([_ tag] ([_ value] (tuple$ (#Cons cursor-code @@ -1770,17 +1770,17 @@ (-> Text Text Text) ("lux text concat" x y)) -(def:''' (ident/encode ident) +(def:''' (name/encode full-name) #Nil - (-> Ident Text) - (let' [[module name] ident] + (-> Name Text) + (let' [[module name] full-name] ({"" name _ ($_ text/compose module "." name)} module))) (def:''' (get-meta tag def-meta) #Nil - (-> Ident Code ($' Maybe Code)) + (-> Name Code ($' Maybe Code)) (let' [[prefix name] tag] ({[_ (#Record def-meta)] ({(#Cons [key value] def-meta') @@ -1805,10 +1805,10 @@ #None} def-meta))) -(def:''' (resolve-global-symbol ident state) +(def:''' (resolve-global-symbol full-name state) #Nil - (-> Ident ($' Meta Ident)) - (let' [[module name] ident + (-> Name ($' Meta Name)) + (let' [[module name] full-name {#info info #source source #current-module _ #modules modules #scopes scopes #type-context types #host host #seed seed #expected expected #cursor cursor #extensions extensions @@ -1819,15 +1819,15 @@ (#Right [state real-name]) _ - (#Right [state ident])} + (#Right [state full-name])} (get-meta ["lux" "alias"] def-meta)) #None - (#Left ($_ text/compose "Unknown definition: " (ident/encode ident)))} + (#Left ($_ text/compose "Unknown definition: " (name/encode full-name)))} (get name definitions)) #None - (#Left ($_ text/compose "Unknown module: " module " @ " (ident/encode ident)))} + (#Left ($_ text/compose "Unknown module: " module " @ " (name/encode full-name)))} (get module modules)))) (def:''' (splice replace? untemplate elems) @@ -2105,9 +2105,9 @@ (-> (-> b c) (-> a b) (-> a c))) (function' [x] (f (g x)))) -(def:''' (get-ident x) +(def:''' (get-name x) #Nil - (-> Code ($' Maybe Ident)) + (-> Code ($' Maybe Name)) ({[_ (#Symbol sname)] (#Some sname) @@ -2117,7 +2117,7 @@ (def:''' (get-tag x) #Nil - (-> Code ($' Maybe Ident)) + (-> Code ($' Maybe Name)) ({[_ (#Tag sname)] (#Some sname) @@ -2125,7 +2125,7 @@ #None} x)) -(def:''' (get-name x) +(def:''' (get-short x) #Nil (-> Code ($' Maybe Text)) ({[_ (#Symbol "" sname)] @@ -2273,7 +2273,7 @@ _ (fail "Wrong syntax for do-template")} - [(monad/map Monad get-name bindings) + [(monad/map Monad get-short bindings) (monad/map Monad tuple->list data)]) _ @@ -2642,24 +2642,24 @@ (get-meta ["lux" "macro?"] def-meta))) )) -(def:''' (normalize ident) +(def:''' (normalize name) #Nil - (-> Ident ($' Meta Ident)) + (-> Name ($' Meta Name)) ({["" name] (do Monad [module-name current-module-name] (wrap [module-name name])) _ - (return ident)} - ident)) + (return name)} + name)) -(def:''' (find-macro ident) +(def:''' (find-macro full-name) #Nil - (-> Ident ($' Meta ($' Maybe Macro))) + (-> Name ($' Meta ($' Maybe Macro))) (do Monad [current-module current-module-name] - (let' [[module name] ident] + (let' [[module name] full-name] (function' [state] ({{#info info #source source #current-module _ #modules modules #scopes scopes #type-context types #host host @@ -2669,12 +2669,12 @@ (#Right state (find-macro' modules current-module module name))} state))))) -(def:''' (macro? ident) +(def:''' (macro? name) #Nil - (-> Ident ($' Meta Bit)) + (-> Name ($' Meta Bit)) (do Monad - [ident (normalize ident) - output (find-macro ident)] + [name (normalize name) + output (find-macro name)] (wrap ({(#Some _) #1 #None #0} output)))) @@ -3431,7 +3431,7 @@ (list [(tag$ ["lux" "doc"]) (text$ "Macro-definition macro. - (macro: #export (ident-for tokens) + (macro: #export (name-for tokens) (case tokens (^template [] (^ (list [_ ( [prefix name])])) @@ -3439,9 +3439,9 @@ ([#Symbol] [#Tag]) _ - (fail \"Wrong syntax for ident-for\")))")]) + (fail \"Wrong syntax for name-for\")))")]) (let [[exported? tokens] (export^ tokens) - name+args+meta+body?? (: (Maybe [Ident (List Code) Code Code]) + name+args+meta+body?? (: (Maybe [Name (List Code) Code Code]) (case tokens (^ (list [_ (#Form (list& [_ (#Symbol name)] args))] body)) (#Some [name args (` {}) body]) @@ -3489,7 +3489,7 @@ (: (-> a a Bit) >=))"} (let [[exported? tokens'] (export^ tokens) - ?parts (: (Maybe [Ident (List Code) Code (List Code)]) + ?parts (: (Maybe [Name (List Code) Code (List Code)]) (case tokens' (^ (list& [_ (#Form (list& [_ (#Symbol name)] args))] [meta-rec-cursor (#Record meta-rec-parts)] sigs)) (#Some name args [meta-rec-cursor (#Record meta-rec-parts)] sigs) @@ -3791,7 +3791,7 @@ (find-module module-name))) (def: (resolve-tag [module name]) - (-> Ident (Meta [Nat (List Ident) Bit Type])) + (-> Name (Meta [Nat (List Name) Bit Type])) (do Monad [=module (find-module module) #let [{#module-hash _ #module-aliases _ #definitions bindings #imports _ #tags tags-table #types types #module-annotations _ #module-state _} =module]] @@ -3800,10 +3800,10 @@ (return output) _ - (fail (text/compose "Unknown tag: " (ident/encode [module name])))))) + (fail (text/compose "Unknown tag: " (name/encode [module name])))))) (def: (resolve-type-tags type) - (-> Type (Meta (Maybe [(List Ident) (List Type)]))) + (-> Type (Meta (Maybe [(List Name) (List Type)]))) (case type (#Apply arg func) (resolve-type-tags func) @@ -3853,7 +3853,7 @@ [tokens' (monad/map Monad macro-expand tokens) struct-type get-expected-type tags+type (resolve-type-tags struct-type) - tags (: (Meta (List Ident)) + tags (: (Meta (List Name)) (case tags+type (#Some [tags _]) (return tags) @@ -4339,7 +4339,7 @@ scopes))) (def: (find-def-type name state) - (-> Ident Lux (Maybe Type)) + (-> Name Lux (Maybe Type)) (let [[v-prefix v-name] name {#info info #source source #current-module _ #modules modules #scopes scopes #type-context types #host host @@ -4358,7 +4358,7 @@ (#Some def-type))))) (def: (find-def-value name state) - (-> Ident (Meta [Type Any])) + (-> Name (Meta [Type Any])) (let [[v-prefix v-name] name {#info info #source source #current-module _ #modules modules #scopes scopes #type-context types #host host @@ -4366,12 +4366,12 @@ #scope-type-vars scope-type-vars} state] (case (get v-prefix modules) #None - (#Left (text/compose "Unknown definition: " (ident/encode name))) + (#Left (text/compose "Unknown definition: " (name/encode name))) (#Some {#definitions definitions #module-hash _ #module-aliases _ #imports _ #tags tags #types types #module-annotations _ #module-state _}) (case (get v-name definitions) #None - (#Left (text/compose "Unknown definition: " (ident/encode name))) + (#Left (text/compose "Unknown definition: " (name/encode name))) (#Some [def-type def-meta def-value]) (#Right [state [def-type def-value]]))))) @@ -4387,10 +4387,10 @@ bound (find-type-var idx bindings')))) -(def: (find-type ident) - (-> Ident (Meta Type)) +(def: (find-type full-name) + (-> Name (Meta Type)) (do Monad - [#let [[module name] ident] + [#let [[module name] full-name] current-module current-module-name] (function (_ compiler) (let [temp (if (text/= "" module) @@ -4404,13 +4404,13 @@ (#Right [compiler struct-type]) _ - (#Left ($_ text/compose "Unknown var: " (ident/encode ident))))) - (case (find-def-type ident compiler) + (#Left ($_ text/compose "Unknown var: " (name/encode full-name))))) + (case (find-def-type full-name compiler) (#Some struct-type) (#Right [compiler struct-type]) _ - (#Left ($_ text/compose "Unknown var: " (ident/encode ident)))))] + (#Left ($_ text/compose "Unknown var: " (name/encode full-name)))))] (case temp (#Right [compiler (#Var type-id)]) (let [{#info _ #source _ #current-module _ #modules _ @@ -4511,7 +4511,7 @@ (#Some tags&members) (do Monad - [full-body ((: (-> Ident [(List Ident) (List Type)] Code (Meta Code)) + [full-body ((: (-> Name [(List Name) (List Type)] Code (Meta Code)) (function (recur source [tags members] target) (let [pattern (record$ (list/map (function (_ [t-module t-name]) [(tag$ [t-module t-name]) @@ -4593,7 +4593,7 @@ g!output (gensym "")] (case (resolve-struct-type type) (#Some members) - (let [pattern (record$ (list/map (: (-> [Ident [Nat Type]] [Code Code]) + (let [pattern (record$ (list/map (: (-> [Name [Nat Type]] [Code Code]) (function (_ [[r-prefix r-name] [r-idx r-type]]) [(tag$ [r-prefix r-name]) (if (n/= idx r-idx) @@ -4622,7 +4622,7 @@ (fail "Wrong syntax for get@"))) (def: (open-field alias [module name] source type) - (-> Text Ident Code Type (Meta (List Code))) + (-> Text Name Code Type (Meta (List Code))) (do Monad [output (resolve-type-tags type) #let [source+ (` (get@ (~ (tag$ [module name])) (~ source)))]] @@ -4630,7 +4630,7 @@ (#Some [tags members]) (do Monad [decls' (monad/map Monad - (: (-> [Ident Type] (Meta (List Code))) + (: (-> [Name Type] (Meta (List Code))) (function (_ [sname stype]) (open-field alias sname source+ stype))) (zip2 tags members))] (return (list/join decls'))) @@ -4660,7 +4660,7 @@ (case output (#Some [tags members]) (do Monad - [decls' (monad/map Monad (: (-> [Ident Type] (Meta (List Code))) + [decls' (monad/map Monad (: (-> [Name Type] (Meta (List Code))) (function (_ [sname stype]) (open-field alias sname source stype))) (zip2 tags members))] @@ -4829,26 +4829,20 @@ ## Examples (.module: {#.doc \"Some documentation...\"} - lux - (lux (control (monad #as M #refer #all)) - (data (text #open (\"text/\" Monoid)) - (collection (list #open (\"list/\" Monad))) - maybe - (ident #open (\"ident/\" Codec))) - meta - (macro code)) - (// (type #open (\"\" Equivalence)))) - - (.module: {#.doc \"Some documentation...\"} - lux - (lux (control [\"M\" monad #*]) - (data [text \"text/\" Monoid] - (collection [list \"list/\" Monad]) - maybe - [ident \"ident/\" Codec]) - meta - (macro code)) - (// [type \"\" Equivalence]))"} + [lux #* + [control + [\"M\" monad #*]] + [data + maybe + [\".\" name (\"name/.\" Codec)] + [\".\" text (\"text/.\" Monoid)] + [collection + [list (\"list/.\" Monad)]]] + meta + [macro + code]] + [// + [type (\".\" Equivalence)]])"} (do Monad [#let [[_meta _imports] (: [(List [Code Code]) (List Code)] (case tokens @@ -4913,18 +4907,18 @@ (#Some members) (do Monad [pattern' (monad/map Monad - (: (-> [Ident [Nat Type]] (Meta [Ident Nat Code])) + (: (-> [Name [Nat Type]] (Meta [Name Nat Code])) (function (_ [r-slot-name [r-idx r-type]]) (do Monad [g!slot (gensym "")] (return [r-slot-name r-idx g!slot])))) (zip2 tags (enumerate members)))] - (let [pattern (record$ (list/map (: (-> [Ident Nat Code] [Code Code]) + (let [pattern (record$ (list/map (: (-> [Name Nat Code] [Code Code]) (function (_ [r-slot-name r-idx r-var]) [(tag$ r-slot-name) r-var])) pattern')) - output (record$ (list/map (: (-> [Ident Nat Code] [Code Code]) + output (record$ (list/map (: (-> [Name Nat Code] [Code Code]) (function (_ [r-slot-name r-idx r-var]) [(tag$ r-slot-name) (if (n/= idx r-idx) @@ -5003,18 +4997,18 @@ (#Some members) (do Monad [pattern' (monad/map Monad - (: (-> [Ident [Nat Type]] (Meta [Ident Nat Code])) + (: (-> [Name [Nat Type]] (Meta [Name Nat Code])) (function (_ [r-slot-name [r-idx r-type]]) (do Monad [g!slot (gensym "")] (return [r-slot-name r-idx g!slot])))) (zip2 tags (enumerate members)))] - (let [pattern (record$ (list/map (: (-> [Ident Nat Code] [Code Code]) + (let [pattern (record$ (list/map (: (-> [Name Nat Code] [Code Code]) (function (_ [r-slot-name r-idx r-var]) [(tag$ r-slot-name) r-var])) pattern')) - output (record$ (list/map (: (-> [Ident Nat Code] [Code Code]) + output (record$ (list/map (: (-> [Name Nat Code] [Code Code]) (function (_ [r-slot-name r-idx r-var]) [(tag$ r-slot-name) (if (n/= idx r-idx) @@ -5097,7 +5091,7 @@ branches)) (case (: (Maybe (List Code)) (do Monad - [bindings' (monad/map Monad get-name bindings) + [bindings' (monad/map Monad get-short bindings) data' (monad/map Monad tuple->list data)] (if (every? (n/= (list/size bindings')) (list/map list/size data')) (let [apply (: (-> RepEnv (List Code)) @@ -5189,8 +5183,8 @@ ) (def: tag/encode - (-> Ident Text) - (|>> ident/encode (text/compose "#"))) + (-> Name Text) + (|>> name/encode (text/compose "#"))) (do-template [ ] [(def: #export @@ -5247,7 +5241,7 @@ [#Int int/encode] [#Frac frac/encode] [#Text text/encode] - [#Symbol ident/encode] + [#Symbol name/encode] [#Tag tag/encode]) (^template [ ] @@ -5389,8 +5383,8 @@ inits (list/map second pairs)] (if (every? symbol? inits) (do Monad - [inits' (: (Meta (List Ident)) - (case (monad/map Monad get-ident inits) + [inits' (: (Meta (List Name)) + (case (monad/map Monad get-name inits) (#Some inits') (return inits') #None (fail "Wrong syntax for loop"))) init-types (monad/map Monad find-type inits') @@ -5420,8 +5414,8 @@ (case tokens (^ (list& [_ (#Form (list [_ (#Tuple (list& hslot' tslots'))]))] body branches)) (do Monad - [slots (: (Meta [Ident (List Ident)]) - (case (: (Maybe [Ident (List Ident)]) + [slots (: (Meta [Name (List Name)]) + (case (: (Maybe [Name (List Name)]) (do Monad [hslot (get-tag hslot') tslots (monad/map Monad get-tag tslots')] @@ -5437,10 +5431,10 @@ output (resolve-tag hslot) g!_ (gensym "_") #let [[idx tags exported? type] output - slot-pairings (list/map (: (-> Ident [Text Code]) + slot-pairings (list/map (: (-> Name [Text Code]) (function (_ [module name]) [name (symbol$ ["" name])])) (list& hslot tslots)) - pattern (record$ (list/map (: (-> Ident [Code Code]) + pattern (record$ (list/map (: (-> Name [Code Code]) (function (_ [module name]) (let [tag (tag$ [module name])] (case (get name slot-pairings) @@ -5559,7 +5553,7 @@ type)) (def: (anti-quote-def name) - (-> Ident (Meta Code)) + (-> Name (Meta Code)) (do Monad [type+value (find-def-value name) #let [[type value] type+value]] @@ -5575,7 +5569,7 @@ ["Text" Text text$]) _ - (fail (text/compose "Cannot anti-quote type: " (ident/encode name)))))) + (fail (text/compose "Cannot anti-quote type: " (name/encode name)))))) (def: (anti-quote token) (-> Code (Meta Code)) @@ -5698,9 +5692,9 @@ _ (fail "Wrong syntax for ^multi"))) -(macro: #export (ident-for tokens) +(macro: #export (name-for tokens) {#.doc (doc "Given a symbol or a tag, gives back a 2 tuple with the prefix and name parts, both as Text." - (ident-for #.doc) + (name-for #.doc) "=>" ["lux" "doc"])} (case tokens @@ -5710,7 +5704,7 @@ ([#Symbol] [#Tag]) _ - (fail "Wrong syntax for ident-for"))) + (fail "Wrong syntax for name-for"))) (do-template [ <%> <=> <0> <2>] [(def: #export ( n) @@ -6069,8 +6063,8 @@ (fail "Wrong syntax for ``") )) -(def: (ident$ [module name]) - (-> Ident Code) +(def: (name$ [module name]) + (-> Name Code) (` [(~ (text$ module)) (~ (text$ name))])) (def: (untemplate-list& last inits) @@ -6090,14 +6084,14 @@ (do Monad [g!meta (gensym "g!meta")] (wrap (` [(~ g!meta) ( (~ ( value)))])))) - ([#Bit "Bit" bit$] - [#Nat "Nat" nat$] - [#Int "Int" int$] - [#Rev "Rev" rev$] - [#Frac "Frac" frac$] - [#Text "Text" text$] - [#Tag "Tag" ident$] - [#Symbol "Symbol" ident$]) + ([#Bit "Bit" bit$] + [#Nat "Nat" nat$] + [#Int "Int" int$] + [#Rev "Rev" rev$] + [#Frac "Frac" frac$] + [#Text "Text" text$] + [#Tag "Tag" name$] + [#Symbol "Symbol" name$]) [_ (#Record fields)] (do Monad diff --git a/stdlib/source/lux/compiler/default/name.lux b/stdlib/source/lux/compiler/default/name.lux index f6489b89c..50240a801 100644 --- a/stdlib/source/lux/compiler/default/name.lux +++ b/stdlib/source/lux/compiler/default/name.lux @@ -43,6 +43,6 @@ (|> (text.nth idx name) maybe.assume sanitize (format output))) output)))) -(def: #export (definition [module name]) - (-> Ident Text) - (format (normalize module) "___" (normalize name))) +(def: #export (definition [module short]) + (-> Name Text) + (format (normalize module) "___" (normalize short))) diff --git a/stdlib/source/lux/compiler/default/phase/analysis/module.lux b/stdlib/source/lux/compiler/default/phase/analysis/module.lux index adc442c1f..61d3a2ec6 100644 --- a/stdlib/source/lux/compiler/default/phase/analysis/module.lux +++ b/stdlib/source/lux/compiler/default/phase/analysis/module.lux @@ -35,8 +35,8 @@ [cannot-declare-tags-for-foreign-type] ) -(exception: #export (cannot-define-more-than-once {name Ident}) - (%ident name)) +(exception: #export (cannot-define-more-than-once {name Name}) + (%name name)) (exception: #export (can-only-change-state-of-active-module {module Text} {state Module-State}) (ex.report ["Module" module] @@ -203,8 +203,8 @@ #.None ((///.throw unknown-module module-name) state)))))] - [tags #.tags (List [Text [Nat (List Ident) Bit Type]])] - [types #.types (List [Text [(List Ident) Bit Type]])] + [tags #.tags (List [Text [Nat (List Name) Bit Type]])] + [types #.types (List [Text [(List Name) Bit Type]])] [hash #.module-hash Nat] ) @@ -228,8 +228,8 @@ (do ///.Monad [self-name (extension.lift macro.current-module-name) [type-module type-name] (case type - (#.Named type-ident _) - (wrap type-ident) + (#.Named type-name _) + (wrap type-name) _ (///.throw cannot-declare-tags-for-unnamed-type [tags type])) diff --git a/stdlib/source/lux/compiler/default/phase/analysis/reference.lux b/stdlib/source/lux/compiler/default/phase/analysis/reference.lux index bb78a32fb..0647dd391 100644 --- a/stdlib/source/lux/compiler/default/phase/analysis/reference.lux +++ b/stdlib/source/lux/compiler/default/phase/analysis/reference.lux @@ -19,16 +19,16 @@ (ex.report ["Current" current] ["Foreign" foreign])) -(exception: #export (definition-has-not-been-expored {definition Ident}) - (ex.report ["Definition" (%ident definition)])) +(exception: #export (definition-has-not-been-expored {definition Name}) + (ex.report ["Definition" (%name definition)])) ## [Analysers] (def: (definition def-name) - (-> Ident (Operation Analysis)) + (-> Name (Operation Analysis)) (with-expansions [ (wrap (|> def-name reference.constant #//.Reference))] (do ///.Monad [[actualT def-anns _] (extension.lift (macro.find-def def-name))] - (case (macro.get-symbol-ann (ident-for #.alias) def-anns) + (case (macro.get-symbol-ann (name-for #.alias) def-anns) (#.Some real-def-name) (definition real-def-name) @@ -61,7 +61,7 @@ (wrap #.None)))) (def: #export (reference reference) - (-> Ident (Operation Analysis)) + (-> Name (Operation Analysis)) (case reference ["" simple-name] (do ///.Monad diff --git a/stdlib/source/lux/compiler/default/phase/analysis/structure.lux b/stdlib/source/lux/compiler/default/phase/analysis/structure.lux index c50383eb8..e4d6159fc 100644 --- a/stdlib/source/lux/compiler/default/phase/analysis/structure.lux +++ b/stdlib/source/lux/compiler/default/phase/analysis/structure.lux @@ -4,7 +4,7 @@ ["." monad (#+ do)] ["ex" exception (#+ exception:)]] [data - ["." ident] + ["." name] ["." number] ["." product] ["." maybe] @@ -57,7 +57,7 @@ ["Record" (%code (code.record record))])) (do-template [] - [(exception: #export ( {key Ident} {record (List [Ident Code])}) + [(exception: #export ( {key Name} {record (List [Name Code])}) (ex.report ["Tag" (%code (code.tag key))] ["Record" (%code (code.record (list/map (function (_ [keyI valC]) [(code.tag keyI) valC]) @@ -66,11 +66,11 @@ [cannot-repeat-tag] ) -(exception: #export (tag-does-not-belong-to-record {key Ident} {type Type}) +(exception: #export (tag-does-not-belong-to-record {key Name} {type Type}) (ex.report ["Tag" (%code (code.tag key))] ["Type" (%type type)])) -(exception: #export (record-size-mismatch {expected Nat} {actual Nat} {type Type} {record (List [Ident Code])}) +(exception: #export (record-size-mismatch {expected Nat} {actual Nat} {type Type} {record (List [Name Code])}) (ex.report ["Expected" (|> expected .int %i)] ["Actual" (|> actual .int %i)] ["Type" (%type type)] @@ -259,7 +259,7 @@ )))) (def: #export (tagged-sum analyse tag valueC) - (-> Phase Ident Code (Operation Analysis)) + (-> Phase Name Code (Operation Analysis)) (do ///.Monad [tag (extension.lift (macro.normalize tag)) [idx group variantT] (extension.lift (macro.resolve-tag tag)) @@ -280,7 +280,7 @@ ## Normalization just means that all the tags get resolved to their ## canonical form (with their corresponding module identified). (def: #export (normalize record) - (-> (List [Code Code]) (Operation (List [Ident Code]))) + (-> (List [Code Code]) (Operation (List [Name Code]))) (monad.map ///.Monad (function (_ [key val]) (case key @@ -297,7 +297,7 @@ ## re-implementing the same functionality for records makes no sense. ## Records, thus, get transformed into tuples by ordering the elements. (def: #export (order record) - (-> (List [Ident Code]) (Operation [(List Code) Type])) + (-> (List [Name Code]) (Operation [(List Code) Type])) (case record ## empty-record = empty-tuple = unit = [] #.Nil @@ -313,7 +313,7 @@ (wrap []) (///.throw record-size-mismatch [size-ts size-record recordT record])) #let [tuple-range (list.n/range +0 (dec size-ts)) - tag->idx (dict.from-list ident.Hash (list.zip2 tag-set tuple-range))] + tag->idx (dict.from-list name.Hash (list.zip2 tag-set tuple-range))] idx->val (monad.fold @ (function (_ [key val] idx->val) (do @ diff --git a/stdlib/source/lux/compiler/default/phase/translation.lux b/stdlib/source/lux/compiler/default/phase/translation.lux index 82e31320a..f9b5dfbb4 100644 --- a/stdlib/source/lux/compiler/default/phase/translation.lux +++ b/stdlib/source/lux/compiler/default/phase/translation.lux @@ -6,7 +6,7 @@ [data ["." product] ["." error (#+ Error)] - [ident ("ident/." Equivalence Codec)] + [name ("name/." Equivalence Codec)] ["." text format] [collection @@ -30,8 +30,8 @@ message) (do-template [] - [(exception: #export ( {name Ident}) - (ex.report ["Artifact" (ident/encode name)]))] + [(exception: #export ( {name Name}) + (ex.report ["Artifact" (name/encode name)]))] [cannot-overwrite-artifact] [no-buffer-for-saving-code] @@ -47,7 +47,7 @@ (: (-> statement (Error Any)) execute!)) -(type: #export (Buffer statement) (Row [Ident statement])) +(type: #export (Buffer statement) (Row [Name statement])) (type: #export (Artifacts statement) (Dictionary File (Buffer statement))) @@ -175,13 +175,13 @@ (def: #export (save! name code) (All [anchor expression statement] - (-> Ident statement (Operation anchor expression statement Any))) + (-> Name statement (Operation anchor expression statement Any))) (do //.Monad [_ (execute! code) ?buffer (extension.read (get@ #buffer))] (case ?buffer (#.Some buffer) - (if (row.any? (|>> product.left (ident/= name)) buffer) + (if (row.any? (|>> product.left (name/= name)) buffer) (//.throw cannot-overwrite-artifact name) (extension.update (set@ #buffer (#.Some (row.add [name code] buffer))))) diff --git a/stdlib/source/lux/compiler/default/phase/translation/scheme/reference.jvm.lux b/stdlib/source/lux/compiler/default/phase/translation/scheme/reference.jvm.lux index 3fca5842f..240513fbc 100644 --- a/stdlib/source/lux/compiler/default/phase/translation/scheme/reference.jvm.lux +++ b/stdlib/source/lux/compiler/default/phase/translation/scheme/reference.jvm.lux @@ -40,11 +40,11 @@ operation/wrap)) (def: #export constant' - (-> Ident Var) + (-> Name Var) (|>> name.definition _.var)) (def: #export constant - (-> Ident (Operation Var)) + (-> Name (Operation Var)) (|>> constant' operation/wrap)) (def: #export reference' diff --git a/stdlib/source/lux/compiler/default/reference.lux b/stdlib/source/lux/compiler/default/reference.lux index 84b838b3d..086c72810 100644 --- a/stdlib/source/lux/compiler/default/reference.lux +++ b/stdlib/source/lux/compiler/default/reference.lux @@ -13,7 +13,7 @@ (type: #export Reference (#Variable Variable) - (#Constant Ident)) + (#Constant Name)) (structure: #export _ (Equivalence Variable) (def: (= reference sample) diff --git a/stdlib/source/lux/compiler/default/repl/type.lux b/stdlib/source/lux/compiler/default/repl/type.lux index 2af590c4b..4a1cdbe57 100644 --- a/stdlib/source/lux/compiler/default/repl/type.lux +++ b/stdlib/source/lux/compiler/default/repl/type.lux @@ -80,7 +80,7 @@ (format "(#.Some " (elemR elemV) ")")))))))) (def: (record-representation tags representation) - (-> (List Ident) (Poly Representation) (Poly Representation)) + (-> (List Name) (Poly Representation) (Poly Representation)) (do p.Monad [membersR+ (poly.tuple (p.many representation)) _ (p.assert "Number of tags does not match record type size." @@ -102,7 +102,7 @@ (format "{" record-body "}")))))) (def: (variant-representation tags representation) - (-> (List Ident) (Poly Representation) (Poly Representation)) + (-> (List Name) (Poly Representation) (Poly Representation)) (do p.Monad [casesR+ (poly.variant (p.many representation)) #let [num-tags (list.size tags)] diff --git a/stdlib/source/lux/compiler/default/syntax.lux b/stdlib/source/lux/compiler/default/syntax.lux index 41c11ee2d..1378e37c0 100644 --- a/stdlib/source/lux/compiler/default/syntax.lux +++ b/stdlib/source/lux/compiler/default/syntax.lux @@ -482,18 +482,18 @@ (wrap [where' [where (#.Record elems)]]))) -## The parts of an identifier are separated by a single mark. -## E.g. module.name. -## Only one such mark may be used in an identifier, since there -## can only be 2 parts to an identifier (the module [before the -## mark], and the name [after the mark]). -## There are also some extra rules regarding identifier syntax, +## The parts of an name are separated by a single mark. +## E.g. module.short. +## Only one such mark may be used in an name, since there +## can only be 2 parts to an name (the module [before the +## mark], and the short [after the mark]). +## There are also some extra rules regarding name syntax, ## encoded on the parser. -(def: identifier-separator Text ".") +(def: name-separator Text ".") -## A Lux identifier is a pair of chunks of text, where the first-part -## refers to the module that gives context to the identifier, and the -## second part corresponds to the name of the identifier itself. +## A Lux name is a pair of chunks of text, where the first-part +## refers to the module that gives context to the name, and the +## second part corresponds to the short of the name itself. ## The module part may be absent (by being the empty text ""), but the ## name part must always be present. ## The rules for which characters you may use are specified in terms @@ -502,13 +502,13 @@ ## In particular, no white-space can be used, and neither can other ## characters which are already used by Lux as delimiters for other ## Code nodes (thereby reducing ambiguity while parsing). -## Additionally, the first character in an identifier's part cannot be +## Additionally, the first character in an name's part cannot be ## a digit, to avoid confusion with regards to numbers. -(def: ident-part^ +(def: name-part^ (l.Lexer Text) (do p.Monad [#let [digits "0123456789" - delimiters (format "()[]{}#\"" identifier-separator) + delimiters (format "()[]{}#\"" name-separator) space (format white-space new-line) head-lexer (l.none-of (format digits delimiters space)) tail-lexer (l.some (l.none-of (format delimiters space)))] @@ -516,45 +516,45 @@ tail tail-lexer] (wrap (format head tail)))) -(def: current-module-mark Text (format identifier-separator identifier-separator)) +(def: current-module-mark Text (format name-separator name-separator)) -(def: (ident^ current-module aliases) - (-> Text Aliases (l.Lexer [Ident Nat])) +(def: (name^ current-module aliases) + (-> Text Aliases (l.Lexer [Name Nat])) ($_ p.either - ## When an identifier starts with 2 marks, its module is + ## When an name starts with 2 marks, its module is ## taken to be the current-module being compiled at the moment. - ## This can be useful when mentioning identifiers and tags + ## This can be useful when mentioning names and tags ## inside quoted/templated code in macros. (do p.Monad [_ (l.this current-module-mark) - def-name ident-part^] + def-name name-part^] (wrap [[current-module def-name] (n/+ +2 (text.size def-name))])) - ## If the identifier is prefixed by the mark, but no module + ## If the name is prefixed by the mark, but no module ## part, the module is assumed to be "lux" (otherwise known as ## the 'prelude'). ## This makes it easy to refer to definitions in that module, ## since it is the most fundamental module in the entire ## standard library. (do p.Monad - [_ (l.this identifier-separator) - def-name ident-part^] + [_ (l.this name-separator) + def-name name-part^] (wrap [["lux" def-name] (inc (text.size def-name))])) - ## Not all identifiers must be specified with a module part. - ## If that part is not provided, the identifier will be created + ## Not all names must be specified with a module part. + ## If that part is not provided, the name will be created ## with the empty "" text as the module. - ## During program analysis, such identifiers tend to be treated + ## During program analysis, such names tend to be treated ## as if their context is the current-module, but this only - ## applies to identifiers for tags and module definitions. + ## applies to names for tags and module definitions. ## Function arguments and local-variables may not be referred-to - ## using identifiers with module parts, so being able to specify - ## identifiers with empty modules helps with those use-cases. + ## using names with module parts, so being able to specify + ## names with empty modules helps with those use-cases. (do p.Monad - [first-part ident-part^] + [first-part name-part^] (p.either (do @ - [_ (l.this identifier-separator) - second-part ident-part^] + [_ (l.this name-separator) + second-part name-part^] (wrap [[(|> aliases (dict.get first-part) (maybe.default first-part)) second-part] ($_ n/+ @@ -568,14 +568,14 @@ (-> Text Aliases Cursor (l.Lexer [Cursor Code])) (do p.Monad [[value length] (p.after (l.this "#") - (ident^ current-module aliases))] + (name^ current-module aliases))] (wrap [(update@ #.column (|>> ($_ n/+ +1 length)) where) [where (#.Tag value)]]))) (def: #export (symbol current-module aliases where) (-> Text Aliases Cursor (l.Lexer [Cursor Code])) (do p.Monad - [[value length] (ident^ current-module aliases)] + [[value length] (name^ current-module aliases)] (wrap [(update@ #.column (|>> (n/+ length)) where) [where (case value (^template [ ] diff --git a/stdlib/source/lux/compiler/meta/archive.lux b/stdlib/source/lux/compiler/meta/archive.lux index ee31e65d9..47572fe04 100644 --- a/stdlib/source/lux/compiler/meta/archive.lux +++ b/stdlib/source/lux/compiler/meta/archive.lux @@ -6,7 +6,7 @@ ["." monad (#+ do)]] [data ["." error (#+ Error)] - ["." ident] + ["." name] ["." text format] [collection @@ -20,16 +20,16 @@ ## Key (type: #export Signature - {#name Ident + {#name Name #version Version}) (def: Equivalence (Equivalence Signature) - (equivalence.product ident.Equivalence text.Equivalence)) + (equivalence.product name.Equivalence text.Equivalence)) (def: (describe signature) (-> Signature Text) - (format (%ident (get@ #name signature)) " " (get@ #version signature))) + (format (%name (get@ #name signature)) " " (get@ #version signature))) (abstract: #export (Key k) {} diff --git a/stdlib/source/lux/compiler/meta/cache.lux b/stdlib/source/lux/compiler/meta/cache.lux index eb702c0da..fe9a32266 100644 --- a/stdlib/source/lux/compiler/meta/cache.lux +++ b/stdlib/source/lux/compiler/meta/cache.lux @@ -99,7 +99,7 @@ ## Load (def: signature (Format Signature) - ($_ binary.seq binary.ident binary.text)) + ($_ binary.seq binary.name binary.text)) (def: descriptor (Format Descriptor) diff --git a/stdlib/source/lux/concurrency/actor.lux b/stdlib/source/lux/concurrency/actor.lux index 52bf7621d..b9b1a22c2 100644 --- a/stdlib/source/lux/concurrency/actor.lux +++ b/stdlib/source/lux/concurrency/actor.lux @@ -150,15 +150,15 @@ ## [Syntax] (do-template [ ] [(def: #export ( name) - (-> Ident cs.Annotations cs.Annotations) - (|>> (#.Cons [(ident-for ) + (-> Name cs.Annotations cs.Annotations) + (|>> (#.Cons [(name-for ) (code.tag name)]))) (def: #export ( name) - (-> Ident (Meta Ident)) + (-> Name (Meta Name)) (do Monad [[_ annotations _] (macro.find-def name)] - (case (macro.get-tag-ann (ident-for ) annotations) + (case (macro.get-tag-ann (name-for ) annotations) (#.Some actor-name) (wrap actor-name) @@ -293,7 +293,7 @@ s.any))) (def: reference^ - (s.Syntax [Ident (List Text)]) + (s.Syntax [Name (List Text)]) (p.either (s.form (p.seq s.symbol (p.some s.local-symbol))) (p.seq s.symbol (:: p.Monad wrap (list))))) @@ -373,7 +373,7 @@ (~ g!self))] (if (~ g!sent?) ((~' wrap) (~ g!task)) - ((~' wrap) (task.throw ..dead [(~ (code.text (%ident actor-name))) - (~ (code.text (%ident message-name)))])))))))) + ((~' wrap) (task.throw ..dead [(~ (code.text (%name actor-name))) + (~ (code.text (%name message-name)))])))))))) )) ))) diff --git a/stdlib/source/lux/data/format/binary.lux b/stdlib/source/lux/data/format/binary.lux index 27a510b44..add376a44 100644 --- a/stdlib/source/lux/data/format/binary.lux +++ b/stdlib/source/lux/data/format/binary.lux @@ -219,8 +219,8 @@ (..alt ..any (..seq value recur))))) -(def: #export ident - (Format Ident) +(def: #export name + (Format Name) (..seq ..text ..text)) (def: #export type @@ -252,7 +252,7 @@ ## #Apply pair ## #Named - (..seq ..ident type) + (..seq ..name type) ))))) (def: #export cursor @@ -278,9 +278,9 @@ ## #Text ..text ## #Symbol - ..ident + ..name ## #Tag - ..ident + ..name ## #Form sequence ## #Tuple diff --git a/stdlib/source/lux/data/format/xml.lux b/stdlib/source/lux/data/format/xml.lux index 5e92de080..a990e6901 100644 --- a/stdlib/source/lux/data/format/xml.lux +++ b/stdlib/source/lux/data/format/xml.lux @@ -10,17 +10,17 @@ ["." number] ["E" error] ["." product] - ["." ident ("ident/." Equivalence Codec)] + ["." name ("name/." Equivalence Codec)] ["." text ("text/." Equivalence Monoid) ["l" lexer]] [collection ["." list ("list/." Monad)] ["d" dictionary]]]]) -(type: #export Tag Ident) -(type: #export Attrs (d.Dictionary Ident Text)) +(type: #export Tag Name) +(type: #export Attrs (d.Dictionary Name Text)) -(def: #export attrs Attrs (d.new ident.Hash)) +(def: #export attrs Attrs (d.new name.Hash)) (type: #export #rec XML (#Text Text) @@ -69,7 +69,7 @@ (wrap ($_ text/compose head tail)))) (def: namespaced-symbol^ - (l.Lexer Ident) + (l.Lexer Name) (do p.Monad [first-part xml-identifier ?second-part (<| p.maybe (p.after (l.this ":")) xml-identifier)] @@ -97,7 +97,7 @@ (def: attrs^ (l.Lexer Attrs) - (<| (:: p.Monad map (d.from-list ident.Hash)) + (<| (:: p.Monad map (d.from-list name.Hash)) p.some (p.seq (spaced^ attr-name^)) (p.after (l.this "=")) @@ -111,9 +111,9 @@ (p.after (l.this "/")) (l.enclosed ["<" ">"]))] (p.assert ($_ text/compose "Close tag does not match open tag.\n" - "Expected: " (ident/encode expected) "\n" - " Actual: " (ident/encode actual) "\n") - (ident/= expected actual)))) + "Expected: " (name/encode expected) "\n" + " Actual: " (name/encode actual) "\n") + (name/= expected actual)))) (def: comment^ (l.Lexer Text) @@ -234,7 +234,7 @@ [(#Node reference/tag reference/attrs reference/children) (#Node sample/tag sample/attrs sample/children)] - (and (ident/= reference/tag sample/tag) + (and (name/= reference/tag sample/tag) (:: (d.Equivalence text.Equivalence) = reference/attrs sample/attrs) (n/= (list.size reference/children) (list.size sample/children)) @@ -251,8 +251,8 @@ (exception: #export unexpected-input) (exception: #export unknown-attribute) -(exception: #export (wrong-tag {tag Ident}) - (ident/encode tag)) +(exception: #export (wrong-tag {tag Name}) + (name/encode tag)) (exception: #export (unconsumed-inputs {inputs (List XML)}) (|> inputs @@ -275,7 +275,7 @@ (ex.throw unexpected-input []))))) (def: #export (attr name) - (-> Ident (Reader Text)) + (-> Name (Reader Text)) (function (_ docs) (case docs #.Nil @@ -306,7 +306,7 @@ (#E.Error error))) (def: #export (node tag) - (-> Ident (Reader Any)) + (-> Name (Reader Any)) (function (_ docs) (case docs #.Nil @@ -318,7 +318,7 @@ (ex.throw unexpected-input []) (#Node _tag _attrs _children) - (if (ident/= tag _tag) + (if (name/= tag _tag) (#E.Success [docs []]) (ex.throw wrong-tag tag)))))) diff --git a/stdlib/source/lux/data/ident.lux b/stdlib/source/lux/data/ident.lux deleted file mode 100644 index 27d45227f..000000000 --- a/stdlib/source/lux/data/ident.lux +++ /dev/null @@ -1,53 +0,0 @@ -(.module: - [lux #* - [control - [equivalence (#+ Equivalence)] - [codec (#+ Codec)] - hash] - [data - ["." text ("text/." Monoid Hash)]]]) - -## [Types] -## (type: Ident -## [Text Text]) - -## [Functions] -(do-template [ ] - [(def: #export ( [module name]) - (-> Ident Text) - )] - - [module module] - [name name] - ) - -## [Structures] -(structure: #export _ (Equivalence Ident) - (def: (= [xmodule xname] [ymodule yname]) - (and (text/= xmodule ymodule) - (text/= xname yname)))) - -(structure: #export _ (Codec Text Ident) - (def: (encode [module name]) - (case module - "" name - _ ($_ text/compose module "." name))) - - (def: (decode input) - (if (text/= "" input) - (#.Left (text/compose "Invalid format for Ident: " input)) - (case (text.split-all-with "." input) - (^ (list name)) - (#.Right ["" name]) - - (^ (list module name)) - (#.Right [module name]) - - _ - (#.Left (text/compose "Invalid format for Ident: " input)))))) - -(structure: #export _ (Hash Ident) - (def: eq Equivalence) - - (def: (hash [module name]) - (n/+ (text/hash module) (text/hash name)))) diff --git a/stdlib/source/lux/data/name.lux b/stdlib/source/lux/data/name.lux new file mode 100644 index 000000000..0129bc5cc --- /dev/null +++ b/stdlib/source/lux/data/name.lux @@ -0,0 +1,53 @@ +(.module: + [lux #* + [control + [equivalence (#+ Equivalence)] + [codec (#+ Codec)] + hash] + [data + ["." text ("text/." Monoid Hash)]]]) + +## [Types] +## (type: Name +## [Text Text]) + +## [Functions] +(do-template [ ] + [(def: #export ( [module short]) + (-> Name Text) + )] + + [module module] + [short short] + ) + +## [Structures] +(structure: #export _ (Equivalence Name) + (def: (= [xmodule xname] [ymodule yname]) + (and (text/= xmodule ymodule) + (text/= xname yname)))) + +(structure: #export _ (Codec Text Name) + (def: (encode [module short]) + (case module + "" short + _ ($_ text/compose module "." short))) + + (def: (decode input) + (if (text/= "" input) + (#.Left (text/compose "Invalid format for Name: " input)) + (case (text.split-all-with "." input) + (^ (list short)) + (#.Right ["" short]) + + (^ (list module short)) + (#.Right [module short]) + + _ + (#.Left (text/compose "Invalid format for Name: " input)))))) + +(structure: #export _ (Hash Name) + (def: eq Equivalence) + + (def: (hash [module name]) + (n/+ (text/hash module) (text/hash name)))) diff --git a/stdlib/source/lux/data/text/format.lux b/stdlib/source/lux/data/text/format.lux index 7592b7b28..7f4188154 100644 --- a/stdlib/source/lux/data/text/format.lux +++ b/stdlib/source/lux/data/text/format.lux @@ -5,7 +5,7 @@ ["p" parser]] [data ["." bit] - ["." ident] + ["." name] ["." number] ["." text] [format @@ -46,7 +46,7 @@ [%r Rev (:: number.Codec encode)] [%f Frac (:: number.Codec encode)] [%t Text text.encode] - [%ident Ident (:: ident.Codec encode)] + [%name Name (:: name.Codec encode)] [%code Code code.to-text] [%type Type type.to-text] [%bin Nat (:: number.Binary@Codec encode)] diff --git a/stdlib/source/lux/data/text/regex.lux b/stdlib/source/lux/data/text/regex.lux index 34505d157..158eea153 100644 --- a/stdlib/source/lux/data/text/regex.lux +++ b/stdlib/source/lux/data/text/regex.lux @@ -52,31 +52,31 @@ [parts part^] (wrap (text.join-with "" parts)))) -(def: identifier-char^ +(def: name-char^ (l.Lexer Text) (l.none-of "[]{}()s\"#.<>")) -(def: identifier-part^ +(def: name-part^ (l.Lexer Text) (do p.Monad [head (refine^ (l.not l.decimal) - identifier-char^) - tail (l.some identifier-char^)] + name-char^) + tail (l.some name-char^)] (wrap (format head tail)))) -(def: (identifier^ current-module) - (-> Text (l.Lexer Ident)) +(def: (name^ current-module) + (-> Text (l.Lexer Name)) ($_ p.either - (p.seq (parser/wrap current-module) (p.after (l.this "..") identifier-part^)) - (p.seq identifier-part^ (p.after (l.this ".") identifier-part^)) - (p.seq (parser/wrap "lux") (p.after (l.this ".") identifier-part^)) - (p.seq (parser/wrap "") identifier-part^))) + (p.seq (parser/wrap current-module) (p.after (l.this "..") name-part^)) + (p.seq name-part^ (p.after (l.this ".") name-part^)) + (p.seq (parser/wrap "lux") (p.after (l.this ".") name-part^)) + (p.seq (parser/wrap "") name-part^))) (def: (re-var^ current-module) (-> Text (l.Lexer Code)) (do p.Monad - [ident (l.enclosed ["\\@<" ">"] (identifier^ current-module))] - (wrap (` (: (l.Lexer Text) (~ (code.symbol ident))))))) + [name (l.enclosed ["\\@<" ">"] (name^ current-module))] + (wrap (` (: (l.Lexer Text) (~ (code.symbol name))))))) (def: re-range^ (l.Lexer Code) @@ -194,7 +194,7 @@ (wrap (` ((~! ..copy) (~ (code.symbol ["" (int/encode (.int id))])))))) (do p.Monad [_ (l.this "\\k<") - captured-name identifier-part^ + captured-name name-part^ _ (l.this ">")] (wrap (` ((~! ..copy) (~ (code.symbol ["" captured-name])))))))) @@ -384,7 +384,7 @@ (wrap [#Non-Capturing complex])) (do p.Monad [_ (l.this "(?<") - captured-name identifier-part^ + captured-name name-part^ _ (l.this ">") [num-captures pattern] (re-alternative^ #1 re-scoped^ current-module) _ (l.this ")")] diff --git a/stdlib/source/lux/host.jvm.lux b/stdlib/source/lux/host.jvm.lux index a3f8a82c4..7b02f3df6 100644 --- a/stdlib/source/lux/host.jvm.lux +++ b/stdlib/source/lux/host.jvm.lux @@ -369,7 +369,7 @@ definitions (macro.definitions current-module)] (wrap (list/fold (: (-> [Text Definition] Class-Imports Class-Imports) (function (_ [short-name [_ meta _]] imports) - (case (macro.get-text-ann (ident-for #..jvm-class) meta) + (case (macro.get-text-ann (name-for #..jvm-class) meta) (#.Some full-class-name) (add-import [short-name full-class-name] imports) diff --git a/stdlib/source/lux/macro.lux b/stdlib/source/lux/macro.lux index 64dfcff24..f6dc72204 100644 --- a/stdlib/source/lux/macro.lux +++ b/stdlib/source/lux/macro.lux @@ -6,7 +6,7 @@ ["." monad (#+ do Monad)]] [data ["." product] - [ident ("ident/." Codec Equivalence)] + [name ("name/." Codec Equivalence)] ["." maybe] ["e" error] ["." number ("nat/." Codec)] @@ -142,7 +142,7 @@ (def: #export (get-ann tag anns) {#.doc "Looks-up a particular annotation's value within the set of annotations."} - (-> Ident Code (Maybe Code)) + (-> Name Code (Maybe Code)) (case anns [_ (#.Record anns)] (loop [anns anns] @@ -150,7 +150,7 @@ (#.Cons [key value] anns') (case key [_ (#.Tag tag')] - (if (ident/= tag tag') + (if (name/= tag tag') (#.Some value) (recur anns')) @@ -165,7 +165,7 @@ (do-template [ ] [(def: #export ( tag anns) - (-> Ident Code (Maybe )) + (-> Name Code (Maybe )) (case (get-ann tag anns) (#.Some [_ ( value)]) (#.Some value) @@ -177,8 +177,8 @@ [get-int-ann #.Int Int] [get-frac-ann #.Frac Frac] [get-text-ann #.Text Text] - [get-symbol-ann #.Symbol Ident] - [get-tag-ann #.Tag Ident] + [get-symbol-ann #.Symbol Name] + [get-tag-ann #.Tag Name] [get-form-ann #.Form (List Code)] [get-tuple-ann #.Tuple (List Code)] [get-record-ann #.Record (List [Code Code])] @@ -187,18 +187,18 @@ (def: #export (get-doc anns) {#.doc "Looks-up a definition's documentation."} (-> Code (Maybe Text)) - (get-text-ann (ident-for #.doc) anns)) + (get-text-ann (name-for #.doc) anns)) (def: #export (flag-set? flag-name anns) {#.doc "Finds out whether an annotation-as-a-flag is set (has value '#1')."} - (-> Ident Code Bit) + (-> Name Code Bit) (maybe.default #0 (get-bit-ann flag-name anns))) (do-template [ ] [(def: #export {#.doc (code.text ($_ text/compose "Checks whether a definition is " "."))} (-> Code Bit) - (flag-set? (ident-for )))] + (flag-set? (name-for )))] [export? #.export? "exported"] [macro? #.macro? "a macro"] @@ -210,7 +210,7 @@ (def: #export (aliased? annotations) (-> Code Bit) - (case (get-symbol-ann (ident-for #.alias) annotations) + (case (get-symbol-ann (name-for #.alias) annotations) (#.Some _) #1 @@ -237,7 +237,7 @@ (-> Code (List Text)) (maybe.default (list) (do maybe.Monad - [_args (get-ann (ident-for ) anns) + [_args (get-ann (name-for ) anns) args (parse-tuple _args)] (monad.map @ parse-text args))))] @@ -255,36 +255,35 @@ (if (and (macro? def-anns) (or (export? def-anns) (text/= module this-module))) (#.Some (:coerce Macro def-value)) - (case (get-symbol-ann (ident-for #.alias) def-anns) + (case (get-symbol-ann (name-for #.alias) def-anns) (#.Some [r-module r-name]) (find-macro' modules this-module r-module r-name) _ #.None)))) -(def: #export (normalize ident) - {#.doc "If given an identifier without a module prefix, gives it the current module's name as prefix. +(def: #export (normalize name) + {#.doc "If given a name without a module prefix, gives it the current module's name as prefix. - Otherwise, returns the identifier as-is."} - (-> Ident (Meta Ident)) - (case ident + Otherwise, returns the name as-is."} + (-> Name (Meta Name)) + (case name ["" name] (do Monad [module-name current-module-name] (wrap [module-name name])) _ - (:: Monad wrap ident))) + (:: Monad wrap name))) -(def: #export (find-macro ident) - (-> Ident (Meta (Maybe Macro))) +(def: #export (find-macro full-name) + (-> Name (Meta (Maybe Macro))) (do Monad - [ident (normalize ident) + [[module name] (normalize full-name) this-module current-module-name] - (let [[module name] ident] - (: (Meta (Maybe Macro)) - (function (_ compiler) - (#e.Success [compiler (find-macro' (get@ #.modules compiler) this-module module name)])))))) + (: (Meta (Maybe Macro)) + (function (_ compiler) + (#e.Success [compiler (find-macro' (get@ #.modules compiler) this-module module name)]))))) (def: #export (expand-once syntax) {#.doc "Given code that requires applying a macro, does it once and returns the result. @@ -361,7 +360,7 @@ (:: Monad wrap (list syntax)))) (def: #export (gensym prefix) - {#.doc "Generates a unique identifier as an Code node (ready to be used in code templates). + {#.doc "Generates a unique name as an Code node (ready to be used in code templates). A prefix can be given (or just be empty text \"\") to better identify the code for debugging purposes."} (-> Text (Meta Code)) @@ -490,7 +489,7 @@ (def: #export (find-def name) {#.doc "Looks-up a definition's whole data in the available modules (including the current one)."} - (-> Ident (Meta Definition)) + (-> Name (Meta Definition)) (do Monad [name (normalize name)] (function (_ compiler) @@ -505,7 +504,7 @@ _ (let [current-module (|> compiler (get@ #.current-module) (maybe.default "???"))] (#e.Error ($_ text/compose - "Unknown definition: " (ident/encode name) "\n" + "Unknown definition: " (name/encode name) "\n" " Current module: " current-module "\n" (case (get current-module (get@ #.modules compiler)) (#.Some this-module) @@ -519,14 +518,14 @@ (def: #export (find-def-type name) {#.doc "Looks-up a definition's type in the available modules (including the current one)."} - (-> Ident (Meta Type)) + (-> Name (Meta Type)) (do Monad [[def-type def-data def-value] (find-def name)] (clean-type def-type))) (def: #export (find-type name) {#.doc "Looks-up the type of either a local variable or a definition."} - (-> Ident (Meta Type)) + (-> Name (Meta Type)) (do Monad [#let [[_ _name] name]] (case name @@ -539,7 +538,7 @@ (def: #export (find-type-def name) {#.doc "Finds the value of a type definition (such as Int, Any or Lux)."} - (-> Ident (Meta Type)) + (-> Name (Meta Type)) (do Monad [[def-type def-data def-value] (find-def name)] (wrap (:coerce Type def-value)))) @@ -573,7 +572,7 @@ (def: #export (tags-of type-name) {#.doc "All the tags associated with a type definition."} - (-> Ident (Meta (Maybe (List Ident)))) + (-> Name (Meta (Maybe (List Name)))) (do Monad [#let [[module name] type-name] module (find-module module)] @@ -623,7 +622,7 @@ (def: #export (resolve-tag tag) {#.doc "Given a tag, finds out what is its index, its related tag-list and it's associated type."} - (-> Ident (Meta [Nat (List Ident) Type])) + (-> Name (Meta [Nat (List Name) Type])) (do Monad [#let [[module name] tag] =module (find-module module) @@ -634,14 +633,14 @@ (if (or (text/= this-module-name module) (and imported! exported?)) (wrap [idx tag-list type]) - (fail ($_ text/compose "Cannot access tag: " (ident/encode tag) " from module " this-module-name))) + (fail ($_ text/compose "Cannot access tag: " (name/encode tag) " from module " this-module-name))) _ - (fail ($_ text/compose "Unknown tag: " (ident/encode tag)))))) + (fail ($_ text/compose "Unknown tag: " (name/encode tag)))))) (def: #export (tag-lists module) {#.doc "All the tag-lists defined in a module, with their associated types."} - (-> Text (Meta (List [(List Ident) Type]))) + (-> Text (Meta (List [(List Name) Type]))) (do Monad [=module (find-module module) this-module-name current-module-name] @@ -669,10 +668,10 @@ (def: #export (un-alias def-name) {#.doc "Given an aliased definition's name, returns the original definition being referenced."} - (-> Ident (Meta Ident)) + (-> Name (Meta Name)) (do Monad [[_ def-anns _] (find-def def-name)] - (case (get-symbol-ann (ident-for #.alias) def-anns) + (case (get-symbol-ann (name-for #.alias) def-anns) (#.Some real-def-name) (wrap real-def-name) diff --git a/stdlib/source/lux/macro/code.lux b/stdlib/source/lux/macro/code.lux index de6f1fd50..b48406f13 100644 --- a/stdlib/source/lux/macro/code.lux +++ b/stdlib/source/lux/macro/code.lux @@ -5,7 +5,7 @@ [data bit number - ident + name ["." text (#+ Equivalence) ("text/." Monoid)] [collection ["." list ("list/." Functor Fold)]]]]) @@ -41,8 +41,8 @@ [rev Rev #.Rev] [frac Frac #.Frac] [text Text #.Text] - [symbol Ident #.Symbol] - [tag Ident #.Tag] + [symbol Name #.Symbol] + [tag Name #.Tag] [form (List Code) #.Form] [tuple (List Code) #.Tuple] [record (List [Code Code]) #.Record] @@ -70,8 +70,8 @@ [#.Rev Equivalence] [#.Frac Equivalence] [#.Text Equivalence] - [#.Symbol Equivalence] - [#.Tag Equivalence]) + [#.Symbol Equivalence] + [#.Tag Equivalence]) (^template [] [[_ ( xs')] [_ ( ys')]] @@ -98,13 +98,13 @@ [#.Int Codec] [#.Rev Codec] [#.Frac Codec] - [#.Symbol Codec]) + [#.Symbol Codec]) [_ (#.Text value)] (text.encode value) - [_ (#.Tag ident)] - (text/compose "#" (:: Codec encode ident)) + [_ (#.Tag name)] + (text/compose "#" (:: Codec encode name)) (^template [ ] [_ ( members)] diff --git a/stdlib/source/lux/macro/poly.lux b/stdlib/source/lux/macro/poly.lux index f234980c6..1dffc77ea 100644 --- a/stdlib/source/lux/macro/poly.lux +++ b/stdlib/source/lux/macro/poly.lux @@ -10,7 +10,7 @@ ["." product] ["." bit] ["." maybe] - [ident ("ident/." Codec)] + [name ("name/." Codec)] ["e" error] ["." number ("nat/." Codec)] ["." text ("text/." Monoid) @@ -290,7 +290,7 @@ (p.fail (ex.construct not-existential headT))))) (def: #export named - (Poly [Ident Type]) + (Poly [Name Type]) (do p.Monad [inputT any] (case inputT @@ -347,7 +347,7 @@ (do p.Monad [current any #let [_ (log! ($_ text/compose - "{" (ident/encode (ident-for ..log)) "} " + "{" (name/encode (name-for ..log)) "} " (%type current)))]] (p.fail "LOGGING"))) diff --git a/stdlib/source/lux/macro/syntax.lux b/stdlib/source/lux/macro/syntax.lux index 5bf0f21b0..1334296da 100644 --- a/stdlib/source/lux/macro/syntax.lux +++ b/stdlib/source/lux/macro/syntax.lux @@ -6,7 +6,7 @@ ["p" parser]] [data ["." bit] - ["." ident] + ["." name] ["." maybe] ["." error (#+ Error)] ["." number] @@ -61,8 +61,8 @@ [ rev Rev #.Rev number.Equivalence "rev"] [ frac Frac #.Frac number.Equivalence "frac"] [ text Text #.Text text.Equivalence "text"] - [symbol Ident #.Symbol ident.Equivalence "symbol"] - [ tag Ident #.Tag ident.Equivalence "tag"] + [symbol Name #.Symbol name.Equivalence "symbol"] + [ tag Name #.Tag name.Equivalence "tag"] ) (def: #export (this? ast) diff --git a/stdlib/source/lux/macro/syntax/common.lux b/stdlib/source/lux/macro/syntax/common.lux index 1ea1624da..dc38d1409 100644 --- a/stdlib/source/lux/macro/syntax/common.lux +++ b/stdlib/source/lux/macro/syntax/common.lux @@ -8,7 +8,7 @@ #declaration-args (List Text)}) (type: #export Annotations - (List [Ident Code])) + (List [Name Code])) (def: #export empty-annotations Annotations diff --git a/stdlib/source/lux/macro/syntax/common/reader.lux b/stdlib/source/lux/macro/syntax/common/reader.lux index 818320a1a..2ec2ee95d 100644 --- a/stdlib/source/lux/macro/syntax/common/reader.lux +++ b/stdlib/source/lux/macro/syntax/common/reader.lux @@ -4,7 +4,7 @@ monad ["p" parser ("parser/." Monad)]] [data - [ident ("ident/." Equivalence)] + [name ("name/." Equivalence)] ["." product] ["." maybe] [collection @@ -49,7 +49,7 @@ s.any))) (def: _definition-anns-tag^ - (Syntax Ident) + (Syntax Name) (s.tuple (p.seq s.text s.text))) (def: (_definition-anns^ _) @@ -88,9 +88,9 @@ ) (def: (find-definition-args meta-data) - (-> (List [Ident Code]) (List Text)) + (-> (List [Name Code]) (List Text)) (<| (maybe.default (list)) - (case (list.find (|>> product.left (ident/= ["lux" "func-args"])) meta-data) + (case (list.find (|>> product.left (name/= ["lux" "func-args"])) meta-data) (^multi (#.Some [_ value]) [(p.run (list value) tuple-meta^) (#.Right [_ args])] diff --git a/stdlib/source/lux/test.lux b/stdlib/source/lux/test.lux index 3c213e29b..75879343c 100644 --- a/stdlib/source/lux/test.lux +++ b/stdlib/source/lux/test.lux @@ -205,7 +205,7 @@ [defs (macro.exports module-name)] (wrap (|> defs (list/map (function (_ [def-name [_ def-anns _]]) - (case (macro.get-text-ann (ident-for #..test) def-anns) + (case (macro.get-text-ann (name-for #..test) def-anns) (#.Some description) [#1 module-name def-name description] diff --git a/stdlib/source/lux/type.lux b/stdlib/source/lux/type.lux index 9d774198d..929967e84 100644 --- a/stdlib/source/lux/type.lux +++ b/stdlib/source/lux/type.lux @@ -6,7 +6,7 @@ ["p" parser]] [data ["." text ("text/." Monoid Equivalence)] - [ident ("ident/." Equivalence Codec)] + [name ("name/." Equivalence Codec)] [number ("nat/." Codec)] ["." maybe] [collection @@ -69,7 +69,7 @@ (= xright yright)) [(#.Named xname xtype) (#.Named yname ytype)] - (and (ident/= xname yname) + (and (name/= xname yname) (= xtype ytype)) (^template [] @@ -251,8 +251,8 @@ (def: #export (un-alias type) (-> Type Type) (case type - (#.Named _ (#.Named ident type')) - (un-alias (#.Named ident type')) + (#.Named _ (#.Named name type')) + (un-alias (#.Named name type')) _ type)) @@ -260,7 +260,7 @@ (def: #export (un-name type) (-> Type Type) (case type - (#.Named ident type') + (#.Named name type') (un-name type') _ @@ -345,7 +345,7 @@ valueT (macro.find-type valueN) #let [_ (log! ($_ text/compose ":log!" " @ " (.cursor-description cursor) "\n" - (ident/encode valueN) " : " (..to-text valueT) "\n"))]] + (name/encode valueN) " : " (..to-text valueT) "\n"))]] (wrap (list (' [])))) (#.Right valueC) diff --git a/stdlib/source/lux/type/abstract.lux b/stdlib/source/lux/type/abstract.lux index 7dd65b106..648435721 100644 --- a/stdlib/source/lux/type/abstract.lux +++ b/stdlib/source/lux/type/abstract.lux @@ -61,7 +61,7 @@ (def: representation-name (-> Text Text) (|>> ($_ text/compose "{" kind "@" module "}") - (let [[module kind] (ident-for #..Representation)]))) + (let [[module kind] (name-for #..Representation)]))) (def: (cast type-vars input-declaration output-declaration) (-> (List Code) Code Code Macro) diff --git a/stdlib/source/lux/type/implicit.lux b/stdlib/source/lux/type/implicit.lux index f8be1a83f..1deb21c60 100644 --- a/stdlib/source/lux/type/implicit.lux +++ b/stdlib/source/lux/type/implicit.lux @@ -39,7 +39,7 @@ )) (def: (resolve-type var-name) - (-> Ident (Meta Type)) + (-> Name (Meta Type)) (do Monad [raw-type (macro.find-type var-name) compiler macro.get-compiler] @@ -75,7 +75,7 @@ (check.fail (format "Cannot find member type " (%n idx) " for " (%type sig-type)))))) (def: (find-member-name member) - (-> Ident (Meta Ident)) + (-> Name (Meta Name)) (case member ["" simple-name] (macro.either (do Monad @@ -91,26 +91,26 @@ tag-lists)]] (case candidates #.Nil - (macro.fail (format "Unknown tag: " (%ident member))) + (macro.fail (format "Unknown tag: " (%name member))) (#.Cons winner #.Nil) (wrap winner) _ - (macro.fail (format "Too many candidate tags: " (%list %ident candidates)))))) + (macro.fail (format "Too many candidate tags: " (%list %name candidates)))))) _ (:: Monad wrap member))) (def: (resolve-member member) - (-> Ident (Meta [Nat Type])) + (-> Name (Meta [Nat Type])) (do Monad [member (find-member-name member) [idx tag-list sig-type] (macro.resolve-tag member)] (wrap [idx sig-type]))) (def: (prepare-definitions this-module-name definitions) - (-> Text (List [Text Definition]) (List [Ident Type])) + (-> Text (List [Text Definition]) (List [Name Type])) (|> definitions (list.filter (function (_ [name [def-type def-anns def-value]]) (macro.struct? def-anns))) @@ -118,7 +118,7 @@ [[this-module-name name] def-type])))) (def: local-env - (Meta (List [Ident Type])) + (Meta (List [Name Type])) (do Monad [local-batches macro.locals #let [total-locals (list/fold (function (_ [name type] table) @@ -131,14 +131,14 @@ (list/map (function (_ [name type]) [["" name] type])))))) (def: local-structs - (Meta (List [Ident Type])) + (Meta (List [Name Type])) (do Monad [this-module-name macro.current-module-name definitions (macro.definitions this-module-name)] (wrap (prepare-definitions this-module-name definitions)))) (def: import-structs - (Meta (List [Ident Type])) + (Meta (List [Name Type])) (do Monad [this-module-name macro.current-module-name imp-mods (macro.imported-modules this-module-name) @@ -193,12 +193,12 @@ (check.check output-type member-type'))) (type: #rec Instance - {#constructor Ident + {#constructor Name #dependencies (List Instance)}) (def: (test-provision provision context dep alts) (-> (-> Lux Type-Context Type (Check Instance)) - Type-Context Type (List [Ident Type]) + Type-Context Type (List [Name Type]) (Meta (List Instance))) (do Monad [compiler macro.get-compiler] @@ -243,11 +243,11 @@ (:: check.Monad wrap winner) _ - (check.fail (format "Too many candidates for provisioning: " (%type dep) " --- " (%list (|>> product.left %ident) candidates)))) + (check.fail (format "Too many candidates for provisioning: " (%type dep) " --- " (%list (|>> product.left %name) candidates)))) )) (def: (test-alternatives sig-type member-idx input-types output-type alts) - (-> Type Nat (List Type) Type (List [Ident Type]) (Meta (List Instance))) + (-> Type Nat (List Type) Type (List [Name Type]) (Meta (List Instance))) (do Monad [compiler macro.get-compiler context macro.type-context] @@ -341,7 +341,7 @@ chosen-ones (find-alternatives sig-type member-idx input-types output-type)] (case chosen-ones #.Nil - (macro.fail (format "No structure option could be found for member: " (%ident member))) + (macro.fail (format "No structure option could be found for member: " (%name member))) (#.Cons chosen #.Nil) (wrap (list (` (:: (~ (instance$ chosen)) @@ -351,7 +351,7 @@ _ (macro.fail (format "Too many options available: " (|> chosen-ones - (list/map (|>> product.left %ident)) + (list/map (|>> product.left %name)) (text.join-with ", ")) " --- for type: " (%type sig-type))))) diff --git a/stdlib/source/lux/type/object/interface.lux b/stdlib/source/lux/type/object/interface.lux index cb92c7253..fb2579d55 100644 --- a/stdlib/source/lux/type/object/interface.lux +++ b/stdlib/source/lux/type/object/interface.lux @@ -6,7 +6,7 @@ [data ["." product] ["." maybe] - [ident ("ident/." Equivalence)] + [name ("name/." Equivalence)] ["." text format] [collection @@ -65,7 +65,7 @@ (p.default default-alias))) (def: (ancestor-inputs ancestors) - (-> (List Ident) (List Code)) + (-> (List Name) (List Code)) (if (list.empty? ancestors) (list) (|> (list.size ancestors) @@ -120,39 +120,39 @@ ## [Inheritance] (type: Reference - [Ident (List Code)]) + [Name (List Code)]) -(def: no-parent Ident ["" ""]) +(def: no-parent Name ["" ""]) (def: (no-parent? parent) - (-> Ident Bit) - (ident/= no-parent parent)) + (-> Name Bit) + (name/= no-parent parent)) (def: (with-interface parent interface) - (-> Ident Ident cs.Annotations cs.Annotations) - (|>> (#.Cons [(ident-for #..interface-name) + (-> Name Name cs.Annotations cs.Annotations) + (|>> (#.Cons [(name-for #..interface-name) (code.tag interface)]) - (#.Cons [(ident-for #..interface-parent) + (#.Cons [(name-for #..interface-parent) (code.tag parent)]))) (def: (with-class interface parent class) - (-> Ident Ident Ident cs.Annotations cs.Annotations) - (|>> (#.Cons [(ident-for #..class-interface) + (-> Name Name Name cs.Annotations cs.Annotations) + (|>> (#.Cons [(name-for #..class-interface) (code.tag interface)]) - (#.Cons [(ident-for #..class-parent) + (#.Cons [(name-for #..class-parent) (code.tag parent)]) - (#.Cons [(ident-for #..class-name) + (#.Cons [(name-for #..class-name) (code.tag class)]))) (do-template [ ] [(def: ( name) - (-> Ident (Meta [Ident (List Ident)])) + (-> Name (Meta [Name (List Name)])) (do Monad [[_ annotations _] (macro.find-def name)] - (case [(macro.get-tag-ann (ident-for ) annotations) - (macro.get-tag-ann (ident-for ) annotations)] + (case [(macro.get-tag-ann (name-for ) annotations) + (macro.get-tag-ann (name-for ) annotations)] [(#.Some real-name) (#.Some parent)] - (if (ident/= no-parent parent) + (if (name/= no-parent parent) (wrap [real-name (list)]) (do @ [[_ ancestors] ( parent)] @@ -238,7 +238,7 @@ (do-template [ ] [(def: ( raw) (-> Text Text) - (let [[module kind] (ident-for )] + (let [[module kind] (name-for )] (format "{" kind "@" module "}" raw)))] [signatureN #..Signature] @@ -247,7 +247,7 @@ ) (def: (getterN export interface g!parameters g!ext g!child ancestors) - (-> Bit Text (List Code) Code Code (List Ident) + (-> Bit Text (List Code) Code Code (List Name) Code) (let [g!get (code.local-symbol (getN interface)) g!interface (code.local-symbol interface) @@ -266,7 +266,7 @@ (~ g!_state)))))) (def: (setterN export interface g!parameters g!ext g!child ancestors) - (-> Bit Text (List Code) Code Code (List Ident) + (-> Bit Text (List Code) Code Code (List Name) Code) (let [g!set (code.local-symbol (setN interface)) g!interface (code.local-symbol interface) @@ -289,7 +289,7 @@ (~ g!build-up)))))) (def: (updaterN export interface g!parameters g!ext g!child ancestors) - (-> Bit Text (List Code) Code Code (List Ident) + (-> Bit Text (List Code) Code Code (List Name) Code) (let [g!update (code.local-symbol (updateN interface)) g!interface (code.local-symbol interface) @@ -367,7 +367,7 @@ (macro.with-gensyms [g!self-class g!child g!ext] (do @ [module macro.current-module-name - [parent ancestors mappings] (: (Meta [Ident (List Ident) (List Code)]) + [parent ancestors mappings] (: (Meta [Name (List Name) (List Code)]) (case ?extends #.None (wrap [no-parent (list) (list)]) @@ -437,7 +437,7 @@ (do @ [module macro.current-module-name [interface _] (interfaceN interface) - [parent ancestors parent-mappings] (: (Meta [Ident (List Ident) (List Code)]) + [parent ancestors parent-mappings] (: (Meta [Name (List Name) (List Code)]) (case super (#.Some [super-class super-mappings]) (do @ diff --git a/stdlib/source/lux/type/resource.lux b/stdlib/source/lux/type/resource.lux index c683a93cb..68d0410dd 100644 --- a/stdlib/source/lux/type/resource.lux +++ b/stdlib/source/lux/type/resource.lux @@ -19,7 +19,8 @@ ["." list ("list/." Functor Fold)]]] [concurrency ["." promise (#+ Promise)]] - ["." macro ["s" syntax (#+ Syntax syntax:)]] + ["." macro + ["s" syntax (#+ Syntax syntax:)]] [type abstract] ["." io (#+ IO)]]) diff --git a/stdlib/source/lux/type/unit.lux b/stdlib/source/lux/type/unit.lux index e7be06eed..230818e30 100644 --- a/stdlib/source/lux/type/unit.lux +++ b/stdlib/source/lux/type/unit.lux @@ -62,7 +62,7 @@ [(def: (-> Text Text) (|>> (format "{" kind "@" module "}") - (let [[module kind] (ident-for )])))] + (let [[module kind] (name-for )])))] [unit-name #..Unit] [scale-name #..Scale] -- cgit v1.2.3