Skip to content

Commit f5488a5

Browse files
committed
rename Weak -> Weakened
Separates it from `Weak :: Strength`.
1 parent 74496ba commit f5488a5

File tree

9 files changed

+75
-72
lines changed

9 files changed

+75
-72
lines changed

CHANGELOG.md

+3
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
## 0.10.0 (unreleased)
2+
* rename `Weak` to `Weakened`, to separate from `Weak :: Strength`
3+
14
## 0.9.1 (2024-10-01)
25
* update rerefined dependency
36

src/Strongweak/Generic.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module Strongweak.Generic
1818
import Strongweak.Weaken.Generic
1919
import Strongweak.Strengthen.Generic
2020

21-
import Strongweak.Weaken ( Weaken(Weak, weaken) )
21+
import Strongweak.Weaken ( Weaken(Weakened, weaken) )
2222
import Strongweak.Strengthen ( Strengthen(strengthen) )
2323
import GHC.Generics
2424
import Data.Kind ( Type )
@@ -79,7 +79,7 @@ instance
7979
( Generic s, Generic w
8080
, GWeaken (Rep s) (Rep w)
8181
) => Weaken (GenericallySW s w) where
82-
type Weak (GenericallySW s w) = w
82+
type Weakened (GenericallySW s w) = w
8383
weaken = weakenGeneric . unGenericallySW
8484

8585
instance

src/Strongweak/Strengthen.hs

+5-5
Original file line numberDiff line numberDiff line change
@@ -17,11 +17,11 @@ module Strongweak.Strengthen
1717
, failStrengthen
1818

1919
-- * Re-exports
20-
, Strongweak.Weaken.Weak
20+
, Strongweak.Weaken.Weakened
2121
) where
2222

2323
import Strongweak.Util.TypeNats ( natVal'' )
24-
import Strongweak.Weaken ( Weaken(..) )
24+
import Strongweak.Weaken ( Weaken(Weakened, weaken) )
2525

2626
import GHC.TypeNats ( KnownNat )
2727
import Data.Word
@@ -52,9 +52,9 @@ are a little confusingly worded. Alas.
5252
See "Strongweak" for class design notes and laws.
5353
-}
5454
class Weaken a => Strengthen a where
55-
-- | Attempt to strengthen some @'Weak' a@ to its associated strong type
55+
-- | Attempt to strengthen some @'Weakened' a@ to its associated strong type
5656
-- @a@.
57-
strengthen :: Weak a -> Either StrengthenFailure' a
57+
strengthen :: Weakened a -> Either StrengthenFailure' a
5858

5959
-- | Weaken a strong value, then strengthen it again.
6060
--
@@ -199,7 +199,7 @@ instance Strengthen a => Strengthen [a] where
199199
strengthen = strengthenList
200200

