Skip to content

Commit 9259d0c

Browse files
committed
start cleaning up
1 parent 5e63f2d commit 9259d0c

File tree

8 files changed

+74
-95
lines changed

8 files changed

+74
-95
lines changed

src/Strongweak.hs

+1
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ module Strongweak
2323

2424
import Strongweak.Weaken
2525
import Strongweak.Strengthen
26+
import Strongweak.Strength
2627

2728
{- $strongweak-instance-design
2829

src/Strongweak/Chain.hs

+3-4
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,12 @@
11
{-# LANGUAGE UndecidableInstances #-} -- type family 'Weakened' in constraints
2-
{-# LANGUAGE AllowAmbiguousTypes #-} -- TODO
2+
{-# LANGUAGE AllowAmbiguousTypes #-} -- ambiguous intermediate type classes
33

44
module Strongweak.Chain where
55

6-
import Strongweak.Weaken
6+
import Strongweak.Weaken ( Weaken(weaken), type WeakenedN )
77
import Strongweak.Strengthen
88
import GHC.TypeNats
9-
10-
import Unsafe.Coerce
9+
import Unsafe.Coerce ( unsafeCoerce )
1110

1211
{- | When weakening (or strengthening), chain the operation @n@ times.
1312

src/Strongweak/Example.hs

-16
This file was deleted.

src/Strongweak/Strength.hs

+26
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
module Strongweak.Strength where
2+
3+
import Strongweak.Weaken ( type Weakened )
4+
import Data.Kind ( type Type )
5+
6+
-- | Strength enumeration: is it strong, or weak?
7+
--
8+
-- Primarily interesting at the type level (using DataKinds).
9+
data Strength = Strong | Weak
10+
11+
{- | Get either the strong or weak representation of a type, depending on the
12+
type-level "switch" provided.
13+
14+
This is intended to be used in data types that take a 'Strength' type. Define
15+
your type using strong fields wrapped in @SW s@. You then get the weak
16+
representation for free, using the same definition.
17+
18+
@
19+
data A (s :: Strength) = A
20+
{ a1 :: SW s Word8
21+
, a2 :: String }
22+
@
23+
-}
24+
type family SW (s :: Strength) a :: Type where
25+
SW Strong a = a
26+
SW Weak a = Weakened a

src/Strongweak/Strengthen.hs

+15-4
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,13 @@ module Strongweak.Strengthen
2020
, Strongweak.Weaken.Weakened
2121
) where
2222

23+
import Strongweak.Weaken ( Weaken(Weakened) )
24+
25+
import Strongweak.Weaken ( Weaken(weaken) )
26+
27+
import Strongweak.Weaken ( SWCoercibly(..) )
28+
2329
import Strongweak.Util.TypeNats ( natVal'' )
24-
import Strongweak.Weaken ( Weaken(Weakened, weaken) )
2530

2631
import GHC.TypeNats ( KnownNat )
2732
import Data.Word
@@ -101,6 +106,15 @@ failStrengthen t fs = Left $ StrengthenFailure t fs
101106
failStrengthen1 :: [text] -> Either (StrengthenFailure text) a
102107
failStrengthen1 t = failStrengthen t []
103108

109+
-- TODO add a via type for obtaining strengthen via unsafestrengthen :)
110+
-- should be permitted only for non-failing, zero invariant strengthens
111+
112+
instance Strengthen (SWCoercibly a) where
113+
strengthen = Right . SWCoercibly
114+
115+
deriving via SWCoercibly a instance Strengthen (Identity a)
116+
deriving via SWCoercibly a instance Strengthen (Const a b)
117+
104118
-- | Strengthen a type by refining it with a predicate.
105119
instance Refine p a => Strengthen (Refined p a) where
106120
strengthen = refine .> \case
@@ -236,6 +250,3 @@ f .> g = g . f
236250

237251
typeRep' :: forall a. Typeable a => TypeRep
238252
typeRep' = typeRep (Proxy @a)
239-
240-
instance Strengthen (Identity a) where
241-
strengthen = Right . Identity

src/Strongweak/Strengthen/Unsafe.hs

+10-2
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,13 @@ import Rerefined.Refine
77
import Data.Vector.Generic.Sized qualified as VGS -- Shazbot!
88
import Data.Vector.Generic qualified as VG
99
import Data.Vector.Generic.Sized.Internal qualified
10-
import Data.Functor.Identity
11-
import Data.Functor.Const
1210
import Data.List.NonEmpty qualified as NonEmpty
1311
import Data.List.NonEmpty ( NonEmpty )
1412

13+
import Strongweak.Weaken ( SWCoercibly(..) )
14+
import Data.Functor.Identity
15+
import Data.Functor.Const
16+
1517
{- | Unsafely transform a @'Weakened' a@ to an @a@, without asserting invariants.
1618
1719
Naturally, you must only even /consider/ using this if you have a guarantee that
@@ -34,6 +36,12 @@ class Weaken a => UnsafeStrengthen a where
3436
-- | Unsafely transform a @'Weakened' a@ to its associated strong type @a@.
3537
unsafeStrengthen :: Weakened a -> a
3638

39+
instance UnsafeStrengthen (SWCoercibly a) where
40+
unsafeStrengthen = SWCoercibly
41+
42+
deriving via SWCoercibly a instance UnsafeStrengthen (Identity a)
43+
deriving via SWCoercibly a instance UnsafeStrengthen (Const a b)
44+
3745
-- | Add a refinement to a type without checking the associated predicate.
3846
instance UnsafeStrengthen (Refined p a) where
3947
unsafeStrengthen = unsafeRefine

src/Strongweak/Weaken.hs

+18-68
Original file line numberDiff line numberDiff line change
@@ -2,16 +2,10 @@
22

33
module Strongweak.Weaken
44
(
5-
-- * 'Weaken' class
6-
Weaken(..)
5+
Weaken(Weakened, weaken)
76
, type WeakenedN
87
, liftWeakF
9-
10-
-- * Strength switch helper
11-
, Strength(..)
12-
, type SW
13-
14-
, ErrZeroInvariantNewtype'
8+
, SWCoercibly(..)
159
) where
1610

1711
import Rerefined
@@ -26,10 +20,6 @@ import Data.List.NonEmpty qualified as NonEmpty
2620
import Data.List.NonEmpty ( NonEmpty )
2721
import GHC.TypeNats
2822

29-
import GHC.TypeError
30-
import Strongweak.Util.TypeErrors
31-
import GHC.TypeLits ( type Symbol )
32-
3323
{- | Weaken some @a@, relaxing certain invariants.
3424
3525
See "Strongweak" for class design notes and laws.
@@ -41,38 +31,32 @@ class Weaken a where
4131
-- | Weaken some @a@ to its associated weak type @'Weakened' a@.
4232
weaken :: a -> Weakened a
4333

44-
-- | Strength enumeration: is it strong, or weak?
45-
--
46-
-- Primarily interesting at the type level (using DataKinds).
47-
data Strength = Strong | Weak
48-
4934
-- | Lift a function on a weak type to the associated strong type by weakening
5035
-- first.
5136
liftWeakF :: Weaken a => (Weakened a -> b) -> a -> b
5237
liftWeakF f = f . weaken
5338

54-
{- | Get either the strong or weak representation of a type, depending on the
55-
type-level "switch" provided.
56-
57-
This is intended to be used in data types that take a 'Strength' type. Define
58-
your type using strong fields wrapped in @SW s@. You then get the weak
59-
representation for free, using the same definition.
60-
61-
@
62-
data A (s :: Strength) = A
63-
{ a1 :: SW s Word8
64-
, a2 :: String }
65-
@
66-
-}
67-
type family SW (s :: Strength) a :: Type where
68-
SW Strong a = a
69-
SW Weak a = Weakened a
70-
7139
-- | The type of @a@ after weakening @n@ times.
7240
type family WeakenedN (n :: Natural) a :: Type where
7341
WeakenedN 0 a = a
7442
WeakenedN n a = Weakened (WeakenedN (n-1) a)
7543

44+
-- | A "via type" newtype for defining strongweak instances for zero-invariant,
45+
-- coercible newtypes.
46+
--
47+
-- Use like so:
48+
--
49+
-- @
50+
-- deriving via 'SWCoercibly' a instance 'Weaken' ('Identity' a)
51+
-- @
52+
newtype SWCoercibly a = SWCoercibly { unSWCoercibly :: a }
53+
instance Weaken (SWCoercibly a) where
54+
type Weakened (SWCoercibly a) = a
55+
weaken = unSWCoercibly
56+
57+
deriving via SWCoercibly a instance Weaken (Identity a)
58+
deriving via SWCoercibly a instance Weaken (Const a b)
59+
7660
-- | Strip refined type refinement.
7761
instance Weaken (Refined p a) where
7862
type Weakened (Refined p a) = a
@@ -144,37 +128,3 @@ instance (Weaken a, Weaken b) => Weaken (Either a b) where
144128
type Weakened (Either a b) = Either (Weakened a) (Weakened b)
145129
weaken = \case Left a -> Left $ weaken a
146130
Right b -> Right $ weaken b
147-
148-
---
149-
150-
newtype ErrZeroInvariantNewtype' (typeName :: Symbol) a
151-
= ErrZeroInvariantNewtype' a
152-
instance Unsatisfiable (ErrZeroInvariantNewtype typeName)
153-
=> Weaken (ErrZeroInvariantNewtype' typeName a) where
154-
type Weakened (ErrZeroInvariantNewtype' typeName a) =
155-
TypeError (ErrZeroInvariantNewtype typeName)
156-
weaken = unsatisfiable
157-
158-
--deriving via ErrZeroInvariantNewtype' "Identity" a
159-
-- instance Weaken (Identity a)
160-
161-
{- TODO 2024-10-16T04:21:22+0100
162-
aww this doesn't work haha. ok fine just gotta make some utils for filling out
163-
the context and Weakened associated type family for custom erroring instances
164-
-}
165-
166-
{-
167-
instance Unsatisfiable (ErrZeroInvariantNewtype "Identity")
168-
=> Weaken (Identity a) where
169-
type Weakened (Identity a) = a
170-
weaken = unsatisfiable
171-
-}
172-
173-
-- TODO define custom errors using Unsatisfiable to point users to Coercibly
174-
-- Unsatisfiable is base-4.19 -> GHC 9.8
175-
--deriving via Coercibly1 Shallow Identity a instance Weaken (Identity a)
176-
--deriving via Coercibly Shallow (Const a b) a instance Weaken (Const a b)
177-
178-
instance Weaken (Identity a) where
179-
type Weakened (Identity a) = a
180-
weaken (Identity a) = a

strongweak.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -32,8 +32,8 @@ library
3232
Strongweak
3333
Strongweak.Chain
3434
Strongweak.Coercibly
35-
Strongweak.Example
3635
Strongweak.Generic
36+
Strongweak.Strength
3737
Strongweak.Strengthen
3838
Strongweak.Strengthen.Generic
3939
Strongweak.Strengthen.Unsafe

0 commit comments

Comments
 (0)