Skip to content

Commit

Permalink
Disambiguate Haddock references
Browse files Browse the repository at this point in the history
  • Loading branch information
ncfavier committed Jul 22, 2023
1 parent 4249bcd commit 4056ccf
Show file tree
Hide file tree
Showing 24 changed files with 207 additions and 208 deletions.
99 changes: 49 additions & 50 deletions src/Control/Exception/Lens.hs

Large diffs are not rendered by default.

4 changes: 2 additions & 2 deletions src/Control/Lens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@
--
-- @
-- import Control.Lens
--
--
-- data FooBar a
-- = Foo { _x :: ['Int'], _y :: a }
-- | Bar { _x :: ['Int'] }
Expand All @@ -25,7 +25,7 @@
--
-- @
-- x :: 'Lens'' (FooBar a) ['Int']
-- y :: 'Traversal' (FooBar a) (FooBar b) a b
-- y :: t'Traversal' (FooBar a) (FooBar b) a b
-- @
--
-- You can then access the value of @_x@ with ('^.'), the value of @_y@ –
Expand Down
2 changes: 1 addition & 1 deletion src/Control/Lens/Extras.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Data.Data.Lens
-- >>> import Control.Lens
-- >>> import Numeric.Lens (hex)

-- | Check to see if this 'Prism' matches.
-- | Check to see if this t'Prism' matches.
--
-- >>> is _Left (Right 12)
-- False
Expand Down
14 changes: 7 additions & 7 deletions src/Control/Lens/Getter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Trustworthy #-}

