Skip to content

Commit

Permalink
Fix documentation for instances involving Void (#147)
Browse files Browse the repository at this point in the history
* remove Emacs auto-save file

* fix documentation for instances involving Void

* link to uncluttering note
  • Loading branch information
Prillan authored Jul 2, 2022
1 parent 45a1bf2 commit e5a3907
Show file tree
Hide file tree
Showing 17 changed files with 70 additions and 198 deletions.
31 changes: 18 additions & 13 deletions generic-lens-core/src/Data/Generics/Internal/Void.hs
Original file line number Diff line number Diff line change
@@ -1,19 +1,24 @@
{-# LANGUAGE PolyKinds #-}
module Data.Generics.Internal.Void where
module Data.Generics.Internal.Void
( -- $note
Void
, Void1
, Void2
) where

{-
Note [Uncluttering type signatures]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- $note
-- = Uncluttering type signatures
--
-- Because the various instances in the library always match (the Has* classes
-- are essentially glorified constraint synonyms), they get replaced with
-- their constraints, resulting in large, unreadable types.
--
-- Writing an (overlapping instance) for this Void type means that the original
-- instance might not be the one selected, thus GHC leaves the constraints in
-- place until further information is provided, at which point the type
-- machinery has sufficient information to reduce to sensible types.

Because the various instances in the library always match (the Has* classes
are essentially glorified constraint synonyms), they get replaced with
their constraints, resulting in large, unreadable types.
Writing an (overlapping instance) for this Void type means that the original
instance might not be the one selected, thus GHC leaves the constraints in
place until further information is provided, at which point the type
machinery has sufficient information to reduce to sensible types.
-}
data Void
data Void1 a
data Void2 a b
154 changes: 0 additions & 154 deletions generic-lens-core/src/Data/Generics/Product/#Positions.hs#

This file was deleted.

4 changes: 3 additions & 1 deletion generic-lens/generic-lens.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -101,5 +101,7 @@ test-suite doctests
type: exitcode-stdio-1.0
ghc-options: -threaded
main-is: doctest.hs
build-depends: base >4 && <5, doctest
build-depends: base >4 && <5
, doctest
, lens
hs-source-dirs: examples
3 changes: 2 additions & 1 deletion generic-lens/src/Data/Generics/Product/Fields.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,7 +155,8 @@ instance (Core.Context field s t a b , HasField0 field s t a b) => HasField fiel
-- instance {-# OVERLAPPING #-} HasField' field s a => HasField field s s a a where
-- field f s = field' @field f s

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d field
-- field
-- :: (HasField field s t a b, Functor f) => (a -> f b) -> s -> f t
Expand Down
3 changes: 2 additions & 1 deletion generic-lens/src/Data/Generics/Product/Positions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,8 @@ instance (Core.Context i s t a b , HasPosition0 i s t a b) => HasPosition i s t
position = position0 @i
{-# INLINE position #-}

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d position
-- position
-- :: (HasPosition i s t a b, Functor f) => (a -> f b) -> s -> f t
Expand Down
6 changes: 4 additions & 2 deletions generic-lens/src/Data/Generics/Product/Subtype.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,14 +117,16 @@ instance Core.Context a b => Subtype b a where
instance {-# OVERLAPPING #-} Subtype a a where
super = id

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d super
-- super
-- :: (Subtype sup sub, Functor f) => (sup -> f sup) -> sub -> f sub
instance {-# OVERLAPPING #-} Subtype a Void where
super = undefined

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d super @Int
-- super @Int
-- :: (Subtype Int sub, Functor f) => (Int -> f Int) -> sub -> f sub
Expand Down
5 changes: 3 additions & 2 deletions generic-lens/src/Data/Generics/Product/Typed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,10 +109,11 @@ instance {-# OVERLAPPING #-} HasType a a where
setTyped a _ = a
{-# INLINE setTyped #-}

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d typed
-- typed :: (HasType a s, Functor f) => (a -> f a) -> s -> f s
--
-- Note that this might not longer be needed given the above 'HasType a a' instance.
-- Note that this might not longer be needed given the 'HasType a a' instance.
instance {-# OVERLAPPING #-} HasType a Void where
typed = undefined
3 changes: 2 additions & 1 deletion generic-lens/src/Data/Generics/Sum/Constructors.hs
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,8 @@ instance (Core.Context ctor s t a b, AsConstructor0 ctor s t a b) => AsConstruct
_Ctor eta = _Ctor0 @ctor eta
{-# INLINE _Ctor #-}

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d _Ctor
-- _Ctor
-- :: (AsConstructor ctor s t a b, Choice p, Applicative f) =>
Expand Down
15 changes: 9 additions & 6 deletions generic-lens/src/Data/Generics/Sum/Subtype.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,22 +109,25 @@ instance Core.Context sub sup => AsSubtype sub sup where
{-# INLINE _Sub #-}

-- | Reflexive case
--
-- >>> _Sub # dog :: Animal
-- Dog (MkDog {name = "Shep", age = 3})
instance {-# OVERLAPPING #-} AsSubtype a a where
_Sub = id
{-# INLINE _Sub #-}

-- | See Note [Uncluttering type signatures]
--_Sub
-- :: (AsSubtype sub sup, Data.Profunctor.Choice.Choice p,
-- Applicative f) =>
-- p sub (f sub) -> p sup (f sup)
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d _Sub
-- _Sub
-- :: (AsSubtype sub sup, Choice p, Applicative f) =>
-- p sub (f sub) -> p sup (f sup)
instance {-# OVERLAPPING #-} AsSubtype a Void where
injectSub = undefined
projectSub = undefined

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d _Sub @Int
-- _Sub @Int
-- :: (AsSubtype Int sup, Choice p, Applicative f) =>
Expand Down
6 changes: 4 additions & 2 deletions generic-lens/src/Data/Generics/Sum/Typed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,8 @@ instance Core.Context a s => AsType a s where
_Typed eta = prism2prismvl Core.derived eta
{-# INLINE _Typed #-}

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d _Typed
-- _Typed
-- :: (AsType a s, Choice p, Applicative f) => p a (f a) -> p s (f s)
Expand All @@ -110,7 +111,8 @@ instance {-# OVERLAPPING #-} AsType a Void where
injectTyped = undefined
projectTyped = undefined

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t +d _Typed @Int
-- _Typed @Int
-- :: (AsType Int s, Choice p, Applicative f) =>
Expand Down
3 changes: 2 additions & 1 deletion generic-optics/src/Data/Generics/Product/Fields.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,7 +155,8 @@ instance (Core.Context field s t a b , HasField0 field s t a b) => HasField fiel
-- instance {-# OVERLAPPING #-} HasField' field s a => HasField field s s a a where
-- field f s = field' @field f s

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t field
-- field :: HasField field s t a b => Lens s t a b
instance {-# OVERLAPPING #-} HasField f (Void1 a) (Void1 b) a b where
Expand Down
3 changes: 2 additions & 1 deletion generic-optics/src/Data/Generics/Product/Positions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,8 @@ instance (Core.Context i s t a b , HasPosition0 i s t a b) => HasPosition i s t
position = position0 @i
{-# INLINE position #-}

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t position
-- position :: HasPosition i s t a b => Lens s t a b
instance {-# OVERLAPPING #-} HasPosition f (Void1 a) (Void1 b) a b where
Expand Down
6 changes: 4 additions & 2 deletions generic-optics/src/Data/Generics/Product/Subtype.hs
Original file line number Diff line number Diff line change
Expand Up @@ -118,13 +118,15 @@ instance Core.Context a b => Subtype b a where
instance {-# OVERLAPPING #-} Subtype a a where
super = Optic id

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t super
-- super :: Subtype sup sub => Lens sub sub sup sup
instance {-# OVERLAPPING #-} Subtype a Void where
super = undefined

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t super @Int
-- super @Int :: Subtype Int sub => Lens sub sub Int Int
instance {-# OVERLAPPING #-} Subtype Void a where
Expand Down
5 changes: 3 additions & 2 deletions generic-optics/src/Data/Generics/Product/Typed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,10 +110,11 @@ instance {-# OVERLAPPING #-} HasType a a where
setTyped a _ = a
{-# INLINE setTyped #-}

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t typed
-- typed :: HasType a s => Lens s s a a
--
-- Note that this might not longer be needed given the above 'HasType a a' instance.
-- Note that this might not longer be needed given the 'HasType a a' instance.
instance {-# OVERLAPPING #-} HasType a Void where
typed = undefined
3 changes: 2 additions & 1 deletion generic-optics/src/Data/Generics/Sum/Constructors.hs
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,8 @@ instance (Core.Context ctor s t a b, AsConstructor0 ctor s t a b) => AsConstruct
_Ctor = _Ctor0 @ctor
{-# INLINE _Ctor #-}

-- | See Note [Uncluttering type signatures]
-- | Uncluttering type signatures (see 'Void')
--
-- >>> :t _Ctor
-- _Ctor :: AsConstructor ctor s t a b => Prism s t a b
instance {-# OVERLAPPING #-} AsConstructor ctor (Void1 a) (Void1 b) a b where
Expand Down
Loading

0 comments on commit e5a3907

Please sign in to comment.