Skip to content

Commit 6cff5df

Browse files
committed
Remove the ... & \case -> ... workaround
Since #442 we require GHC >= 9.2. We can drop the workaround, which was needed for 9.0 only. Tested by building with 9.2 and 9.6.
1 parent 3e80229 commit 6cff5df

File tree

25 files changed

+162
-196
lines changed

25 files changed

+162
-196
lines changed

bench/Data/Mutable/HashMap.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ linear_hashmap inp@(BenchInput {pairs = kvs}) =
135135

136136
look :: LMap.HashMap Key Int %1 -> Key -> LMap.HashMap Key Int
137137
look hmap k =
138-
LMap.lookup k hmap Linear.& \case
138+
case LMap.lookup k hmap of
139139
(Linear.Ur Nothing, hmap0) -> hmap0
140140
(Linear.Ur (Just v), hmap0) -> Linear.seq (force v) hmap0
141141

docs/USER_GUIDE.md

-33
Original file line numberDiff line numberDiff line change
@@ -107,39 +107,6 @@ lifetime (i.e, the scope) of `SomeType`.
107107

108108
## Temporary limitations
109109

110-
### Case statements are not linear
111-
112-
The following definition will **fail** to type check:
113-
114-
```haskell
115-
maybeFlip :: Int %1-> Int %1-> (a,a) -> a
116-
maybeFlip i j (x,y) = case i < j of
117-
True -> x
118-
False -> y
119-
```
120-
121-
The scrutinee on (i.e., `x` in `case x of ...`) is considered to be
122-
consumed many times. It's a limitation of the current implementation
123-
of the type checker.
124-
125-
For now, we can mimic a linear case statement using the
126-
`-XLambdaCase` language extension and the `(&)` from `Prelude.Linear`:
127-
128-
```haskell
129-
{-# LANGUAGE LambdaCase #-}
130-
import Prelude.Linear ((&))
131-
132-
maybeFlip :: Int %1-> Int %1-> (a,a) -> a
133-
maybeFlip i j (x,y) = i < j & \case
134-
True -> x
135-
False -> y
136-
```
137-
138-
The `(&)` operator is like `($)` with the argument order flipped.
139-
140-
This workaround will no longer be needed in GHC 9.2, where this limitation
141-
has been lifted and `case` can be used in a linear context.
142-
143110
### `let` and `where` bindings are not linear
144111

145112
The following will **fail** to type check:

examples/Simple/TopSort.hs

+8-9
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,6 @@ import Data.HashMap.Mutable.Linear (HashMap)
1313
import qualified Data.HashMap.Mutable.Linear as HMap
1414
import Data.Maybe.Linear (catMaybes)
1515
import Data.Unrestricted.Linear
16-
import Prelude.Linear ((&))
1716
import qualified Prelude.Linear as Linear
1817

1918
-- # The topological sort of a DAG
@@ -36,7 +35,7 @@ topsort = reverse . postOrder . fmap (\(n, nbrs) -> (n, (nbrs, 0)))
3635

3736
postOrderHM :: [Node] -> InDegGraph %1 -> Ur [Node]
3837
postOrderHM nodes dag =
39-
findSources nodes (computeInDeg nodes dag) & \case
38+
case findSources nodes (computeInDeg nodes dag) of
4039
(dag, Ur sources) -> pluckSources sources [] dag
4140
where
4241
-- O(V + N)
@@ -46,7 +45,7 @@ postOrderHM nodes dag =
4645
-- Increment in-degree of all neighbors
4746
incChildren :: InDegGraph %1 -> Ur Node %1 -> InDegGraph
4847
incChildren dag (Ur node) =
49-
HMap.lookup node dag & \case
48+
case HMap.lookup node dag of
5049
(Ur Nothing, dag) -> dag
5150
(Ur (Just (xs, i)), dag) -> incNodes (move xs) dag
5251
where
@@ -55,7 +54,7 @@ postOrderHM nodes dag =
5554