-- Disable the warnings generated by 'to', 'ito', 'like', 'ilike'.
-- Disable the warnings generated by 'Control.Lens.Getter.to', 'ito', 'like', 'ilike'.
-- These functions are intended to produce 'Getters'. Without this constraint
-- users would get warnings when annotating types at uses of these functions.
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
Expand Down Expand Up @@ -108,11 +108,11 @@ infixl 8 ^., ^@.
-- | Build an (index-preserving) 'Getter' from an arbitrary Haskell function.
--
-- @
-- 'to' f '.' 'to' g ≡ 'to' (g '.' f)
-- 'Control.Lens.Getter.to' f '.' 'Control.Lens.Getter.to' g ≡ 'Control.Lens.Getter.to' (g '.' f)
-- @
--
-- @
-- a '^.' 'to' f ≡ f a
-- a '^.' 'Control.Lens.Getter.to' f ≡ f a
-- @
--
-- >>> a ^.to f
Expand All @@ -128,7 +128,7 @@ infixl 8 ^., ^@.
-- 5
--
-- @
-- 'to' :: (s -> a) -> 'IndexPreservingGetter' s a
-- 'Control.Lens.Getter.to' :: (s -> a) -> 'IndexPreservingGetter' s a
-- @
to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
to k = dimap k (contramap k)
Expand All @@ -148,7 +148,7 @@ ito k = dimap k (contramap (snd . k)) . uncurry . indexed
-- @
-- 'like' a '.' 'like' b ≡ 'like' b
-- a '^.' 'like' b ≡ b
-- a '^.' 'like' b ≡ a '^.' 'to' ('const' b)
-- a '^.' 'like' b ≡ a '^.' 'Control.Lens.Getter.to' ('const' b)
-- @
--
-- This can be useful as a second case 'failing' a 'Fold'
Expand Down Expand Up @@ -205,7 +205,7 @@ type Accessing p m s a = p a (Const m a) -> s -> Const m s
-- at a monoidal value.
--
-- @
-- 'view' '.' 'to' ≡ 'id'
-- 'view' '.' 'Control.Lens.Getter.to' ≡ 'id'
-- @
--
-- >>> view (to f) a
Expand Down Expand Up @@ -250,7 +250,7 @@ view l = Reader.asks (getConst #. l Const)
-- 'Control.Lens.Traversal.Traversal'.
--
-- @
-- 'views' l f ≡ 'view' (l '.' 'to' f)
-- 'views' l f ≡ 'view' (l '.' 'Control.Lens.Getter.to' f)
-- @
--
-- >>> views (to f) g a
Expand Down
2 changes: 1 addition & 1 deletion src/Control/Lens/Plated.hs
Original file line number Diff line number Diff line change
Expand Up @@ -680,7 +680,7 @@ para = paraOf plate
--
-- @
-- 'composOpMonoid' ≡ 'foldMapOf' 'plate'
-- 'composOpMPlus' f ≡ 'msumOf' ('plate' '.' 'to' f)
-- 'composOpMPlus' f ≡ 'msumOf' ('plate' '.' 'Control.Lens.Getter.to' f)
-- 'composOp' ≡ 'descend' ≡ 'over' 'plate'
-- 'composOpM' ≡ 'descendM' ≡ 'mapMOf' 'plate'
-- 'composOpM_' ≡ 'descendM_' ≡ 'mapMOf_' 'plate'
Expand Down
22 changes: 11 additions & 11 deletions src/Control/Lens/Reified.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ import Data.Semigroup
-- Lens
------------------------------------------------------------------------------

-- | Reify a 'Lens' so it can be stored safely in a container.
-- | Reify a t'Lens' so it can be stored safely in a container.
newtype ReifiedLens s t a b = Lens { runLens :: Lens s t a b }

-- | @
Expand All @@ -62,7 +62,7 @@ type ReifiedLens' s a = ReifiedLens s s a a
-- IndexedLens
------------------------------------------------------------------------------

-- | Reify an 'IndexedLens' so it can be stored safely in a container.
-- | Reify an t'IndexedLens' so it can be stored safely in a container.
newtype ReifiedIndexedLens i s t a b = IndexedLens { runIndexedLens :: IndexedLens i s t a b }

-- | @
Expand All @@ -74,7 +74,7 @@ type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a
-- IndexedTraversal
------------------------------------------------------------------------------

-- | Reify an 'IndexedTraversal' so it can be stored safely in a container.
-- | Reify an t'IndexedTraversal' so it can be stored safely in a container.
newtype ReifiedIndexedTraversal i s t a b = IndexedTraversal { runIndexedTraversal :: IndexedTraversal i s t a b }

-- | @
Expand All @@ -86,7 +86,7 @@ type ReifiedIndexedTraversal' i s a = ReifiedIndexedTraversal i s s a a
-- Traversal
------------------------------------------------------------------------------

-- | A form of 'Traversal' that can be stored monomorphically in a container.
-- | A form of t'Traversal' that can be stored monomorphically in a container.
newtype ReifiedTraversal s t a b = Traversal { runTraversal :: Traversal s t a b }

-- | @
Expand All @@ -98,7 +98,7 @@ type ReifiedTraversal' s a = ReifiedTraversal s s a a
-- Getter
------------------------------------------------------------------------------

-- | Reify a 'Getter' so it can be stored safely in a container.
-- | Reify a t'Getter' so it can be stored safely in a container.
--
-- This can also be useful when combining getters in novel ways, as
-- 'ReifiedGetter' is isomorphic to '(->)' and provides similar instances.
Expand Down Expand Up @@ -249,7 +249,7 @@ instance ArrowLoop ReifiedGetter where
-- IndexedGetter
------------------------------------------------------------------------------

-- | Reify an 'IndexedGetter' so it can be stored safely in a container.
-- | Reify an t'IndexedGetter' so it can be stored safely in a container.
newtype ReifiedIndexedGetter i s a = IndexedGetter { runIndexedGetter :: IndexedGetter i s a }

instance Profunctor (ReifiedIndexedGetter i) where
Expand Down Expand Up @@ -289,7 +289,7 @@ instance Semigroup i => Apply (ReifiedIndexedGetter i s) where
-- Fold
------------------------------------------------------------------------------

-- | Reify a 'Fold' so it can be stored safely in a container.
-- | Reify a t'Fold' so it can be stored safely in a container.
--
-- This can also be useful for creatively combining folds as
-- @'ReifiedFold' s@ is isomorphic to @ReaderT s []@ and provides similar
Expand Down Expand Up @@ -490,7 +490,7 @@ instance Strong (ReifiedIndexedFold i) where
-- Setter
------------------------------------------------------------------------------

-- | Reify a 'Setter' so it can be stored safely in a container.
-- | Reify a t'Setter' so it can be stored safely in a container.
newtype ReifiedSetter s t a b = Setter { runSetter :: Setter s t a b }

-- | @
Expand All @@ -502,7 +502,7 @@ type ReifiedSetter' s a = ReifiedSetter s s a a
-- IndexedSetter
------------------------------------------------------------------------------

-- | Reify an 'IndexedSetter' so it can be stored safely in a container.
-- | Reify an t'IndexedSetter' so it can be stored safely in a container.
newtype ReifiedIndexedSetter i s t a b =
IndexedSetter { runIndexedSetter :: IndexedSetter i s t a b }

Expand All @@ -515,7 +515,7 @@ type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a
-- Iso
------------------------------------------------------------------------------

-- | Reify an 'Iso' so it can be stored safely in a container.
-- | Reify an t'Iso' so it can be stored safely in a container.
newtype ReifiedIso s t a b = Iso { runIso :: Iso s t a b }

-- | @
Expand All @@ -527,7 +527,7 @@ type ReifiedIso' s a = ReifiedIso s s a a
-- Prism
------------------------------------------------------------------------------

-- | Reify a 'Prism' so it can be stored safely in a container.
-- | Reify a t'Prism' so it can be stored safely in a container.
newtype ReifiedPrism s t a b = Prism { runPrism :: Prism s t a b }

-- | @
Expand Down
4 changes: 2 additions & 2 deletions src/Control/Lens/Unsound.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@
-- Portability : Rank2Types
--
-- One commonly asked question is: can we combine two lenses,
-- @`Lens'` a b@ and @`Lens'` a c@ into @`Lens'` a (b, c)@.
-- @'Lens'' a b@ and @'Lens'' a c@ into @'Lens'' a (b, c)@.
-- This is fair thing to ask, but such operation is unsound in general.
-- See `lensProduct`.
--
Expand All @@ -39,7 +39,7 @@ import Prelude ()
-- >>> import Control.Lens

-- | A lens product. There is no law-abiding way to do this in general.
-- Result is only a valid 'Lens' if the input lenses project disjoint parts of
-- Result is only a valid t'Lens' if the input lenses project disjoint parts of
-- the structure @s@. Otherwise "you get what you put in" law
--
-- @
Expand Down
20 changes: 10 additions & 10 deletions src/Control/Lens/Wrapped.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@
-- Stability : experimental
-- Portability : Rank2, MPTCs, fundeps
--
-- The 'Wrapped' class provides similar functionality as @Control.Newtype@,
-- The t'Wrapped' class provides similar functionality as @Control.Newtype@,
-- from the @newtype@ package, but in a more convenient and efficient form.
--
-- There are a few functions from @newtype@ that are not provided here, because
Expand Down Expand Up @@ -169,7 +169,7 @@ import Data.Ord (Down(Down))
-- >>> import Data.Foldable (foldMap)
-- >>> import Data.Monoid (Sum (..), Product (..), All (..), Any (..))

-- | 'Wrapped' provides isomorphisms to wrap and unwrap newtypes or
-- | t'Wrapped' provides isomorphisms to wrap and unwrap newtypes or
-- data types with one constructor.
class Wrapped s where
type Unwrapped s :: Type
Expand Down Expand Up @@ -568,14 +568,14 @@ instance Wrapped (IterT m a) where

-- * unordered-containers

-- | Use @'wrapping' 'HashMap.fromList'@. Unwrapping returns some permutation of the list.
-- | Use @'_Wrapping' 'HashMap.fromList'@. Unwrapping returns some permutation of the list.
instance (t ~ HashMap k' a', Hashable k, Eq k) => Rewrapped (HashMap k a) t
instance (Hashable k, Eq k) => Wrapped (HashMap k a) where
type Unwrapped (HashMap k a) = [(k, a)]
_Wrapped' = iso HashMap.toList HashMap.fromList
{-# INLINE _Wrapped' #-}

-- | Use @'wrapping' 'HashSet.fromList'@. Unwrapping returns some permutation of the list.
-- | Use @'_Wrapping' 'HashSet.fromList'@. Unwrapping returns some permutation of the list.
instance (t ~ HashSet a', Hashable a, Eq a) => Rewrapped (HashSet a) t
instance (Hashable a, Eq a) => Wrapped (HashSet a) where
type Unwrapped (HashSet a) = [a]
Expand All @@ -584,28 +584,28 @@ instance (Hashable a, Eq a) => Wrapped (HashSet a) where

-- * containers

-- | Use @'wrapping' 'IntMap.fromList'@. unwrapping returns a /sorted/ list.
-- | Use @'_Wrapping' 'IntMap.fromList'@. unwrapping returns a /sorted/ list.
instance (t ~ IntMap a') => Rewrapped (IntMap a) t
instance Wrapped (IntMap a) where
type Unwrapped (IntMap a) = [(Int, a)]
_Wrapped' = iso IntMap.toAscList IntMap.fromList
{-# INLINE _Wrapped' #-}

-- | Use @'wrapping' 'IntSet.fromList'@. unwrapping returns a /sorted/ list.
-- | Use @'_Wrapping' 'IntSet.fromList'@. unwrapping returns a /sorted/ list.
instance (t ~ IntSet) => Rewrapped IntSet t
instance Wrapped IntSet where
type Unwrapped IntSet = [Int]
_Wrapped' = iso IntSet.toAscList IntSet.fromList
{-# INLINE _Wrapped' #-}

-- | Use @'wrapping' 'Map.fromList'@. unwrapping returns a /sorted/ list.
-- | Use @'_Wrapping' 'Map.fromList'@. unwrapping returns a /sorted/ list.
instance (t ~ Map k' a', Ord k) => Rewrapped (Map k a) t
instance Ord k => Wrapped (Map k a) where
type Unwrapped (Map k a) = [(k, a)]
_Wrapped' = iso Map.toAscList Map.fromList
{-# INLINE _Wrapped' #-}

-- | Use @'wrapping' 'Set.fromList'@. unwrapping returns a /sorted/ list.
-- | Use @'_Wrapping' 'Set.fromList'@. unwrapping returns a /sorted/ list.
instance (t ~ Set a', Ord a) => Rewrapped (Set a) t
instance Ord a => Wrapped (Set a) where
type Unwrapped (Set a) = [a]
Expand Down Expand Up @@ -1273,10 +1273,10 @@ instance Wrapped CTimer where
# endif
#endif

-- | Given the constructor for a 'Wrapped' type, return a
-- | Given the constructor for a t'Wrapped' type, return a
-- deconstructor that is its inverse.
--
-- Assuming the 'Wrapped' instance is legal, these laws hold:
-- Assuming the t'Wrapped' instance is legal, these laws hold:
--
-- @
-- 'op' f '.' f ≡ 'id'
Expand Down
32 changes: 16 additions & 16 deletions src/Control/Monad/Error/Lens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,32 +44,32 @@ import Data.Semigroup (Semigroup(..))
-- Catching
------------------------------------------------------------------------------

-- | Catch exceptions that match a given 'Prism' (or any 'Getter', really).
-- | Catch exceptions that match a given t'Prism' (or any t'Getter', really).
--
-- @
-- 'catching' :: 'MonadError' e m => 'Prism'' e a -> m r -> (a -> m r) -> m r
-- 'catching' :: 'MonadError' e m => 'Lens'' e a -> m r -> (a -> m r) -> m r
-- 'catching' :: 'MonadError' e m => 'Traversal'' e a -> m r -> (a -> m r) -> m r
-- 'catching' :: 'MonadError' e m => 'Iso'' e a -> m r -> (a -> m r) -> m r
-- 'catching' :: 'MonadError' e m => 'Getter' e a -> m r -> (a -> m r) -> m r
-- 'catching' :: 'MonadError' e m => 'Fold' e a -> m r -> (a -> m r) -> m r
-- 'catching' :: 'MonadError' e m => t'Getter' e a -> m r -> (a -> m r) -> m r
-- 'catching' :: 'MonadError' e m => t'Fold' e a -> m r -> (a -> m r) -> m r
-- @
catching :: MonadError e m => Getting (M.First a) e a -> m r -> (a -> m r) -> m r
catching l = catchJust (preview l)
{-# INLINE catching #-}

-- | Catch exceptions that match a given 'Prism' (or any 'Getter'), discarding
-- | Catch exceptions that match a given t'Prism' (or any t'Getter'), discarding
-- the information about the match. This is particularly useful when you have
-- a @'Prism'' e ()@ where the result of the 'Prism' or 'Fold' isn't
-- a @'Prism'' e ()@ where the result of the t'Prism' or t'Fold' isn't
-- particularly valuable, just the fact that it matches.
--
-- @
-- 'catching_' :: 'MonadError' e m => 'Prism'' e a -> m r -> m r -> m r
-- 'catching_' :: 'MonadError' e m => 'Lens'' e a -> m r -> m r -> m r
-- 'catching_' :: 'MonadError' e m => 'Traversal'' e a -> m r -> m r -> m r
-- 'catching_' :: 'MonadError' e m => 'Iso'' e a -> m r -> m r -> m r
-- 'catching_' :: 'MonadError' e m => 'Getter' e a -> m r -> m r -> m r
-- 'catching_' :: 'MonadError' e m => 'Fold' e a -> m r -> m r -> m r
-- 'catching_' :: 'MonadError' e m => t'Getter' e a -> m r -> m r -> m r
-- 'catching_' :: 'MonadError' e m => t'Fold' e a -> m r -> m r -> m r
-- @
catching_ :: MonadError e m => Getting (M.First a) e a -> m r -> m r -> m r
catching_ l a b = catchJust (preview l) a (const b)
Expand All @@ -87,8 +87,8 @@ catching_ l a b = catchJust (preview l) a (const b)
-- 'handling' :: 'MonadError' e m => 'Lens'' e a -> (a -> m r) -> m r -> m r
-- 'handling' :: 'MonadError' e m => 'Traversal'' e a -> (a -> m r) -> m r -> m r
-- 'handling' :: 'MonadError' e m => 'Iso'' e a -> (a -> m r) -> m r -> m r
-- 'handling' :: 'MonadError' e m => 'Fold' e a -> (a -> m r) -> m r -> m r
-- 'handling' :: 'MonadError' e m => 'Getter' e a -> (a -> m r) -> m r -> m r
-- 'handling' :: 'MonadError' e m => t'Fold' e a -> (a -> m r) -> m r -> m r
-- 'handling' :: 'MonadError' e m => t'Getter' e a -> (a -> m r) -> m r -> m r
-- @
handling :: MonadError e m => Getting (M.First a) e a -> (a -> m r) -> m r -> m r
handling l = flip (catching l)
Expand All @@ -102,8 +102,8 @@ handling l = flip (catching l)
-- 'handling_' :: 'MonadError' e m => 'Lens'' e a -> m r -> m r -> m r
-- 'handling_' :: 'MonadError' e m => 'Traversal'' e a -> m r -> m r -> m r
-- 'handling_' :: 'MonadError' e m => 'Iso'' e a -> m r -> m r -> m r
-- 'handling_' :: 'MonadError' e m => 'Getter' e a -> m r -> m r -> m r
-- 'handling_' :: 'MonadError' e m => 'Fold' e a -> m r -> m r -> m r
-- 'handling_' :: 'MonadError' e m => t'Getter' e a -> m r -> m r -> m r
-- 'handling_' :: 'MonadError' e m => t'Fold' e a -> m r -> m r -> m r
-- @
handling_ :: MonadError e m => Getting (M.First a) e a -> m r -> m r -> m r
handling_ l = flip (catching_ l)
Expand All @@ -113,16 +113,16 @@ handling_ l = flip (catching_ l)
-- Trying
------------------------------------------------------------------------------

-- | 'trying' takes a 'Prism' (or any 'Getter') to select which exceptions are caught
-- If the 'Exception' does not match the predicate, it is re-thrown.
-- | 'trying' takes a t'Prism' (or any t'Getter') to select which exceptions are caught
-- If the exception does not match the predicate, it is re-thrown.
--
-- @
-- 'trying' :: 'MonadError' e m => 'Prism'' e a -> m r -> m ('Either' a r)
-- 'trying' :: 'MonadError' e m => 'Lens'' e a -> m r -> m ('Either' a r)
-- 'trying' :: 'MonadError' e m => 'Traversal'' e a -> m r -> m ('Either' a r)
-- 'trying' :: 'MonadError' e m => 'Iso'' e a -> m r -> m ('Either' a r)
-- 'trying' :: 'MonadError' e m => 'Getter' e a -> m r -> m ('Either' a r)
-- 'trying' :: 'MonadError' e m => 'Fold' e a -> m r -> m ('Either' a r)
-- 'trying' :: 'MonadError' e m => t'Getter' e a -> m r -> m ('Either' a r)
-- 'trying' :: 'MonadError' e m => t'Fold' e a -> m r -> m ('Either' a r)
-- @
trying :: MonadError e m => Getting (M.First a) e a -> m r -> m (Either a r)
trying l m = catching l (liftM Right m) (return . Left)
Expand Down Expand Up @@ -206,7 +206,7 @@ instance Handleable e m (Handler e m) where
-- Throwing
------------------------------------------------------------------------------

-- | Throw an 'Exception' described by a 'Prism'.
-- | Throw an exception described by a t'Prism'.
--
-- @'throwing' l ≡ 'reviews' l 'throwError'@
--
Expand Down
Loading

0 comments on commit 4056ccf

Please sign in to comment.