From 64d12f85e861cb8ab4d59c31f0f8d2b71b865852 Mon Sep 17 00:00:00 2001
From: Eduardo Julian
Date: Wed, 15 Jun 2022 00:23:15 -0400
Subject: Re-named "prelude_module" to "prelude".

---
 stdlib/source/documentation/lux.lux                |   6 +-
 stdlib/source/library/lux.lux                      | 166 ++++++++++-----------
 stdlib/source/library/lux/control/try.lux          |   2 +-
 stdlib/source/library/lux/data/collection/list.lux |   2 +-
 stdlib/source/library/lux/data/text/regex.lux      |   2 +-
 stdlib/source/library/lux/documentation.lux        |   6 +-
 stdlib/source/library/lux/macro/pattern.lux        |   2 +-
 stdlib/source/library/lux/meta.lux                 |   4 +-
 stdlib/source/library/lux/meta/location.lux        |   8 +-
 .../library/lux/tool/compiler/default/platform.lux |   2 +-
 .../lux/tool/compiler/language/lux/syntax.lux      |   4 +-
 .../specification/compositor/generation/case.lux   |   4 +-
 stdlib/source/test/lux.lux                         |  14 +-
 stdlib/source/test/lux/meta/symbol.lux             |   2 +-
 14 files changed, 112 insertions(+), 112 deletions(-)

(limited to 'stdlib/source')

diff --git a/stdlib/source/documentation/lux.lux b/stdlib/source/documentation/lux.lux
index ea9ea318f..78e0f8fb8 100644
--- a/stdlib/source/documentation/lux.lux
+++ b/stdlib/source/documentation/lux.lux
@@ -39,9 +39,9 @@
   ["[1][0]" type]
   ["[1][0]" world]])
 