5655
incNode :: InDegGraph %1 -> Ur Node %1 -> InDegGraph
5756
incNode dag (Ur node) =
58-
HMap.lookup node dag & \case
57+
case HMap.lookup node dag of
5958
(Ur Nothing, dag') -> dag'
6059
(Ur (Just (n, d)), dag') ->
6160
HMap.insert node (n, d + 1) dag'
@@ -66,10 +65,10 @@ postOrderHM nodes dag =
6665
pluckSources :: [Node] -> [Node] -> InDegGraph %1 -> Ur [Node]
6766
pluckSources [] postOrd dag = lseq dag (move postOrd)
6867
pluckSources (s : ss) postOrd dag =
69-
HMap.lookup s dag & \case
68+
case HMap.lookup s dag of
7069
(Ur Nothing, dag) -> pluckSources ss (s : postOrd) dag
7170
(Ur (Just (xs, i)), dag) ->
72-
walk xs dag & \case
71+
case walk xs dag of
7372
(dag', Ur newSrcs) ->
7473
pluckSources (newSrcs ++ ss) (s : postOrd) dag'
7574
where
@@ -81,7 +80,7 @@ pluckSources (s : ss) postOrd dag =
8180
-- Decrement the degree of a node, save it if it is now a source
8281
decDegree :: Node -> InDegGraph %1 -> (InDegGraph, Ur (Maybe Node))
8382
decDegree node dag =
84-
HMap.lookup node dag & \case
83+
case HMap.lookup node dag of
8584
(Ur Nothing, dag') -> (dag', Ur Nothing)
8685
(Ur (Just (n, d)), dag') ->
8786
checkSource node (HMap.insert node (n, d - 1) dag')
@@ -94,7 +93,7 @@ findSources nodes dag =
9493
-- | Check if a node is a source, and if so return it
9594
checkSource :: Node -> InDegGraph %1 -> (InDegGraph, Ur (Maybe Node))
9695
checkSource node dag =
97-
HMap.lookup node dag & \case
96+
case HMap.lookup node dag of
9897
(Ur Nothing, dag) -> (dag, Ur Nothing)
9998
(Ur (Just (xs, 0)), dag) -> (dag, Ur (Just node))
10099
(Ur (Just (xs, n)), dag) -> (dag, Ur Nothing)
@@ -103,5 +102,5 @@ mapAccum ::
103102
(a -> b %1 -> (b, Ur c)) -> [a] -> b %1 -> (b, Ur [c])
104103
mapAccum f [] b = (b, Ur [])
105104
mapAccum f (x : xs) b =
106-
mapAccum f xs b & \case
105+
case mapAccum f xs b of
107106
(b, Ur cs) -> second (Data.fmap (: cs)) (f x b)

src/Control/Optics/Linear/Internal.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -173,7 +173,7 @@ getConst' (Const x) = x
173173

174174
lengthOf :: (MultIdentity r) => Optic_ (NonLinear.Kleisli (Const (Sum r))) s t a b -> s -> r
175175
lengthOf l s =
176-
(gets l (const (Sum one)) s) & \case
176+
case gets l (const (Sum one)) s of
177177
Sum r -> r
178178

179179
-- XXX: the below two functions will be made redundant with multiplicity

src/Control/Optics/Linear/Prism.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@
2323
-- -- (This is a bit of a toy example since we could use @over@ for this.)
2424
-- formatLicenceName :: PersonId %1-> PersonId
2525
-- formatLicenceName personId =
26-
-- Data.fmap modLisc (match pIdLiscPrism personId) & \case
26+
-- case Data.fmap modLisc (match pIdLiscPrism personId) of
2727
-- Left personId' -> personId'
2828
-- Right lisc -> build pIdLiscPrism lisc
2929
-- where

src/Data/Array/Mutable/Linear/Internal.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -190,7 +190,7 @@ slice ::
190190
Array a %1 ->
191191
(Array a, Array a)
192192
slice from targetSize arr =
193-
size arr & \case
193+
case size arr of
194194
(Ur s, Array old)
195195
| s < from + targetSize ->
196196
Unlifted.lseq

src/Data/Functor/Linear/Internal/Traversable.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -239,7 +239,7 @@ instance GTraversable U1 where
239239
{-# INLINE gtraverse #-}
240240

241241
instance GTraversable V1 where
242-
gtraverse _ v = Control.pure ((\case {}) v)
242+
gtraverse _ v = Control.pure (case v of {})
243243

244244
instance GTraversable UAddr where
245245
gtraverse _ (UAddr x) = Control.pure (UAddr x)

src/Data/HashMap/Mutable/Linear/Internal.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -295,7 +295,7 @@ mapMaybeWithKey f (HashMap _ cap arr) =
295295
then (Ur count, shiftSegmentBackward dec (end + 1) arr 0)
296296
else (Ur count, arr)
297297
| otherwise =
298-
Array.unsafeRead arr ix & \case
298+
case Array.unsafeRead arr ix of
299299
(Ur Nothing, arr1) ->
300300
mapAndPushBack (ix + 1) end (False, 0) count arr1
301301
(Ur (Just (RobinVal (PSL p) k v)), arr1) -> case f' k v of
@@ -397,7 +397,7 @@ intersectionWith combine (hm1 :: HashMap k a') hm2 =
397397
HashMap k c
398398
go _ hm (Ur []) acc = hm `lseq` acc
399399
go f hm (Ur ((k, b) : xs)) acc =
400-
lookup k hm & \case
400+
case lookup k hm of
401401
(Ur Nothing, hm') -> go f hm' (Ur xs) acc
402402
(Ur (Just a), hm') -> go f hm' (Ur xs) (insert k (f a b) acc)
403403

@@ -446,7 +446,7 @@ lookup k hm =
446446
-- | Check if the given key exists.
447447
member :: (Keyed k) => k -> HashMap k v %1 -> (Ur Bool, HashMap k v)
448448
member k hm =
449-
lookup k hm & \case
449+
case lookup k hm of
450450
(Ur Nothing, hm') -> (Ur False, hm')
451451
(Ur (Just _), hm') -> (Ur True, hm')
452452

@@ -557,7 +557,7 @@ shiftSegmentBackward ::
557557
Int ->
558558
RobinArr k v
559559
shiftSegmentBackward dec s arr ix =
560-
Array.unsafeRead arr ix & \case
560+
case Array.unsafeRead arr ix of
561561
(Ur Nothing, arr') -> arr'
562562
(Ur (Just (RobinVal 0 _ _)), arr') -> arr'
563563
(Ur (Just val), arr') ->

src/Data/List/Linear.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -117,7 +117,7 @@ map = fmap
117117
filter :: (Dupable a) => (a %1 -> Bool) -> [a] %1 -> [a]
118118
filter _ [] = []
119119
filter p (x : xs) =
120-
dup x & \case
120+
case dup x of
121121
(x', x'') ->
122122
if p x'
123123
then x'' : filter p xs
@@ -149,10 +149,10 @@ splitAt i = Unsafe.toLinear (Prelude.splitAt i)
149149
span :: (Dupable a) => (a %1 -> Bool) -> [a] %1 -> ([a], [a])
150150
span _ [] = ([], [])
151151
span f (x : xs) =
152-
dup x & \case
152+
case dup x of
153153
(x', x'') ->
154154
if f x'
155-
then span f xs & \case (ts, fs) -> (x'' : ts, fs)
155+
then case span f xs of (ts, fs) -> (x'' : ts, fs)
156156
else ([x''], xs)
157157

158158
-- The partition function takes a predicate a list and returns the
@@ -310,7 +310,7 @@ scanl1 f (x : xs) = scanl f x xs
310310
scanr :: (Dupable b) => (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> [b]
311311
scanr _ b [] = [b]
312312
scanr f b (a : as) =
313-
scanr f b as & \case
313+
case scanr f b as of
314314
(b' : bs') ->
315315
dup2 b' & \(b'', b''') ->
316316
f a b'' : b''' : bs'
@@ -322,7 +322,7 @@ scanr1 :: (Dupable a) => (a %1 -> a %1 -> a) -> [a] %1 -> [a]
322322
scanr1 _ [] = []
323323
scanr1 _ [a] = [a]
324324
scanr1 f (a : as) =
325-
scanr1 f as & \case
325+
case scanr1 f as of
326326
(a' : as') ->
327327
dup2 a' & \(a'', a''') ->
328328
f a a'' : a''' : as'
@@ -364,7 +364,7 @@ zipWith' _ [] [] = ([], Nothing)
364364
zipWith' _ (a : as) [] = ([], Just (Left (a :| as)))
365365
zipWith' _ [] (b : bs) = ([], Just (Right (b :| bs)))
366366
zipWith' f (a : as) (b : bs) =
367-
zipWith' f as bs & \case
367+
case zipWith' f as bs of
368368
(cs, rest) -> (f a b : cs, rest)
369369

370370
zipWith3 :: forall a b c d. (Consumable a, Consumable b, Consumable c) => (a %1 -> b %1 -> c %1 -> d) -> [a] %1 -> [b] %1 -> [c] %1 -> [d]

src/Data/Monoid/Linear/Internal/Semigroup.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -126,14 +126,14 @@ instance (Semigroup a) => Semigroup (Identity a) where
126126
instance (Consumable a) => Semigroup (Monoid.First a) where
127127
(Monoid.First Nothing) <> y = y
128128
x <> (Monoid.First y) =
129-
y & \case
129+
case y of
130130
Nothing -> x
131131
Just y' -> y' `lseq` x
132132

133133
instance (Consumable a) => Semigroup (Monoid.Last a) where
134134
x <> (Monoid.Last Nothing) = x
135135
(Monoid.Last x) <> y =
136-
x & \case
136+
case x of
137137
Nothing -> y
138138
Just x' -> x' `lseq` y
139139

@@ -174,7 +174,7 @@ instance (Semigroup a) => Semigroup (Solo a) where
174174
instance (Consumable a, Consumable b) => Semigroup (Either a b) where
175175
Left x <> y = x `lseq` y
176176
x <> y =
177-
y & \case
177+
case y of
178178
Left y' -> y' `lseq` x
179179
Right y' -> y' `lseq` x
180180

src/Data/Ord/Linear/Internal/Ord.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ instance (Consumable a, Ord a) => Ord [a] where
115115
compare xs [] = xs `lseq` GT
116116
compare [] ys = ys `lseq` LT
117117
compare (x : xs) (y : ys) =
118-
compare x y & \case
118+
case compare x y of
119119
EQ -> compare xs ys
120120
res -> (xs, ys) `lseq` res
121121

src/Data/Replicator/Linear/Internal.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -89,7 +89,7 @@ liftA2 f (Streamed sa) (Streamed sb) = Streamed (ReplicationStream.liftA2 f sa s
8989
next :: Replicator a %1 -> (a, Replicator a)
9090
next (Moved x) = (x, Moved x)
9191
next (Streamed (ReplicationStream s give dups consumes)) =
92-
dups s & \case
92+
case dups s of
9393
(s1, s2) -> (give s1, Streamed (ReplicationStream s2 give dups consumes))
9494
{-# INLINEABLE next #-}
9595

@@ -98,18 +98,18 @@ next (Streamed (ReplicationStream s give dups consumes)) =
9898
next# :: Replicator a %1 -> (# a, Replicator a #)
9999
next# (Moved x) = (# x, Moved x #)
100100
next# (Streamed (ReplicationStream s give dups consumes)) =
101-
dups s & \case
101+
case dups s of
102102
(s1, s2) -> (# give s1, Streamed (ReplicationStream s2 give dups consumes) #)
103103
{-# INLINEABLE next# #-}
104104

105105
-- | @'take' n as@ is a list of size @n@, containing @n@ replicas from @as@.
106106
take :: Prelude.Int -> Replicator a %1 -> [a]
107107
take 0 r =
108-
consume r & \case
108+
case consume r of
109109
() -> []
110110
take 1 r = [extract r]
111111
take n r =
112-
next r & \case
112+
case next r of
113113
(a, r') -> a : take (n - 1) r'
114114

115115
-- | Returns the next item from @'Replicator' a@ and efficiently consumes
@@ -170,7 +170,7 @@ class Elim n a b where
170170

171171
instance Elim 'Z a b where
172172
elim' b r =
173-
consume r & \case
173+
case consume r of
174174
() -> b
175175
{-# INLINE elim' #-}
176176

@@ -180,6 +180,6 @@ instance Elim ('S 'Z) a b where
180180

181181
instance (Elim ('S n) a b) => Elim ('S ('S n)) a b where
182182
elim' g r =
183-
next r & \case
183+
case next r of
184184
(a, r') -> elim' @('S n) (g a) r'
185185
{-# INLINE elim' #-}

src/Data/Replicator/Linear/Internal/ReplicationStream.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -70,11 +70,11 @@ pure x =
7070
(sf, sx)
7171
(\(sf', sx') -> givef sf' (givex sx'))
7272
( \(sf', sx') ->
73-
(dupsf sf', dupsx sx') & \case
73+
case (dupsf sf', dupsx sx') of
7474
((sf1, sf2), (sx1, sx2)) -> ((sf1, sx1), (sf2, sx2))
7575
)
7676
( \(sf', sx') ->
77-
consumesf sf' & \case
77+
case consumesf sf' of
7878
() -> consumesx sx'
7979
)
8080

@@ -84,11 +84,11 @@ liftA2 f (ReplicationStream sa givea dupsa consumesa) (ReplicationStream sb give
8484
(sa, sb)
8585
(\(sa', sb') -> f (givea sa') (giveb sb'))
8686
( \(sa', sb') ->
87-
(dupsa sa', dupsb sb') & \case
87+
case (dupsa sa', dupsb sb') of
8888
((sa1, sa2), (sb1, sb2)) -> ((sa1, sb1), (sa2, sb2))
8989
)
9090
( \(sa', sb') ->
91-
consumesa sa' & \case
91+
case consumesa sa' of
9292
() -> consumesb sb'
9393
)
9494
-- We need to inline this to get good results with generic deriving

src/Data/Unrestricted/Linear/Internal/Instances.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -47,17 +47,17 @@ newtype AsMovable a = AsMovable a
4747

4848
instance (Movable a) => Movable (AsMovable a) where
4949
move (AsMovable x) =
50-
move x & \case
50+
case move x of
5151
Ur x' -> Ur (AsMovable x')
5252

5353
instance (Movable a) => Consumable (AsMovable a) where
5454
consume x =
55-
move x & \case
55+
case move x of
5656
Ur _ -> ()
5757

5858
instance (Movable a) => Dupable (AsMovable a) where
5959
dupR x =
60-
move x & \case
60+
case move x of
6161
Ur x' -> Data.pure x'
6262

6363
deriving via (AsMovable Int8) instance Consumable Int8

0 commit comments

Comments
 (0)