Replies: 3 comments 6 replies
-
Hi, just a word to say that I'm traveling for a little while still, and I don't have time to give you're posts the time they deserve. I very much appreciate all the ideas that you're coming up with. I'll get back to you in a week or two. |
Beta Was this translation helpful? Give feedback.
-
I realized that we can go a step further in (2 'resolving the {-# LANGUAGE LinearTypes #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
module Unique (
-- | = Class and combinator functions to work with unique values
Unique,
scoped,
consuming,
-- | = UniqueUnit: the zero-info unique witness type
UniqueUnit,
unit,
) where
import Prelude.Linear
-- | Implemented by types which can used only inside a scoped unique context.
--
-- Instances of this class can be used as 'uniqueness witnesses' to create more unique values.
--
-- = Invariants:
--
-- - A type can either implement @Unique@ or @Movable@ but never both.
-- - A `Unique` has no (safe) normal public constructor. Instead, they are created by type-specific 'unique constructor' functions.
--
class Unique u where
-- | Combinator which allows you to use a unique constructor function to kickstart a unique scope.
--
scoped :: (Unique u, Movable r) =>
(forall witness. Unique witness => witness %1 -> (u, witness)) -- ^ constructor function which when given a uniqueness witness creates a new unique value
%1 -> (u %1 -> r) -- ^ Scoped callback function
%1 -> r -- ^ Final, non-unique result.
scoped constructor callback =
UniqueUnit
& consuming constructor
& callback
-- | Combinator which turns a normal unique constructor function into a consuming constructor function:
-- Given a `b` that you no longer need, consume it after using it as a uniqueness witness to create `a`.
consuming :: (Unique u, Unique witness, Consumable witness) => (witness %1 -> (u, witness)) %1 -> witness %1 -> u
consuming f = (\(a, b) -> b `lseq` a) . f
-- | The zero-info unique unit type
-- This type is similar to @()@ except that the only way to obtain one is inside a scoped unique context.
--
-- (Similar to the `Source` token in https://github.com/tweag/linear-base/issues/130 but more ergonomic to use)
data UniqueUnit = UniqueUnit
instance Unique UniqueUnit where
instance Consumable UniqueUnit where
consume UniqueUnit = ()
instance Dupable UniqueUnit where
dup2 UniqueUnit = (UniqueUnit, UniqueUnit)
-- | Unique constructor for `UniqueUnit`.
unit :: Unique witness => witness %1 -> (UniqueUnit, witness)
unit x = (UniqueUnit, x) The core idea behind this concept is the structure of 'unique constructor' functions. A normal constructors has the type As the observant reader might already have realized: module Array (...) where
fromList :: (Unique witness) => [a] %1 -> witness %1 -> (Array a, witness)
alloc :: (Unique witness) => Int %1 -> a -> witness %1 -> (Array a, witness) The neat thing now is that we can recover the other variants of the functions: fromListScoped :: Movable r => [a] -> (Array a %1 -> r) %1 -> r
fromListScoped list = Unique.scoped (Array.fromList list)
fromListConsuming :: (Unique witness, Consumable witness) => [a] -> witness %1 -> Array a
fromListConsuming list = Unique.consuming (Array.fromList list)
allocScoped :: Movable r => Int -> a -> (Array a %1 -> r) %1 -> r
allocScoped size elem = Unique.scoped (Array.alloc size elem)
allocConsuming :: (Unique witness, Consumable witness) => Int -> a -> witness %1 -> Array a
allocConsuming = Unique.consuming (Array.alloc size elem)
-- essentially 'withSource' from https://github.com/tweag/linear-base/issues/130
unitScoped :: Movable r => (UniqueUnit %1 -> r) %1 -> r
unitScoped = Unique.scoped Unique.unit
unitConsuming :: (Unique witness, Consumable witness) => witness %1 -> UniqueUnit
unitConsuming = Unique.consuming Unique.unit And thus for any new mutable collection we only need to provide:
and you get all the other variants and combinations for free! Here is an example of what you can do with these building blocks today: -- based on the example motivating newMArrayBeside from https://www.tweag.io/blog/2023-03-23-linear-constraints-linearly/
blogExample :: [Int] -> (Int, [Int])
blogExample list =
Unique.scoped (Array.fromList list) $ \arr ->
Array.alloc 2 0 arr & \(prefix, arr) ->
Array.get 0 arr & \(a0, arr) ->
Array.get 1 arr & \(a1, arr) ->
( prefix & Array.set 0 a0 & Array.set 1 a1 & Array.consumingSum, Array.toList arr) I'll be working a little bit on a small proof-of-concept to further flesh out this idea. |
Beta Was this translation helpful? Give feedback.
-
Regarding (1), I like the idea of replacing Or maybe a more practical way of asking the question is: how do I eliminate an |
Beta Was this translation helpful? Give feedback.
-
I've been thinking about https://www.tweag.io/blog/2023-03-23-linear-constraints-linearly/ and the related #130 these last few days.
I think that having a
Linearly
typeclass is a very cool idea. However, for obvious reasons it will probably take quite a while before it might be introduced into GHC and can be used in practical code. So I was thinking about alternative approaches which might be 'good enough' today.1. Removing
Ur
fromalloc
Today in linear-base, the following is the main API entrypoint to work with mutable arrays:
(And similar functions exist to work with mutable vectors, mutable sets, mutable hashmaps, etc.)
It is mentioned in the article that the
Ur
is absolutely necessary here.But I'm not so sure: The main point as far as I can see is to make sure that the
MArray
is not allowed to remain after the callback returns. Another way would be:Where
Immutable
is an (empty) typeclass which is implemented for most types but explicitly not for 'in-place mutation' types.Indeed, a blanket instance
Movable a => Immutable a
could be introduced which essentially recovers the original API but without having to wrap/unwrapUr
.And there might be other types (ex: resource handles which we use linearly to make sure they are cleaned up early and exactly once) that might implement
Immutable
but are intentionally notMovable
.2. Resolving the 'nˆ2
beside
implementations' problemIn the article it is mentioned that because scopes introduced with
alloc
are 'sticky'. As solution, the following function is shown:But the problem which is immediately raised, is that if you want to mix and match different kinds of mutable collections, you'd need n^2 functions of this shape (one for each combination).
But what about introducing a typeclass?
The implementation for arrays could look like:
This way the n^2 problem is averted.
I am still quite new to Linear Haskell so there's a reasonable chance there's a fundamental issue with this approach which I missed, but at least at first glance it seems promising 😅
What do you think?
Beta Was this translation helpful? Give feedback.
All reactions