201201
-- TODO using reverse, SLOW!! >:(
202-
strengthenList :: Strengthen a => [Weak a] -> Either StrengthenFailure' [a]
202+
strengthenList :: Strengthen a => [Weakened a] -> Either StrengthenFailure' [a]
203203
strengthenList = goR (0 :: Int) [] . map strengthen
204204
where
205205
goR i as = \case

src/Strongweak/Strengthen/Generic.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -131,7 +131,7 @@ instance {-# OVERLAPPING #-} GStrengthenS i
131131

132132
-- | Strengthen a field using the existing 'Strengthen' instance.
133133
instance
134-
( Weak s ~ w -- has to be here, else "illegal typesym family app in instance"
134+
( Weakened s ~ w -- required, else "illegal typesym family app in instance"
135135
, Strengthen s
136136
, ReifySelector i wmr smr
137137
) => GStrengthenS i

src/Strongweak/Strengthen/Unsafe.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
module Strongweak.Strengthen.Unsafe where
22

3-
import Strongweak.Weaken
3+
import Strongweak.Weaken ( Weaken(Weakened) )
44
import Data.Word
55
import Data.Int
66
import Rerefined.Refine
@@ -12,7 +12,7 @@ import Data.Functor.Const
1212
import Data.List.NonEmpty qualified as NonEmpty
1313
import Data.List.NonEmpty ( NonEmpty )
1414

15-
{- | Unsafely transform a @'Weak' a@ to an @a@, without asserting invariants.
15+
{- | Unsafely transform a @'Weakened' a@ to an @a@, without asserting invariants.
1616
1717
Naturally, you must only even /consider/ using this if you have a guarantee that
1818
your value is safe to treat as strong.
@@ -31,8 +31,8 @@ doesn't fit in its strong counterpart? That depends on the strengthen.
3131
See "Strongweak" for class design notes and laws.
3232
-}
3333
class Weaken a => UnsafeStrengthen a where
34-
-- | Unsafely transform a @'Weak' a@ to its associated strong type @a@.
35-
unsafeStrengthen :: Weak a -> a
34+
-- | Unsafely transform a @'Weakened' a@ to its associated strong type @a@.
35+
unsafeStrengthen :: Weakened a -> a
3636

3737
-- | Add a refinement to a type without checking the associated predicate.
3838
instance UnsafeStrengthen (Refined p a) where

src/Strongweak/Weaken.hs

+38-38
Original file line numberDiff line numberDiff line change
@@ -30,10 +30,10 @@ See "Strongweak" for class design notes and laws.
3030
-}
3131
class Weaken a where
3232
-- | The weakened type for some type.
33-
type Weak a :: Type
33+
type Weakened a :: Type
3434

35-
-- | Weaken some @a@ to its associated weak type @'Weak' a@.
36-
weaken :: a -> Weak a
35+
-- | Weaken some @a@ to its associated weak type @'Weakened' a@.
36+
weaken :: a -> Weakened a
3737

3838
-- | Strength enumeration: is it strong, or weak?
3939
--
@@ -42,7 +42,7 @@ data Strength = Strong | Weak
4242

4343
-- | Lift a function on a weak type to the associated strong type by weakening
4444
-- first.
45-
liftWeakF :: Weaken a => (Weak a -> b) -> (a -> b)
45+
liftWeakF :: Weaken a => (Weakened a -> b) -> (a -> b)
4646
liftWeakF f = f . weaken
4747

4848
{- | Get either the strong or weak representation of a type, depending on the
@@ -59,93 +59,93 @@ data A (s :: Strength) = A
5959
@
6060
-}
6161
type family SW (s :: Strength) a :: Type where
62-
SW 'Strong a = a
63-
SW 'Weak a = Weak a
62+
SW Strong a = a
63+
SW Weak a = Weakened a
6464

6565
-- | Track multiple levels of weakening. Silly thought I had, don't think it's
6666
-- useful.
6767
type family SWDepth (n :: Natural) a :: Type where
6868
SWDepth 0 a = a
69-
SWDepth n a = Weak (SWDepth (n-1) a)
69+
SWDepth n a = Weakened (SWDepth (n-1) a)
7070

7171
-- | Strip refined type refinement.
72-
instance Weaken (Refined p a) where
73-
type Weak (Refined p a) = a
72+
instance Weaken (Refined p a) where
73+
type Weakened (Refined p a) = a
7474
weaken = unrefine
7575

7676
-- | Strip refined functor type refinement.
77-
instance Weaken (Refined1 p f a) where
78-
type Weak (Refined1 p f a) = f a
77+
instance Weaken (Refined1 p f a) where
78+
type Weakened (Refined1 p f a) = f a
7979
weaken = unrefine1
8080

8181
-- | Weaken non-empty lists into plain lists.
82-
instance Weaken (NonEmpty a) where
83-
type Weak (NonEmpty a) = [a]
82+
instance Weaken (NonEmpty a) where
83+
type Weakened (NonEmpty a) = [a]
8484
weaken = NonEmpty.toList
8585

8686
-- | Weaken sized vectors into plain lists.
8787
instance VG.Vector v a => Weaken (VGS.Vector v n a) where
88-
type Weak (VGS.Vector v n a) = [a]
88+
type Weakened (VGS.Vector v n a) = [a]
8989
weaken = VGS.toList
9090

9191
-- | Strip wrapper.
92-
instance Weaken (Identity a) where
93-
type Weak (Identity a) = a
92+
instance Weaken (Identity a) where
93+
type Weakened (Identity a) = a
9494
weaken = runIdentity
9595

9696
-- | Strip wrapper.
97-
instance Weaken (Const a b) where
98-
type Weak (Const a b) = a
97+
instance Weaken (Const a b) where
98+
type Weakened (Const a b) = a
9999
weaken = getConst
100100

101101
{- TODO controversial. seems logical, but also kinda annoying.
102102
-- | Weaken 'Maybe' (0 or 1) into '[]' (0 to n).
103103
instance Weaken (Maybe a) where
104-
type Weak (Maybe a) = [a]
104+
type Weakened (Maybe a) = [a]
105105
weaken = \case Just a -> [a]
106106
Nothing -> []
107107
-}
108108

109109
-- Weaken the bounded Haskell numeric types using 'fromIntegral'.
110-
instance Weaken Word8 where
111-
type Weak Word8 = Natural
110+
instance Weaken Word8 where
111+
type Weakened Word8 = Natural
112112
weaken = fromIntegral
113-
instance Weaken Word16 where
114-
type Weak Word16 = Natural
113+
instance Weaken Word16 where
114+
type Weakened Word16 = Natural
115115
weaken = fromIntegral
116-
instance Weaken Word32 where
117-
type Weak Word32 = Natural
116+
instance Weaken Word32 where
117+
type Weakened Word32 = Natural
118118
weaken = fromIntegral
119-
instance Weaken Word64 where
120-
type Weak Word64 = Natural
119+
instance Weaken Word64 where
120+
type Weakened Word64 = Natural
121121
weaken = fromIntegral
122-
instance Weaken Int8 where
123-
type Weak Int8 = Integer
122+
instance Weaken Int8 where
123+
type Weakened Int8 = Integer
124124
weaken = fromIntegral
125-
instance Weaken Int16 where
126-
type Weak Int16 = Integer
125+
instance Weaken Int16 where
126+
type Weakened Int16 = Integer
127127
weaken = fromIntegral
128-
instance Weaken Int32 where
129-
type Weak Int32 = Integer
128+
instance Weaken Int32 where
129+
type Weakened Int32 = Integer
130130
weaken = fromIntegral
131-
instance Weaken Int64 where
132-
type Weak Int64 = Integer
131+
instance Weaken Int64 where
132+
type Weakened Int64 = Integer
133133
weaken = fromIntegral
134134

135135
--------------------------------------------------------------------------------
136136

137137
-- | Decomposer. Weaken every element in a list.
138138
instance Weaken a => Weaken [a] where
139-
type Weak [a] = [Weak a]
139+
type Weakened [a] = [Weakened a]
140140
weaken = map weaken
141141

142142
-- | Decomposer. Weaken both elements of a tuple.
143143
instance (Weaken a, Weaken b) => Weaken (a, b) where
144-
type Weak (a, b) = (Weak a, Weak b)
144+
type Weakened (a, b) = (Weakened a, Weakened b)
145145
weaken (a, b) = (weaken a, weaken b)
146146

147147
-- | Decomposer. Weaken either side of an 'Either'.
148148
instance (Weaken a, Weaken b) => Weaken (Either a b) where
149-
type Weak (Either a b) = Either (Weak a) (Weak b)
149+
type Weakened (Either a b) = Either (Weakened a) (Weakened b)
150150
weaken = \case Left a -> Left $ weaken a
151151
Right b -> Right $ weaken b

src/Strongweak/Weaken/Generic.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ instance {-# OVERLAPPING #-} GWeaken (Rec0 s) (Rec0 s) where
3232
gweaken = id
3333

3434
-- | Weaken a field using the existing 'Weaken' instance.
35-
instance (Weaken s, Weak s ~ w) => GWeaken (Rec0 s) (Rec0 w) where
35+
instance (Weaken s, Weakened s ~ w) => GWeaken (Rec0 s) (Rec0 w) where
3636
gweaken = K1 . weaken . unK1
3737

3838
-- | Weaken product types by weakening left and right.

test/Common.hs

+18-18
Original file line numberDiff line numberDiff line change
@@ -17,18 +17,18 @@ data DS (s :: Strength)
1717
| DS1 (SW s (Refined (CompareValue LT Pos 100) Natural))
1818
deriving stock (Generic)
1919

20-
deriving stock instance Eq (DS 'Strong)
21-
deriving stock instance Show (DS 'Strong)
22-
deriving via (GenericArbitraryU `AndShrinking` (DS 'Strong)) instance Arbitrary (DS 'Strong)
20+
deriving stock instance Eq (DS Strong)
21+
deriving stock instance Show (DS Strong)
22+
deriving via (GenericArbitraryU `AndShrinking` (DS Strong)) instance Arbitrary (DS Strong)
2323

24-
deriving stock instance Eq (DS 'Weak)
25-
deriving stock instance Show (DS 'Weak)
26-
deriving via (GenericArbitraryU `AndShrinking` (DS 'Weak)) instance Arbitrary (DS 'Weak)
24+
deriving stock instance Eq (DS Weak)
25+
deriving stock instance Show (DS Weak)
26+
deriving via (GenericArbitraryU `AndShrinking` (DS Weak)) instance Arbitrary (DS Weak)
2727

28-
instance Weaken (DS 'Strong) where
29-
type Weak (DS 'Strong) = DS 'Weak
28+
instance Weaken (DS Strong) where
29+
type Weakened (DS Strong) = DS Weak
3030
weaken = weakenGeneric
31-
instance Strengthen (DS 'Strong) where strengthen = strengthenGeneric
31+
instance Strengthen (DS Strong) where strengthen = strengthenGeneric
3232

3333
data DP (s :: Strength) = DP
3434
{ dp1f0 :: SW s Word32
@@ -38,18 +38,18 @@ data DP (s :: Strength) = DP
3838
, dp1f4 :: SW s Word8
3939
} deriving stock (Generic)
4040

41-
deriving stock instance Eq (DP 'Strong)
42-
deriving stock instance Show (DP 'Strong)
43-
deriving via (GenericArbitraryU `AndShrinking` (DP 'Strong)) instance Arbitrary (DP 'Strong)
41+
deriving stock instance Eq (DP Strong)
42+
deriving stock instance Show (DP Strong)
43+
deriving via (GenericArbitraryU `AndShrinking` (DP Strong)) instance Arbitrary (DP Strong)
4444

45-
deriving stock instance Eq (DP 'Weak)
46-
deriving stock instance Show (DP 'Weak)
47-
deriving via (GenericArbitraryU `AndShrinking` (DP 'Weak)) instance Arbitrary (DP 'Weak)
45+
deriving stock instance Eq (DP Weak)
46+
deriving stock instance Show (DP Weak)
47+
deriving via (GenericArbitraryU `AndShrinking` (DP Weak)) instance Arbitrary (DP Weak)
4848

49-
instance Weaken (DP 'Strong) where
50-
type Weak (DP 'Strong) = DP 'Weak
49+
instance Weaken (DP Strong) where
50+
type Weakened (DP Strong) = DP Weak
5151
weaken = weakenGeneric
52-
instance Strengthen (DP 'Strong) where strengthen = strengthenGeneric
52+
instance Strengthen (DP Strong) where strengthen = strengthenGeneric
5353

5454
tryStrengthenSuccessEq :: Eq a => a -> Either StrengthenFailure' a -> Bool
5555
tryStrengthenSuccessEq a = \case Right a' -> a == a'; Left{} -> False

test/Strongweak/LawsSpec.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -8,11 +8,11 @@ import Test.Hspec.QuickCheck
88
spec :: Spec
99
spec = modifyMaxSize (+1000) $ do
1010
prop "weaken-strengthen roundtrip isomorphism (generic)" $ do
11-
\(d :: DS 'Strong) ->
11+
\(d :: DS Strong) ->
1212
strengthen (weaken d) `shouldSatisfy` tryStrengthenSuccessEq d
1313
prop "strengthen-weaken-strengthen roundtrip partial isomorphism (generic)" $ do
14-
\(dw :: DS 'Weak) ->
15-
case strengthen @(DS 'Strong) dw of
14+
\(dw :: DS Weak) ->
15+
case strengthen @(DS Strong) dw of
1616
Right ds ->
1717
strengthen (weaken ds) `shouldSatisfy` tryStrengthenSuccessEq ds
1818
Left{} -> pure ()

0 commit comments

Comments
 (0)