Navigation Menu

Skip to content

Commit

Permalink
haddocks cosmetics in Prism, Reified, Type
Browse files Browse the repository at this point in the history
  • Loading branch information
basdirks committed Jan 8, 2013
1 parent a961e01 commit 215d32b
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 24 deletions.
15 changes: 7 additions & 8 deletions src/Control/Lens/Prism.hs
Expand Up @@ -55,13 +55,12 @@ import Unsafe.Coerce
-- Prism Internals
------------------------------------------------------------------------------


-- | If you see this in a signature for a function, the function is expecting a 'Prism'.
type APrism s t a b = Market a b a (Mutator b) -> Market a b s (Mutator t)

type APrism' s a = APrism s s a a

-- | Safely decompose 'APrism'
-- | Safely decompose 'APrism'.
runPrism :: APrism s t a b -> (b -> t, s -> Either t a)
#ifdef SAFE
runPrism k = case runMarket (k (Market (Mutator, Right))) of
Expand All @@ -73,7 +72,7 @@ runPrism k = unsafeCoerce (runMarket (k (Market (Mutator, Right))))

-- | Clone a 'Prism' so that you can reuse the same monomorphically typed 'Prism' for different purposes.
--
-- See 'cloneLens' and 'cloneTraversal' for examples of why you might want to do this.
-- See 'Control.Lens.Lens.cloneLens' and 'Control.Lens.Traversal.cloneTraversal' for examples of why you might want to do this.
clonePrism :: APrism s t a b -> Prism s t a b
clonePrism k = case runPrism k of
(bt, sa) -> prism bt sa
Expand Down Expand Up @@ -111,9 +110,9 @@ aside k = case runPrism k of
Right a -> Right (e,a)
{-# INLINE aside #-}

-- | Given a pair of prisms, project sums.
-- | Given a pair of 'Prism's, project sums.
--
-- Viewing a 'Prism' as a co-lens, this combinator can be seen to be dual to 'alongside'.
-- Viewing a 'Prism' as a co-'Lens', this combinator can be seen to be dual to 'Control.Lens.Lens.alongside'.
without :: APrism s t a b
-> APrism u v c d
-> Prism (Either s u) (Either t v) (Either a c) (Either b d)
Expand All @@ -128,7 +127,7 @@ without k = case runPrism k of
-- Common Prisms
------------------------------------------------------------------------------

-- | This prism provides a traversal for tweaking the left-hand value of an 'Either':
-- | This 'Prism' provides a traversal for tweaking the left-hand value of an 'Either':
--
-- >>> over _left (+1) (Left 2)
-- Left 3
Expand All @@ -150,7 +149,7 @@ _left :: Prism (Either a c) (Either b c) a b
_left = prism Left $ either Right (Left . Right)
{-# INLINE _left #-}

-- | This prism provides a traversal for tweaking the right-hand value of an 'Either':
-- | This 'Prism' provides a traversal for tweaking the right-hand value of an 'Either':
--
-- >>> over _right (+1) (Left 2)
-- Left 2
Expand All @@ -172,7 +171,7 @@ _right :: Prism (Either c a) (Either c b) a b
_right = prism Right $ either (Left . Left) Right
{-# INLINE _right #-}

-- | This prism provides a traversal for tweaking the target of the value of 'Just' in a 'Maybe'.
-- | This 'Prism' provides a traversal for tweaking the target of the value of 'Just' in a 'Maybe'.
--
-- >>> over _just (+1) (Just 2)
-- Just 3
Expand Down
20 changes: 10 additions & 10 deletions src/Control/Lens/Reified.hs
Expand Up @@ -17,19 +17,19 @@ import Control.Lens.Type
-- Reifying
------------------------------------------------------------------------------

-- | Useful for storing lenses in containers.
-- | Reify a 'Lens' so it can be stored safely in a container.
newtype ReifiedLens s t a b = ReifyLens { reflectLens :: Lens s t a b }

-- | @type 'ReifiedLens'' = 'Simple' 'ReifiedLens'@
type ReifiedLens' s a = ReifiedLens s s a a

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

-- | @type 'ReifiedIndexedLens'' i = 'Simple' ('ReifiedIndexedLens' i)@
type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a

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

-- | @type 'ReifiedIndexedTraversal'' i = 'Simple' ('ReifiedIndexedTraversal' i)@
Expand All @@ -41,35 +41,35 @@ data ReifiedTraversal s t a b = ReifyTraversal { reflectTraversal :: Traversal s
-- | @type 'ReifiedTraversal'' = 'Simple' 'ReifiedTraversal'@
type ReifiedTraversal' s a = ReifiedTraversal s s a a

-- | Useful for storing getters in containers.
-- | Reify a 'Getter' so it can be stored safely in a container.
newtype ReifiedGetter s a = ReifyGetter { reflectGetter :: Getter s a }

-- | Useful for storage.
-- | Reify an 'IndexedGetter' so it can be stored safely in a container.
newtype ReifiedIndexedGetter i s a = ReifyIndexedGetter { reflectIndexedGetter :: IndexedGetter i s a }

-- | Useful for storing folds in containers.
-- | Reify a 'Fold' so it can be stored safely in a container.
newtype ReifiedFold s a = ReifyFold { reflectFold :: Fold s a }

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

-- | @type 'ReifiedSetter'' = 'Simple' 'ReifiedSetter'@
type ReifiedSetter' s a = ReifiedSetter s s a a

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

-- | @type 'ReifiedIndexedSetter'' i = 'Simple' ('ReifiedIndexedSetter' i)@
type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a

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

-- | @type 'ReifiedIso'' = 'Simple' 'ReifiedIso'@
type ReifiedIso' s a = ReifiedIso s s a a

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

-- | @type 'ReifiedPrism'' = 'Simple' 'ReifiedPrism'@
Expand Down
13 changes: 7 additions & 6 deletions src/Control/Lens/Type.hs
Expand Up @@ -266,16 +266,17 @@ type Iso' s a = Iso s s a a
-- Prism Internals
------------------------------------------------------------------------------

-- | A 'Prism' @l@ is a 0-or-1 target 'Traversal' that can also be turned around with 'remit' to
-- obtain a 'Getter' in the opposite direction.
-- | A 'Prism' @l@ is a 0-or-1 target 'Traversal' that can also be turned
-- around with 'Control.Lens.Review.remit' to obtain a 'Getter' in the
-- opposite direction.
--
-- There are two laws that a 'Prism' should satisfy:
--
-- First, if I 'remit' or 'Control.Lens.Prism.review' a value with a 'Prism' and then 'Control.Lens.Prism.preview' or use ('^?'), I will get it back:
-- First, if I 'Control.Lens.Review.remit' or 'Control.Lens.Prism.review' a value with a 'Prism' and then 'Control.Lens.Prism.preview' or use ('Control.Lens.Fold.^?'), I will get it back:
--
-- * @'Control.Lens.Prism.preview' l ('Control.Lens.Prism.review' l b) ≡ 'Just' b@
--
-- Second, if you can extract a value @a@ using a Prism @l@ from a value @s@, then the value @s@ is completely described my @l@ and @a@:
-- Second, if you can extract a value @a@ using a 'Prism' @l@ from a value @s@, then the value @s@ is completely described my @l@ and @a@:
--
-- * If @'Control.Lens.Prism.preview' l s ≡ 'Just' a@ then @'Control.Lens.Prism.review' l a ≡ s@
--
Expand Down Expand Up @@ -336,12 +337,12 @@ type Iso' s a = Iso s s a a
-- Just 5
--
-- Another interesting way to think of a 'Prism' is as the categorical dual of a 'Lens'
-- -- a /co/-'Lens', so to speak. This is what permits the construction of 'outside'.
-- -- a /co/-'Lens', so to speak. This is what permits the construction of 'Control.Lens.Prism.outside'.
--
-- Note: Composition with a 'Prism' is index-preserving.
type Prism s t a b = forall p f. (Prismatic p, Applicative f) => p a (f b) -> p s (f t)

-- | A 'Simple' 'Prism'
-- | A 'Simple' 'Prism'.
type Prism' s a = Prism s s a a

-------------------------------------------------------------------------------
Expand Down

0 comments on commit 215d32b

Please sign in to comment.