-(documentation: /.prelude_module
+(documentation: /.prelude
   (format "The name of the prelude module"
-          \n "Value: " (%.text /.prelude_module)))
+          \n "Value: " (%.text /.prelude)))
 
 (documentation: /.Any
   (format "The type of things whose type is irrelevant."
@@ -882,7 +882,7 @@
   (.List $.Module)
   ($.module /._
             ""
-            [..prelude_module
+            [..prelude
              ..Any
              ..Nothing
              ..List
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 2eaeec883..e14e1a7e3 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -10,7 +10,7 @@
  ("lux i64 char" +10)
  #0)
 
-("lux def" prelude_module
+("lux def" prelude
  "library/lux"
  #1)
 
@@ -19,7 +19,7 @@
 ("lux def" Any
  ("lux type check type"
   {9 #1
-     [..prelude_module "Any"]
+     [..prelude "Any"]
      {8 #0
         {0 #0}
         {4 #0 1}}})
@@ -30,7 +30,7 @@
 ("lux def" Nothing
  ("lux type check type"
   {9 #1
-     [..prelude_module "Nothing"]
+     [..prelude "Nothing"]
      {7 #0
         {0 #0}
         {4 #0 1}}})
@@ -42,7 +42,7 @@
 ...    {#Item a (List a)}))
 ("lux def type tagged" List
  {9 #1
-    [..prelude_module "List"]
+    [..prelude "List"]
     {7 #0
        {0 #0}
        {1 #0
@@ -60,14 +60,14 @@
 ("lux def" Bit
  ("lux type check type"
   {9 #1
-     [..prelude_module "Bit"]
+     [..prelude "Bit"]
      {0 #0 "#Bit" {#End}}})
  #1)
 
 ("lux def" I64
  ("lux type check type"
   {9 #1
-     [..prelude_module "I64"]
+     [..prelude "I64"]
      {7 #0
         {0 #0}
         {0 #0 "#I64" {#Item {4 #0 1} {#End}}}}})
@@ -76,42 +76,42 @@
 ("lux def" Nat
  ("lux type check type"
   {9 #1
-     [..prelude_module "Nat"]
+     [..prelude "Nat"]
      {0 #0 "#I64" {#Item {0 #0 "#Nat" {#End}} {#End}}}})
  #1)
 
 ("lux def" Int
  ("lux type check type"
   {9 #1
-     [..prelude_module "Int"]
+     [..prelude "Int"]
      {0 #0 "#I64" {#Item {0 #0 "#Int" {#End}} {#End}}}})
  #1)
 
 ("lux def" Rev
  ("lux type check type"
   {9 #1
-     [..prelude_module "Rev"]
+     [..prelude "Rev"]
      {0 #0 "#I64" {#Item {0 #0 "#Rev" {#End}} {#End}}}})
  #1)
 
 ("lux def" Frac
  ("lux type check type"
   {9 #1
-     [..prelude_module "Frac"]
+     [..prelude "Frac"]
      {0 #0 "#Frac" {#End}}})
  #1)
 
 ("lux def" Text
  ("lux type check type"
   {9 #1
-     [..prelude_module "Text"]
+     [..prelude "Text"]
      {0 #0 "#Text" {#End}}})
  #1)
 
 ("lux def" Symbol
  ("lux type check type"
   {9 #1
-     [..prelude_module "Symbol"]
+     [..prelude "Symbol"]
      {2 #0 Text Text}})
  #1)
 
@@ -120,7 +120,7 @@
 ...   {#Some a})
 ("lux def type tagged" Maybe
  {9 #1
-    [..prelude_module "Maybe"]
+    [..prelude "Maybe"]
     {7 #0
        {#End}
        {1 #0
@@ -146,7 +146,7 @@
 ...      {#Apply Type Type}
 ...      {#Named Symbol Type})))
 ("lux def type tagged" Type
- {9 #1 [..prelude_module "Type"]
+ {9 #1 [..prelude "Type"]
     ({Type
       ({Type_List
         ({Type_Pair
@@ -198,7 +198,7 @@
 ...     #line   Nat
 ...     #column Nat]))
 ("lux def type tagged" Location
- {#Named [..prelude_module "Location"]
+ {#Named [..prelude "Location"]
          {#Product Text {#Product Nat Nat}}}
  ["#module" "#line" "#column"]
  #1)
@@ -208,7 +208,7 @@
 ...    [#meta  m
 ...     #datum v]))
 ("lux def type tagged" Ann
- {#Named [..prelude_module "Ann"]
+ {#Named [..prelude "Ann"]
          {#UnivQ {#End}
                  {#UnivQ {#End}
                          {#Product
@@ -230,7 +230,7 @@
 ...    {#Variant (List (w (Code' w)))}
 ...    {#Tuple (List (w (Code' w)))}))
 ("lux def type tagged" Code'
- {#Named [..prelude_module "Code'"]
+ {#Named [..prelude "Code'"]
          ({Code
            ({Code_List
              {#UnivQ {#End}
@@ -276,7 +276,7 @@
 ...   (Ann Location (Code' (Ann Location))))
 ("lux def" Code
  ("lux type check type"
-  {#Named [..prelude_module "Code"]
+  {#Named [..prelude "Code"]
           ({w
             {#Apply {#Apply w Code'} w}}
            ("lux type check type" {#Apply Location Ann}))})
@@ -365,7 +365,7 @@
 ...   [Bit Type Any])
 ("lux def" Definition
  ("lux type check type"
-  {#Named [..prelude_module "Definition"]
+  {#Named [..prelude "Definition"]
           {#Product Bit {#Product Type Any}}})
  .public)
 
@@ -373,7 +373,7 @@
 ...   Symbol)
 ("lux def" Alias
  ("lux type check type"
-  {#Named [..prelude_module "Alias"]
+  {#Named [..prelude "Alias"]
           Symbol})
  .public)
 
@@ -381,7 +381,7 @@
 ...   [Bit Type (List Text) Nat])
 ("lux def" Label
  ("lux type check type"
-  {#Named [..prelude_module "Label"]
+  {#Named [..prelude "Label"]
           {#Product Bit {#Product Type {#Product {#Apply Text List} Nat}}}})
  .public)
 
@@ -393,7 +393,7 @@
 ...    {#Slot Label}
 ...    {#Alias Alias}))
 ("lux def type tagged" Global
- {#Named [..prelude_module "Global"]
+ {#Named [..prelude "Global"]
          {#Sum Definition
                {#Sum ({labels
                        {#Product Bit {#Product Type {#Sum labels labels}}}}
@@ -409,7 +409,7 @@
 ...    [#counter Nat
 ...     #mappings (List [k v])]))
 ("lux def type tagged" Bindings
- {#Named [..prelude_module "Bindings"]
+ {#Named [..prelude "Bindings"]
          {#UnivQ {#End}
                  {#UnivQ {#End}
                          {#Product
@@ -426,7 +426,7 @@
 ...   {#Local Nat}
 ...   {#Captured Nat})
 ("lux def type tagged" Ref
- {#Named [..prelude_module "Ref"]
+ {#Named [..prelude "Ref"]
          {#Sum
           ... Local
           Nat
@@ -443,7 +443,7 @@
 ...     #locals   (Bindings Text [Type Nat])
 ...     #captured (Bindings Text [Type Ref])]))
 ("lux def type tagged" Scope
- {#Named [..prelude_module "Scope"]
+ {#Named [..prelude "Scope"]
          {#Product
           ... name
           {#Apply Text List}
@@ -468,7 +468,7 @@
 ...    {#Left l}
 ...    {#Right r}))
 ("lux def type tagged" Either
- {#Named [..prelude_module "Either"]
+ {#Named [..prelude "Either"]
          {#UnivQ {#End}
                  {#UnivQ {#End}
                          {#Sum
@@ -483,7 +483,7 @@
 ...   [Location Nat Text])
 ("lux def" Source
  ("lux type check type"
-  {#Named [..prelude_module "Source"]
+  {#Named [..prelude "Source"]
           {#Product Location {#Product Nat Text}}})
  .public)
 
@@ -493,7 +493,7 @@
 ...    #Compiled
 ...    #Cached))
 ("lux def type tagged" Module_State
- {#Named [..prelude_module "Module_State"]
+ {#Named [..prelude "Module_State"]
          {#Sum
           ... #Active
           Any
@@ -513,7 +513,7 @@
 ...     #imports            (List Text)
 ...     #module_state       Module_State]))
 ("lux def type tagged" Module
- {#Named [..prelude_module "Module"]
+ {#Named [..prelude "Module"]
          {#Product
           ... module_hash
           Nat
@@ -538,7 +538,7 @@
 ...     #var_counter Nat
 ...     #var_bindings (List [Nat (Maybe Type)])]))
 ("lux def type tagged" Type_Context
- {#Named [..prelude_module "Type_Context"]
+ {#Named [..prelude "Type_Context"]
          {#Product ... ex_counter
           Nat
           {#Product ... var_counter
@@ -554,7 +554,7 @@
 ...   #Eval
 ...   #Interpreter)
 ("lux def type tagged" Mode
- {#Named [..prelude_module "Mode"]
+ {#Named [..prelude "Mode"]
          {#Sum ... Build
           Any
           {#Sum ... Eval
@@ -571,7 +571,7 @@
 ...     #mode          Mode
 ...     #configuration (List [Text Text])]))
 ("lux def type tagged" Info
- {#Named [..prelude_module "Info"]
+ {#Named [..prelude "Info"]
          {#Product
           ... target
           Text
@@ -603,7 +603,7 @@
 ...       #eval            (-> Type Code (-> Lux (Either Text [Lux Any])))
 ...       #host            Any])))
 ("lux def type tagged" Lux
- {#Named [..prelude_module "Lux"]
+ {#Named [..prelude "Lux"]
          ({Lux
            {#Apply {0 #0 ["" {#End}]}
                    {#UnivQ {#End}
@@ -656,7 +656,7 @@
 ...   (-> Lux (Either Text [Lux a])))
 ("lux def" Meta
  ("lux type check type"
-  {#Named [..prelude_module "Meta"]
+  {#Named [..prelude "Meta"]
           {#UnivQ {#End}
                   {#Function Lux
                              {#Apply {#Product Lux {#Parameter 1}}
@@ -667,7 +667,7 @@
 ...   (-> (List Code) (Meta (List Code))))
 ("lux def" Macro'
  ("lux type check type"
-  {#Named [..prelude_module "Macro'"]
+  {#Named [..prelude "Macro'"]
           {#Function Code_List {#Apply Code_List Meta}}})
  .public)
 
@@ -675,7 +675,7 @@
 ...   (Primitive "#Macro"))
 ("lux def" Macro
  ("lux type check type"
-  {#Named [..prelude_module "Macro"]
+  {#Named [..prelude "Macro"]
           {#Primitive "#Macro" {#End}}})
  .public)
 
@@ -764,7 +764,7 @@
                                                   body
 
                                                   _
-                                                  (_ann {#Form {#Item (_ann {#Symbol [..prelude_module "function''"]})
+                                                  (_ann {#Form {#Item (_ann {#Symbol [..prelude "function''"]})
                                                                       {#Item (_ann {#Tuple args'})
                                                                              {#Item body {#End}}}}})}
                                                  args')
@@ -778,7 +778,7 @@
                                                   body
 
                                                   _
-                                                  (_ann {#Form {#Item (_ann {#Symbol [..prelude_module "function''"]})
+                                                  (_ann {#Form {#Item (_ann {#Symbol [..prelude "function''"]})
                                                                       {#Item (_ann {#Tuple args'})
                                                                              {#Item body {#End}}}}})}
                                                  args')
@@ -852,7 +852,7 @@
                                 {#End}})
 
                 _
-                (failure (wrong_syntax_error [..prelude_module "macro"]))}
+                (failure (wrong_syntax_error [..prelude "macro"]))}
                tokens)))
  #1)
 
@@ -868,8 +868,8 @@
             (meta#in tokens)
 
             {#Item x {#Item y xs}}
-            (meta#in {#Item (form$ {#Item (symbol$ [..prelude_module "$'"])
-                                          {#Item (variant$ {#Item (symbol$ [..prelude_module "#Apply"])
+            (meta#in {#Item (form$ {#Item (symbol$ [..prelude "$'"])
+                                          {#Item (variant$ {#Item (symbol$ [..prelude "#Apply"])
                                                                   {#Item y {#Item x {#End}}}})
                                                  xs}})
                             {#End}})
@@ -982,22 +982,22 @@
 
 (def:'' .private |#End|
         Code
-        (variant$ {#Item (symbol$ [..prelude_module "#End"]) {#End}}))
+        (variant$ {#Item (symbol$ [..prelude "#End"]) {#End}}))
 
 (def:'' .private (|#Item| head tail)
         {#Function Code {#Function Code Code}}
-        (variant$ {#Item (symbol$ [..prelude_module "#Item"])
+        (variant$ {#Item (symbol$ [..prelude "#Item"])
                          {#Item head
                                 {#Item tail
                                        {#End}}}}))
 
 (def:'' .private (UnivQ$ body)
         {#Function Code Code}
-        (variant$ {#Item (symbol$ [..prelude_module "#UnivQ"]) {#Item ..|#End| {#Item body {#End}}}}))
+        (variant$ {#Item (symbol$ [..prelude "#UnivQ"]) {#Item ..|#End| {#Item body {#End}}}}))
 
 (def:'' .private (ExQ$ body)
         {#Function Code Code}
-        (variant$ {#Item (symbol$ [..prelude_module "#ExQ"]) {#Item ..|#End| {#Item body {#End}}}}))
+        (variant$ {#Item (symbol$ [..prelude "#ExQ"]) {#Item ..|#End| {#Item body {#End}}}}))
 
 (def:'' .private quantification_level
         Text
@@ -1011,7 +1011,7 @@
 
 (def:'' .private (quantified_type_parameter idx)
         {#Function Nat Code}
-        (variant$ {#Item (symbol$ [..prelude_module "#Parameter"])
+        (variant$ {#Item (symbol$ [..prelude "#Parameter"])
                          {#Item (form$ {#Item (text$ "lux i64 +")
                                               {#Item (local$ ..quantification_level)
                                                      {#Item (nat$ idx)
@@ -1082,7 +1082,7 @@
 
 (def:'' .private (with_correct_quantification body)
         {#Function Code Code}
-        (form$ {#Item (symbol$ [prelude_module "__adjusted_quantified_type__"])
+        (form$ {#Item (symbol$ [prelude "__adjusted_quantified_type__"])
                       {#Item (local$ ..quantification_level)
                              {#Item (nat$ 0)
                                     {#Item body
@@ -1200,7 +1200,7 @@
         (macro (_ tokens)
           ({{#Item output inputs}
             (meta#in {#Item (list#mix ("lux type check" {#Function Code {#Function Code Code}}
-                                       (function'' [i o] (variant$ {#Item (symbol$ [..prelude_module "#Function"]) {#Item i {#Item o {#End}}}})))
+                                       (function'' [i o] (variant$ {#Item (symbol$ [..prelude "#Function"]) {#Item i {#Item o {#End}}}})))
                                       output
                                       inputs)
                             {#End}})
@@ -1229,10 +1229,10 @@
         Macro
         (macro (_ tokens)
           ({{#End}
-            (meta#in (list (symbol$ [..prelude_module "Nothing"])))
+            (meta#in (list (symbol$ [..prelude "Nothing"])))
 
             {#Item last prevs}
-            (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude_module "#Sum"]) left right)))
+            (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude "#Sum"]) left right)))
                                      last
                                      prevs)))}
            (list#reversed tokens))))
@@ -1241,10 +1241,10 @@
         Macro
         (macro (_ tokens)
           ({{#End}
-            (meta#in (list (symbol$ [..prelude_module "Any"])))
+            (meta#in (list (symbol$ [..prelude "Any"])))
 
             {#Item last prevs}
-            (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude_module "#Product"]) left right)))
+            (meta#in (list (list#mix (function'' [left right] (variant$ (list (symbol$ [..prelude "#Product"]) left right)))
                                      last
                                      prevs)))}
            (list#reversed tokens))))
@@ -1287,7 +1287,7 @@
                                         name
                                         (form$ (list (text$ "lux type check")
                                                      type
-                                                     (form$ (list (symbol$ [..prelude_module "function'"])
+                                                     (form$ (list (symbol$ [..prelude "function'"])
                                                                   name
                                                                   (tuple$ args)
                                                                   body))))
@@ -1438,7 +1438,7 @@
 ...    (is (All (_ a b) (-> (-> a (m b)) (m a) (m b)))
 ...        #then)))
 ("lux def type tagged" Monad
- {#Named [..prelude_module "Monad"]
+ {#Named [..prelude "Monad"]
          (All (_ !)
            (Tuple (All (_ a)
                     (-> a ($' ! a)))
@@ -1619,9 +1619,9 @@
 
 (def:''' .private (:List<Code> expression)
          (-> Code Code)
-         (let' [type (variant$ (list (symbol$ [..prelude_module "#Apply"])
-                                     (symbol$ [..prelude_module "Code"])
-                                     (symbol$ [..prelude_module "List"])))]
+         (let' [type (variant$ (list (symbol$ [..prelude "#Apply"])
+                                     (symbol$ [..prelude "Code"])
+                                     (symbol$ [..prelude "List"])))]
                (form$ (list (text$ "lux type check") type expression))))
 
 (def:''' .private (spliced replace? untemplated elems)
@@ -1643,8 +1643,8 @@
                                (function' [leftI rightO]
                                           ({[_ {#Form {#Item [[_ {#Symbol ["" "~+"]}] {#Item [spliced {#End}]}]}}]
                                             (let' [g!in-module (form$ (list (text$ "lux in-module")
-                                                                            (text$ ..prelude_module)
-                                                                            (symbol$ [..prelude_module "list#composite"])))]
+                                                                            (text$ ..prelude)
+                                                                            (symbol$ [..prelude "list#composite"])))]
                                                   (in (form$ (list g!in-module (:List<Code> spliced) rightO))))
 
                                             _
@@ -1662,24 +1662,24 @@
 
 (def:''' .private (untemplated_text value)
          (-> Text Code)
-         (with_location (variant$ (list (symbol$ [..prelude_module "#Text"]) (text$ value)))))
+         (with_location (variant$ (list (symbol$ [..prelude "#Text"]) (text$ value)))))
 
 (def:''' .private (untemplated replace? subst token)
          (-> Bit Text Code ($' Meta Code))
          ({[_ [_ {#Bit value}]]
-           (meta#in (with_location (variant$ (list (symbol$ [..prelude_module "#Bit"]) (bit$ value)))))
+           (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Bit"]) (bit$ value)))))
 
            [_ [_ {#Nat value}]]
-           (meta#in (with_location (variant$ (list (symbol$ [..prelude_module "#Nat"]) (nat$ value)))))
+           (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Nat"]) (nat$ value)))))
 
            [_ [_ {#Int value}]]
-           (meta#in (with_location (variant$ (list (symbol$ [..prelude_module "#Int"]) (int$ value)))))
+           (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Int"]) (int$ value)))))
 
            [_ [_ {#Rev value}]]
-           (meta#in (with_location (variant$ (list (symbol$ [..prelude_module "#Rev"]) (rev$ value)))))
+           (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Rev"]) (rev$ value)))))
            
            [_ [_ {#Frac value}]]
-           (meta#in (with_location (variant$ (list (symbol$ [..prelude_module "#Frac"]) (frac$ value)))))
+           (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Frac"]) (frac$ value)))))
 
            [_ [_ {#Text value}]]
            (meta#in (untemplated_text value))
@@ -1695,20 +1695,20 @@
                           (in [module name])}
                          module)
               .let' [[module name] real_name]]
-             (meta#in (with_location (variant$ (list (symbol$ [..prelude_module "#Symbol"]) (tuple$ (list (text$ module) (text$ name))))))))
+             (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Symbol"]) (tuple$ (list (text$ module) (text$ name))))))))
 
            [#0 [_ {#Symbol [module name]}]]
-           (meta#in (with_location (variant$ (list (symbol$ [..prelude_module "#Symbol"]) (tuple$ (list (text$ module) (text$ name)))))))
+           (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Symbol"]) (tuple$ (list (text$ module) (text$ name)))))))
 
            [#1 [_ {#Form {#Item [[_ {#Symbol ["" "~"]}] {#Item [unquoted {#End}]}]}}]]
            (meta#in (form$ (list (text$ "lux type check")
-                                 (symbol$ [..prelude_module "Code"])
+                                 (symbol$ [..prelude "Code"])
                                  unquoted)))
 
            [#1 [_ {#Form {#Item [[_ {#Symbol ["" "~!"]}] {#Item [dependent {#End}]}]}}]]
            (do meta_monad
              [independent (untemplated replace? subst dependent)]
-             (in (with_location (variant$ (list (symbol$ [..prelude_module "#Form"])
+             (in (with_location (variant$ (list (symbol$ [..prelude "#Form"])
                                                 (untemplated_list (list (untemplated_text "lux in-module")
                                                                         (untemplated_text subst)
                                                                         independent)))))))
@@ -1719,19 +1719,19 @@
            [_ [meta {#Form elems}]]
            (do meta_monad
              [output (spliced replace? (untemplated replace? subst) elems)
-              .let' [[_ output'] (with_location (variant$ (list (symbol$ [..prelude_module "#Form"]) output)))]]
+              .let' [[_ output'] (with_location (variant$ (list (symbol$ [..prelude "#Form"]) output)))]]
              (in [meta output']))
 
            [_ [meta {#Variant elems}]]
            (do meta_monad
              [output (spliced replace? (untemplated replace? subst) elems)
-              .let' [[_ output'] (with_location (variant$ (list (symbol$ [..prelude_module "#Variant"]) output)))]]
+              .let' [[_ output'] (with_location (variant$ (list (symbol$ [..prelude "#Variant"]) output)))]]
              (in [meta output']))
 
            [_ [meta {#Tuple elems}]]
            (do meta_monad
              [output (spliced replace? (untemplated replace? subst) elems)
-              .let' [[_ output'] (with_location (variant$ (list (symbol$ [..prelude_module "#Tuple"]) output)))]]
+              .let' [[_ output'] (with_location (variant$ (list (symbol$ [..prelude "#Tuple"]) output)))]]
              (in [meta output']))}
           [replace? token]))
 
@@ -1739,10 +1739,10 @@
         Macro
         (macro (_ tokens)
           ({{#Item [_ {#Text class_name}] {#End}}
-            (meta#in (list (variant$ (list (symbol$ [..prelude_module "#Primitive"]) (text$ class_name) |#End|))))
+            (meta#in (list (variant$ (list (symbol$ [..prelude "#Primitive"]) (text$ class_name) |#End|))))
 
             {#Item [_ {#Text class_name}] {#Item [_ {#Tuple params}] {#End}}}
-            (meta#in (list (variant$ (list (symbol$ [..prelude_module "#Primitive"]) (text$ class_name) (untemplated_list params)))))
+            (meta#in (list (variant$ (list (symbol$ [..prelude "#Primitive"]) (text$ class_name) (untemplated_list params)))))
 
             _
             (failure "Wrong syntax for Primitive")}
@@ -1770,7 +1770,7 @@
               [current_module current_module_name
                =template (untemplated #1 current_module template)]
               (in (list (form$ (list (text$ "lux type check")
-                                     (symbol$ [..prelude_module "Code"])
+                                     (symbol$ [..prelude "Code"])
                                      =template)))))
 
             _
@@ -1783,7 +1783,7 @@
           ({{#Item template {#End}}
             (do meta_monad
               [=template (untemplated #1 "" template)]
-              (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude_module "Code"]) =template)))))
+              (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude "Code"]) =template)))))
 
             _
             (failure "Wrong syntax for `")}
@@ -1795,7 +1795,7 @@
           ({{#Item template {#End}}
             (do meta_monad
               [=template (untemplated #0 "" template)]
-              (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude_module "Code"]) =template)))))
+              (in (list (form$ (list (text$ "lux type check") (symbol$ [..prelude "Code"]) =template)))))
 
             _
             (failure "Wrong syntax for '")}
@@ -1954,15 +1954,15 @@
                           (list#each (function#composite apply (replacement_environment bindings')))
                           list#conjoint
                           meta#in)
-                      (failure (..wrong_syntax_error [..prelude_module "with_template"]))))
+                      (failure (..wrong_syntax_error [..prelude "with_template"]))))
 
               _
-              (failure (..wrong_syntax_error [..prelude_module "with_template"]))}
+              (failure (..wrong_syntax_error [..prelude "with_template"]))}
              [(monad#each maybe_monad symbol_short bindings)
               (monad#each maybe_monad tuple_list data)])
 
             _
-            (failure (..wrong_syntax_error [..prelude_module "with_template"]))}
+            (failure (..wrong_syntax_error [..prelude "with_template"]))}
            tokens)))
 
 (def:''' .private (n// param subject)
@@ -2347,7 +2347,7 @@
                                     {#Item _level
                                            {#Item body
                                                   {#End}}}}}}]
-           [_0 {#Form {#Item [_1 {#Symbol [..prelude_module "__adjusted_quantified_type__"]}]
+           [_0 {#Form {#Item [_1 {#Symbol [..prelude "__adjusted_quantified_type__"]}]
                              {#Item _permission
                                     {#Item _level
                                            {#Item (normal_type body)
@@ -2635,7 +2635,7 @@
 
 (def:' .private Parser
        Type
-       {#Named [..prelude_module "Parser"]
+       {#Named [..prelude "Parser"]
                (..type (All (_ a)
                          (-> (List Code) (Maybe [(List Code) a]))))})
 
@@ -2939,7 +2939,7 @@
             (meta#in (list (` [(~ (text$ module)) (~ (text$ name))])))
             
             _
-            (failure (..wrong_syntax_error [..prelude_module "symbol"])))))
+            (failure (..wrong_syntax_error [..prelude "symbol"])))))
 
 (def: (list#one f xs)
   (All (_ a b)
diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux
index 3b5da2546..6d0467043 100644
--- a/stdlib/source/library/lux/control/try.lux
+++ b/stdlib/source/library/lux/control/try.lux
@@ -135,7 +135,7 @@
     {#Success value}
 
     {.#None}
-    {#Failure (`` (("lux in-module" (~~ (static .prelude_module)) .symbol#encoded)
+    {#Failure (`` (("lux in-module" (~~ (static .prelude)) .symbol#encoded)
                    (symbol ..of_maybe)))}))
 
 (def: .public else
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index d3afe902c..dec3d00c1 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -77,7 +77,7 @@
 
 (def: wrong_syntax_error
   (template (_ <it>)
-    [((`` ("lux in-module" (~~ (static .prelude_module)) .wrong_syntax_error))
+    [((`` ("lux in-module" (~~ (static .prelude)) .wrong_syntax_error))
       (symbol <it>))]))
 
 (def: .public partial
diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux
index 5a85c94af..34ce70739 100644
--- a/stdlib/source/library/lux/data/text/regex.lux
+++ b/stdlib/source/library/lux/data/text/regex.lux
@@ -75,7 +75,7 @@
   (all <>.either
        (<>.and (<>#in current_module) (<>.after (<text>.this "..") symbol_part^))
        (<>.and symbol_part^ (<>.after (<text>.this ".") symbol_part^))
-       (<>.and (<>#in .prelude_module) (<>.after (<text>.this ".") symbol_part^))
+       (<>.and (<>#in .prelude) (<>.after (<text>.this ".") symbol_part^))
        (<>.and (<>#in "") symbol_part^)))
 
 (def: (re_var^ current_module)
diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux
index 35fbeff10..9b1e70af6 100644
--- a/stdlib/source/library/lux/documentation.lux
+++ b/stdlib/source/library/lux/documentation.lux
@@ -93,7 +93,7 @@
     (let [documentation (cond (text#= expected_module module)
                               short
 
-                              (text#= .prelude_module module)
+                              (text#= .prelude module)
                               (format "." short)
                               
                               ... else
@@ -291,7 +291,7 @@
     (cond (text#= module _module)
           _name
 
-          (text#= .prelude_module _module)
+          (text#= .prelude _module)
           (format "." _name)
 
           ... else
@@ -429,7 +429,7 @@
       (cond (text#= module _module)
             _name
 
-            (text#= .prelude_module _module)
+            (text#= .prelude _module)
             (format "." _name)
 
             ... else
diff --git a/stdlib/source/library/lux/macro/pattern.lux b/stdlib/source/library/lux/macro/pattern.lux
index 7d40b8905..e6ae605a2 100644
--- a/stdlib/source/library/lux/macro/pattern.lux
+++ b/stdlib/source/library/lux/macro/pattern.lux
@@ -3,7 +3,7 @@
   [lux (.except or let with_template |> `)]])
 
 (def: partial_list
-  (`` ("lux in-module" (~~ (static .prelude_module)) .partial_list)))
+  (`` ("lux in-module" (~~ (static .prelude)) .partial_list)))
 
 (def: locally
   (macro (_ tokens lux)
diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux
index 5b38ef955..a4a6d6ec3 100644
--- a/stdlib/source/library/lux/meta.lux
+++ b/stdlib/source/library/lux/meta.lux
@@ -145,7 +145,7 @@
 (def: (macro_type? type)
   (-> Type Bit)
   (`` (case type
-        {.#Named [(~~ (static .prelude_module)) "Macro"] {.#Primitive "#Macro" {.#End}}}
+        {.#Named [(~~ (static .prelude)) "Macro"] {.#Primitive "#Macro" {.#End}}}
         true
 
         _
@@ -435,7 +435,7 @@
       (type_definition de_aliased)
       
       {.#Definition [exported? def_type def_value]}
-      (let [type_code (`` ("lux in-module" (~~ (static .prelude_module)) .type_code))]
+      (let [type_code (`` ("lux in-module" (~~ (static .prelude)) .type_code))]
         (if (or (same? .Type def_type)
                 (at code.equivalence =
                     (type_code .Type)
diff --git a/stdlib/source/library/lux/meta/location.lux b/stdlib/source/library/lux/meta/location.lux
index cdad2fa11..c71dcd094 100644
--- a/stdlib/source/library/lux/meta/location.lux
+++ b/stdlib/source/library/lux/meta/location.lux
@@ -30,7 +30,7 @@
                                  .#column (~ [..dummy {.#Nat (the .#column location)}])])))]})
 
       _
-      {.#Left (`` (("lux in-module" (~~ (static .prelude_module)) wrong_syntax_error) (symbol ..here)))})))
+      {.#Left (`` (("lux in-module" (~~ (static .prelude)) wrong_syntax_error) (symbol ..here)))})))
 
 (def: .public (format it)
   (-> Location Text)
@@ -38,9 +38,9 @@
         [file line column] it]
     (all "lux text concat"
          "@"
-         (`` (("lux in-module" (~~ (static .prelude_module)) .text#encoded) file)) separator
-         (`` (("lux in-module" (~~ (static .prelude_module)) .nat#encoded) line)) separator
-         (`` (("lux in-module" (~~ (static .prelude_module)) .nat#encoded) column)))))
+         (`` (("lux in-module" (~~ (static .prelude)) .text#encoded) file)) separator
+         (`` (("lux in-module" (~~ (static .prelude)) .nat#encoded) line)) separator
+         (`` (("lux in-module" (~~ (static .prelude)) .nat#encoded) column)))))
 
 (def: \n
   ("lux i64 char" +10))
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index 4d259bf18..1bea3c4e9 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -637,7 +637,7 @@
         (let [[all_dependencies duplicates _] (is [(Set descriptor.Module) (Set descriptor.Module) Bit]
                                                   (list#mix (function (_ new [all duplicates seen_prelude?])
                                                               (if (set.member? all new)
-                                                                (if (text#= .prelude_module new)
+                                                                (if (text#= .prelude new)
                                                                   (if seen_prelude?
                                                                     [all (set.has new duplicates) seen_prelude?]
                                                                     [all duplicates true])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
index 908e3898b..3dcd579c9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
@@ -26,7 +26,7 @@
 ... location, which is helpful for documentation and debugging.
 (.using
  [library
-  [lux (.except)
+  [lux (.except prelude)
    ["@" target]
    [abstract
     [monad (.only do)]]
@@ -123,7 +123,7 @@
   (dictionary.empty text.hash))
 
 (def: .public prelude
-  .prelude_module)
+  .prelude)
 
 (def: .public text_delimiter text.double_quote)
 
diff --git a/stdlib/source/specification/compositor/generation/case.lux b/stdlib/source/specification/compositor/generation/case.lux
index d91b8d861..c76cd5037 100644
--- a/stdlib/source/specification/compositor/generation/case.lux
+++ b/stdlib/source/specification/compositor/generation/case.lux
@@ -141,7 +141,7 @@
 (def: special_input
   Synthesis
   (let [_cursor_ (is Synthesis
-                     (synthesis.tuple (list (synthesis.text .prelude_module)
+                     (synthesis.tuple (list (synthesis.text .prelude)
                                             (synthesis.i64 +901)
                                             (synthesis.i64 +13))))
         _code_ (is (-> Synthesis Synthesis)
@@ -175,7 +175,7 @@
       (|> _end_
           (_item_ (__apply__ (__symbol__ ["" "form$"])
                              (__list__ (list (__apply__ (__symbol__ ["" "tag$"])
-                                                        (__tuple__ (list (__text__ .prelude_module)
+                                                        (__tuple__ (list (__text__ .prelude)
                                                                          (__text__ "Item"))))
                                              (__symbol__ ["" "export?-meta"])
                                              (__symbol__ ["" "tail"])))))
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index a43e6a889..37d57a3ac 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -225,8 +225,8 @@
   Test
   (all _.and
        (let [[module short] (/.symbol .example)]
-         (_.coverage [/.symbol /.prelude_module]
-           (and (text#= /.prelude_module module)
+         (_.coverage [/.symbol /.prelude]
+           (and (text#= /.prelude module)
                 (text#= short "example"))))
        (let [[module short] (/.symbol ..example)]
          (_.coverage [/.module_separator]
@@ -275,7 +275,7 @@
            (code#= (code.text "5") (/.' "5"))
            (code#= (code.symbol ["" "example_symbol"])
                    (/.' example_symbol))
-           (code#= (code.symbol [/.prelude_module "example_symbol"])
+           (code#= (code.symbol [/.prelude "example_symbol"])
                    (/.' .example_symbol))
            (code#= (code.symbol [..current_module "example_symbol"])
                    (/.' ..example_symbol))
@@ -305,7 +305,7 @@
            (code#= (code.text "5") (/.` "5"))
            (code#= (code.symbol [..current_module "example_symbol"])
                    (/.` example_symbol))
-           (code#= (code.symbol [/.prelude_module "example_symbol"])
+           (code#= (code.symbol [/.prelude "example_symbol"])
                    (/.` .example_symbol))
            (code#= (code.symbol [..current_module "example_symbol"])
                    (/.` ..example_symbol))
@@ -334,7 +334,7 @@
            (code#= (code.text "5") (/.`' "5"))
            (code#= (code.symbol ["" "example_symbol"])
                    (/.`' example_symbol))
-           (code#= (code.symbol [/.prelude_module "example_symbol"])
+           (code#= (code.symbol [/.prelude "example_symbol"])
                    (/.`' .example_symbol))
            (code#= (code.symbol [..current_module "example_symbol"])
                    (/.`' ..example_symbol))
@@ -1068,8 +1068,8 @@
 (def: for_meta|Module_State
   (syntax (_ [])
     (do meta.monad
-      [prelude_module (meta.module .prelude_module)]
-      (in (list (code.bit (case (the .#module_state prelude_module)
+      [prelude (meta.module .prelude)]
+      (in (list (code.bit (case (the .#module_state prelude)
                             {.#Active} false
                             _ true)))))))
 
diff --git a/stdlib/source/test/lux/meta/symbol.lux b/stdlib/source/test/lux/meta/symbol.lux
index e37dc06a9..76bbb76c6 100644
--- a/stdlib/source/test/lux/meta/symbol.lux
+++ b/stdlib/source/test/lux/meta/symbol.lux
@@ -66,7 +66,7 @@
                            (let [(open "/#[0]") /.equivalence]
                              (all _.and
                                   (_.property "Can obtain Symbol from a symbol."
-                                    (and (/#= [.prelude_module "yolo"] (.symbol .yolo))
+                                    (and (/#= [.prelude "yolo"] (.symbol .yolo))
                                          (/#= ["test/lux/meta/symbol" "yolo"] (.symbol ..yolo))
                                          (/#= ["" "yolo"] (.symbol yolo))
                                          (/#= ["library/lux/test" "yolo"] (.symbol library/lux/test.yolo)))))))
-- 
cgit v1.2.3