Skip to content

Commit bd9beae

Browse files
committed
Add a ($^) application function which moves the argument
Closes #406
1 parent 113a758 commit bd9beae

File tree

3 files changed

+16
-8
lines changed

3 files changed

+16
-8
lines changed

src/Data/Unrestricted/Linear.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -68,22 +68,22 @@ module Data.Unrestricted.Linear
6868

6969
-- * Performing non-linear actions on linearly bound values
7070
Consumable (..),
71-
Dupable (..),
72-
Movable (..),
7371
lseq,
72+
Dupable (..),
7473
dup,
7574
dup3,
7675
dup4,
7776
dup5,
7877
dup6,
7978
dup7,
80-
module Data.Unrestricted.Linear.Internal.Instances,
79+
Movable (..),
80+
($^),
8181
)
8282
where
8383

8484
import Data.Unrestricted.Linear.Internal.Consumable
8585
import Data.Unrestricted.Linear.Internal.Dupable
86-
import Data.Unrestricted.Linear.Internal.Instances
86+
import Data.Unrestricted.Linear.Internal.Instances ()
8787
import Data.Unrestricted.Linear.Internal.Movable
8888
import Data.Unrestricted.Linear.Internal.Ur
8989
import Data.Unrestricted.Linear.Internal.UrT

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

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,10 @@
44
{-# LANGUAGE FlexibleContexts #-}
55
{-# LANGUAGE FlexibleInstances #-}
66
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
7+
{-# LANGUAGE KindSignatures #-}
78
{-# LANGUAGE LambdaCase #-}
89
{-# LANGUAGE LinearTypes #-}
10+
{-# LANGUAGE PolyKinds #-}
911
{-# LANGUAGE QuantifiedConstraints #-}
1012
{-# LANGUAGE ScopedTypeVariables #-}
1113
{-# LANGUAGE StandaloneDeriving #-}
@@ -18,6 +20,7 @@
1820
module Data.Unrestricted.Linear.Internal.Movable
1921
( -- * Movable
2022
Movable (..),
23+
($^),
2124
GMovable,
2225
genericMove,
2326
)
@@ -30,12 +33,11 @@ import qualified Data.Semigroup as Semigroup
3033
import Data.Unrestricted.Linear.Internal.Dupable
3134
import Data.Unrestricted.Linear.Internal.Ur
3235
import GHC.Tuple (Solo)
33-
import GHC.Types (Multiplicity (..))
36+
import GHC.Types
3437
import Generics.Linear
3538
import Prelude.Linear.Generically
3639
import Prelude.Linear.Internal
3740
import qualified Unsafe.Linear as Unsafe
38-
import Prelude (Bool (..), Char, Double, Float, Int, Ordering (..), Word)
3941
import qualified Prelude as Prelude
4042

4143
-- | Use @'Movable' a@ to represent a type which can be used many times even
@@ -56,6 +58,11 @@ import qualified Prelude as Prelude
5658
class Dupable a => Movable a where
5759
move :: a %1 -> Ur a
5860

61+
($^) :: forall {rep} a (b :: TYPE rep). Movable a => (a -> b) %1 -> a %1 -> b
62+
f $^ a =
63+
move a & \case
64+
Ur a' -> f a'
65+
5966
-- -------------
6067
-- Instances
6168

src/Prelude/Linear.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -137,11 +137,12 @@ module Prelude.Linear
137137
-- * Doing non-linear operations inside linear functions
138138
-- $
139139
Consumable (..),
140-
Dupable (..),
141-
Movable (..),
142140
lseq,
141+
Dupable (..),
143142
dup,
144143
dup3,
144+
Movable (..),
145+
($^),
145146
forget,
146147
)
147148
where

0 commit comments

Comments
 (0)