aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/type
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/type')
-rw-r--r--stdlib/source/library/lux/type/check.lux10
-rw-r--r--stdlib/source/library/lux/type/dynamic.lux4
-rw-r--r--stdlib/source/library/lux/type/implicit.lux2
-rw-r--r--stdlib/source/library/lux/type/primitive.lux6
-rw-r--r--stdlib/source/library/lux/type/quotient.lux2
-rw-r--r--stdlib/source/library/lux/type/refinement.lux6
-rw-r--r--stdlib/source/library/lux/type/resource.lux8
-rw-r--r--stdlib/source/library/lux/type/unit.lux4
-rw-r--r--stdlib/source/library/lux/type/unit/scale.lux6
-rw-r--r--stdlib/source/library/lux/type/variance.lux12
10 files changed, 30 insertions, 30 deletions
diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux
index 0c91e0c24..09e496cec 100644
--- a/stdlib/source/library/lux/type/check.lux
+++ b/stdlib/source/library/lux/type/check.lux
@@ -59,19 +59,19 @@
"Expected" (//.format expected)
"Actual" (//.format actual)))
-(type: .public Var
+(type .public Var
Nat)
-(type: Assumption
+(type Assumption
[Type Type])
-(type: .public (Check a)
+(type .public (Check a)
(-> Type_Context (Try [Type_Context a])))
-(type: (Checker a)
+(type (Checker a)
(-> (List Assumption) a a (Check (List Assumption))))
-(type: Type_Vars
+(type Type_Vars
(List [Var (Maybe Type)]))
(def .public functor
diff --git a/stdlib/source/library/lux/type/dynamic.lux b/stdlib/source/library/lux/type/dynamic.lux
index 9c41cffff..0ae433481 100644
--- a/stdlib/source/library/lux/type/dynamic.lux
+++ b/stdlib/source/library/lux/type/dynamic.lux
@@ -45,9 +45,9 @@
(in (list (` (.let [[(~ g!type) (~ g!value)] ((~! ..representation) (~ value))]
(.is ((~! try.Try) (~ type))
(.if (.at (~! type.equivalence) (~' =)
- (.type (~ type)) (~ g!type))
+ (.type_literal (~ type)) (~ g!type))
{try.#Success (.as (~ type) (~ g!value))}
- ((~! exception.except) ..wrong_type [(.type (~ type)) (~ g!type)]))))))))))
+ ((~! exception.except) ..wrong_type [(.type_literal (~ type)) (~ g!type)]))))))))))
(def .public (format value)
(-> Dynamic (Try Text))
diff --git a/stdlib/source/library/lux/type/implicit.lux b/stdlib/source/library/lux/type/implicit.lux
index 733760bf5..3b330f2c1 100644
--- a/stdlib/source/library/lux/type/implicit.lux
+++ b/stdlib/source/library/lux/type/implicit.lux
@@ -219,7 +219,7 @@
[actual_output (monad.mix check.monad ..on_argument member_type input_types)]
(check.check expected_output actual_output)))
-(type: Instance
+(type Instance
(Rec Instance
(Record
[#constructor Symbol
diff --git a/stdlib/source/library/lux/type/primitive.lux b/stdlib/source/library/lux/type/primitive.lux
index 0bddb9c84..4ab0e4e3d 100644
--- a/stdlib/source/library/lux/type/primitive.lux
+++ b/stdlib/source/library/lux/type/primitive.lux
@@ -22,7 +22,7 @@
["[0]" symbol (.use "[1]#[0]" codec)]]]]
["[0]" //])
-(type: .public Frame
+(type .public Frame
(Record
[#name Text
#type_vars (List Code)
@@ -87,10 +87,10 @@
abstraction_declaration (` ((~ (code.local name)) (~+ type_varsC)))
representation_declaration (` ((~ g!Representation) (~+ type_varsC)))]]
(..declaration [name type_varsC abstraction_declaration representation_declaration]
- (` (.these (type: (~ export_policy) (~ abstraction_declaration)
+ (` (.these (type (~ export_policy) (~ abstraction_declaration)
(Primitive (~ (code.text (symbol#encoded [current_module name])))
[(~+ type_varsC)]))
- (type: (~ representation_declaration)
+ (type (~ representation_declaration)
(~ representation_type))
(~+ primitives)))))))
diff --git a/stdlib/source/library/lux/type/quotient.lux b/stdlib/source/library/lux/type/quotient.lux
index bec09aeeb..8e96bfd3b 100644
--- a/stdlib/source/library/lux/type/quotient.lux
+++ b/stdlib/source/library/lux/type/quotient.lux
@@ -53,7 +53,7 @@
]
(.case (.type_of (~ class))
{.#Apply (~ g!%) {.#Apply (~ g!c) {.#Apply (~ g!t) (~ g!:quotient:)}}}
- (.type (..Quotient (~ g!t) (~ g!c) (~ g!%)))
+ (.type_literal (..Quotient (~ g!t) (~ g!c) (~ g!%)))
(~ g!_)
(.undefined))))
diff --git a/stdlib/source/library/lux/type/refinement.lux b/stdlib/source/library/lux/type/refinement.lux
index 4292f771c..a4054407c 100644
--- a/stdlib/source/library/lux/type/refinement.lux
+++ b/stdlib/source/library/lux/type/refinement.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except type only)
+ [lux (.except only type)
[abstract
[predicate (.only Predicate)]]
[control
@@ -16,7 +16,7 @@
[#value t
#predicate (Predicate t)])
- (type: .public (Refiner t %)
+ (.type .public (Refiner t %)
(-> t (Maybe (Refined t %))))
(def .public (refiner predicate)
@@ -94,7 +94,7 @@
]
(.case (.type_of (~ refiner))
{.#Apply (~ g!%) {.#Apply (~ g!t) (~ g!:refiner:)}}
- (.type (..Refined (~ g!t) (~ g!%)))
+ (.type_literal (..Refined (~ g!t) (~ g!%)))
(~ g!_)
(.undefined))))
diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux
index dd1421e6a..0cc8df8bc 100644
--- a/stdlib/source/library/lux/type/resource.lux
+++ b/stdlib/source/library/lux/type/resource.lux
@@ -25,18 +25,18 @@
[type
[primitive (.except)]]]])
-(type: .public (Procedure monad input output value)
+(type .public (Procedure monad input output value)
(-> input (monad [output value])))
-(type: .public (Linear monad value)
+(type .public (Linear monad value)
(All (_ keys)
(Procedure monad keys keys value)))
-(type: .public (Affine monad permissions value)
+(type .public (Affine monad permissions value)
(All (_ keys)
(Procedure monad keys [permissions keys] value)))
-(type: .public (Relevant monad permissions value)
+(type .public (Relevant monad permissions value)
(All (_ keys)
(Procedure monad [permissions keys] keys value)))
diff --git a/stdlib/source/library/lux/type/unit.lux b/stdlib/source/library/lux/type/unit.lux
index 1b63245bf..bcc8f672c 100644
--- a/stdlib/source/library/lux/type/unit.lux
+++ b/stdlib/source/library/lux/type/unit.lux
@@ -68,7 +68,7 @@
[/ i./ p [p s] s]
)
- (type: .public (Unit a)
+ (.type .public (Unit a)
(Interface
(is (-> Int (Qty Any a))
in)
@@ -94,7 +94,7 @@
[(def .public <unit>
(..unit []))
- (type: .public <type>
+ (.type .public <type>
(~ (..type <unit>)))]
[gram Gram]
diff --git a/stdlib/source/library/lux/type/unit/scale.lux b/stdlib/source/library/lux/type/unit/scale.lux
index c4aa8cbba..9eacbb81b 100644
--- a/stdlib/source/library/lux/type/unit/scale.lux
+++ b/stdlib/source/library/lux/type/unit/scale.lux
@@ -13,7 +13,7 @@
["[0]" // (.only)
["/[1]" //]])
-(type: .public (Scale s)
+(.type .public (Scale s)
(Interface
(is (All (_ u) (-> (//.Qty Any u) (//.Qty s u)))
up)
@@ -62,14 +62,14 @@
(scale [ratio.#numerator <order_of_magnitude>
ratio.#denominator 1]))
- (type: .public <up_type>
+ (.type .public <up_type>
(~ (..type <up>)))
(def .public <down>
(scale [ratio.#numerator 1
ratio.#denominator <order_of_magnitude>]))
- (type: .public <down_type>
+ (.type .public <down_type>
(~ (..type <down>)))]
[ 1,000 kilo Kilo milli Milli]
diff --git a/stdlib/source/library/lux/type/variance.lux b/stdlib/source/library/lux/type/variance.lux
index 68c9b4af3..ac7e120d4 100644
--- a/stdlib/source/library/lux/type/variance.lux
+++ b/stdlib/source/library/lux/type/variance.lux
@@ -4,16 +4,16 @@
[meta
["[0]" symbol]]]])
-(type: .public (Co it)
+(type .public (Co it)
(-> Any it))
-(type: .public (Contra it)
+(type .public (Contra it)
(-> it Any))
-(type: .public (In it)
+(type .public (In it)
(-> it it))
-(type: .public (Mutable r w)
+(type .public (Mutable r w)
(Primitive "#Mutable" [(-> w r)]))
(with_template [<name> <type>]
@@ -27,10 +27,10 @@
[write (.-> w (..Mutable r w))]
)
-(type: .public (Read_Only a)
+(type .public (Read_Only a)
(Mutable a Nothing))
-(type: .public (Write_Only a)
+(type .public (Write_Only a)
(Mutable Any a))
(with_template [<name> <type>]