planet-mitchell-0.1.0: Planet Mitchell

Safe HaskellNone
LanguageHaskell2010

Optic.Prism

Contents

Synopsis

Prism

type Prism s t a b = forall (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a (f b) -> p s (f t) #

A Prism l is a Traversal that can also be turned around with re to obtain a Getter in the opposite direction.

There are two laws that a Prism should satisfy:

First, if I re or review a value with a Prism and then preview or use (^?), I will get it back:

preview l (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 by l and a:

If preview l s ≡ Just a then review l a ≡ s

These two laws imply that the Traversal laws hold for every Prism and that we traverse at most 1 element:

lengthOf l x <= 1

It may help to think of this as a Iso that can be partial in one direction.

Every Prism is a valid Traversal.

Every Iso is a valid Prism.

For example, you might have a Prism' Integer Natural allows you to always go from a Natural to an Integer, and provide you with tools to check if an Integer is a Natural and/or to edit one if it is.

nat :: Prism' Integer Natural
nat = prism toInteger $ \ i ->
   if i < 0
   then Left i
   else Right (fromInteger i)

Now we can ask if an Integer is a Natural.

>>> 5^?nat
Just 5
>>> (-5)^?nat
Nothing

We can update the ones that are:

>>> (-3,4) & both.nat *~ 2
(-3,8)

And we can then convert from a Natural to an Integer.

>>> 5 ^. re nat -- :: Natural
5

Similarly we can use a Prism to traverse the Left half of an Either:

>>> Left "hello" & _Left %~ length
Left 5

or to construct an Either:

>>> 5^.re _Left
Left 5

such that if you query it with the Prism, you will get your original input back.

>>> 5^.re _Left ^? _Left
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.

Note: Composition with a Prism is index-preserving.

type Prism' s a = Prism s s a a #

prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b #

Build a Prism.

Either t a is used instead of Maybe a to permit the types of s and t to differ.

prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b #

This is usually used to build a Prism', when you have to use an operation like cast which already returns a Maybe.

is :: APrism s t a b -> s -> Bool #

Check to see if this Prism matches.

>>> is _Left (Right 12)
False
>>> is hex "3f79"
True

only :: Eq a => a -> Prism' a () #

This Prism compares for exact equality with a given value.

>>> only 4 # ()
4
>>> 5 ^? only 4
Nothing

AsAny

class AsAny (sel :: k) a s | s sel k -> a where #

Sums that have generic prisms.

Minimal complete definition

_As

Methods

_As :: Prism s s a a #

A prism that projects a sum as identified by some selector. Currently supported selectors are constructor names and unique types. Compatible with the lens package's Prism type.

>>> dog ^? _As @"Dog"
Just (MkDog {name = "Shep", age = 3})
>>> dog ^? _As @Dog
Just (MkDog {name = "Shep", age = 3})
>>> dog ^? _As @"Cat"
Nothing
>>> cat ^? _As @(Name, Age)
Just ("Mog",5)
>>> cat ^? _As @"Cat"
Just ("Mog",5)
>>> _As @"Cat" # ("Garfield", 6) :: Animal
Cat "Garfield" 6
>>> duck ^? _As @Age
Just 2
Instances
AsConstructor ctor s s a a => AsAny (ctor :: Symbol) a s 
Instance details

Defined in Data.Generics.Sum.Any

Methods

_As :: Prism s s a a #

AsType a s => AsAny (a :: *) a s 
Instance details

Defined in Data.Generics.Sum.Any

Methods

_As :: Prism s s a a #

AsSubtype

class AsSubtype sub sup where #

Structural subtyping between sums. A sum Sub is a subtype of another sum Sup if a value of Sub can be given (modulo naming of constructors) whenever a value of Sup is expected. In the running example for instance, FourLeggedAnimal is a subtype of Animal since a value of the former can be given as a value of the latter (renaming Dog4 to Dog and Cat4 to Cat).

Minimal complete definition

injectSub, projectSub | _Sub

Methods

_Sub :: Prism' sup sub #

A prism that captures structural subtyping. Allows a substructure to be injected (upcast) into a superstructure or a superstructure to be downcast into a substructure (which may fail).

>>> _Sub # dog4 :: Animal
Dog (MkDog {name = "Snowy", age = 4})
>>> cat ^? _Sub :: Maybe FourLeggedAnimal
Just (Cat4 "Mog" 5)
>>> duck ^? _Sub :: Maybe FourLeggedAnimal
Nothing
Instances
(Generic sub, Generic sup, GAsSubtype (Rep sub) (Rep sup)) => AsSubtype sub sup 
Instance details

Defined in Data.Generics.Sum.Subtype

Methods

_Sub :: Prism' sup sub #

injectSub :: sub -> sup #

projectSub :: sup -> Maybe sub #

AsSubtype a Void 
Instance details

Defined in Data.Generics.Sum.Subtype

Methods

_Sub :: Prism' Void a #

injectSub :: a -> Void #

projectSub :: Void -> Maybe a #

AsSubtype Void a 
Instance details

Defined in Data.Generics.Sum.Subtype

Methods

_Sub :: Prism' a Void #

injectSub :: Void -> a #

projectSub :: a -> Maybe Void #

Cons

class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where #

This class provides a way to attach or detach elements on the left side of a structure in a flexible manner.

Minimal complete definition

_Cons

Methods

_Cons :: Prism s t (a, s) (b, t) #

_Cons :: Prism [a] [b] (a, [a]) (b, [b])
_Cons :: Prism (Seq a) (Seq b) (a, Seq a) (b, Seq b)
_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
_Cons :: Prism' String (Char, String)
_Cons :: Prism' Text (Char, Text)
_Cons :: Prism' ByteString (Word8, ByteString)
Instances
Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Cons Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Cons Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Cons [a] [b] a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism [a] [b] (a, [a]) (b, [b]) #

Cons (ZipList a) (ZipList b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (ZipList a) (ZipList b) (a, ZipList a) (b, ZipList b) #

Cons (Seq a) (Seq b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Seq a) (Seq b) (a, Seq a) (b, Seq b) #

(Prim a, Prim b) => Cons (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(Storable a, Storable b) => Cons (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(Unbox a, Unbox b) => Cons (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

Cons (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b) #

(<|) :: Cons s s a a => a -> s -> s infixr 5 #

cons an element onto a container.

This is an infix alias for cons.

>>> a <| []
[a]
>>> a <| [b, c]
[a,b,c]
>>> a <| Seq.fromList []
fromList [a]
>>> a <| Seq.fromList [b, c]
fromList [a,b,c]

cons :: Cons s s a a => a -> s -> s infixr 5 #

cons an element onto a container.

>>> cons a []
[a]
>>> cons a [b, c]
[a,b,c]
>>> cons a (Seq.fromList [])
fromList [a]
>>> cons a (Seq.fromList [b, c])
fromList [a,b,c]

uncons :: Cons s s a a => s -> Maybe (a, s) #

Attempt to extract the left-most element from a container, and a version of the container without that element.

>>> uncons []
Nothing
>>> uncons [a, b, c]
Just (a,[b,c])

_head :: Cons s s a a => Traversal' s a #

A Traversal reading and writing to the head of a non-empty container.

>>> [a,b,c]^? _head
Just a
>>> [a,b,c] & _head .~ d
[d,b,c]
>>> [a,b,c] & _head %~ f
[f a,b,c]
>>> [] & _head %~ f
[]
>>> [1,2,3]^?!_head
1
>>> []^?_head
Nothing
>>> [1,2]^?_head
Just 1
>>> [] & _head .~ 1
[]
>>> [0] & _head .~ 2
[2]
>>> [0,1] & _head .~ 2
[2,1]

This isn't limited to lists.

For instance you can also traverse the head of a Seq:

>>> Seq.fromList [a,b,c,d] & _head %~ f
fromList [f a,b,c,d]
>>> Seq.fromList [] ^? _head
Nothing
>>> Seq.fromList [a,b,c,d] ^? _head
Just a
_head :: Traversal' [a] a
_head :: Traversal' (Seq a) a
_head :: Traversal' (Vector a) a

_tail :: Cons s s a a => Traversal' s s #

A Traversal reading and writing to the tail of a non-empty container.

>>> [a,b] & _tail .~ [c,d,e]
[a,c,d,e]
>>> [] & _tail .~ [a,b]
[]
>>> [a,b,c,d,e] & _tail.traverse %~ f
[a,f b,f c,f d,f e]
>>> [1,2] & _tail .~ [3,4,5]
[1,3,4,5]
>>> [] & _tail .~ [1,2]
[]
>>> [a,b,c]^?_tail
Just [b,c]
>>> [1,2]^?!_tail
[2]
>>> "hello"^._tail
"ello"
>>> ""^._tail
""

This isn't limited to lists. For instance you can also traverse the tail of a Seq.

>>> Seq.fromList [a,b] & _tail .~ Seq.fromList [c,d,e]
fromList [a,c,d,e]
>>> Seq.fromList [a,b,c] ^? _tail
Just (fromList [b,c])
>>> Seq.fromList [] ^? _tail
Nothing
_tail :: Traversal' [a] [a]
_tail :: Traversal' (Seq a) (Seq a)
_tail :: Traversal' (Vector a) (Vector a)

pattern (:<) :: forall b a. Cons b b a a => a -> b -> b infixr 5 #

Snoc

class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where #

This class provides a way to attach or detach elements on the right side of a structure in a flexible manner.

Minimal complete definition

_Snoc

Methods

_Snoc :: Prism s t (s, a) (t, b) #

_Snoc :: Prism [a] [b] ([a], a) ([b], b)
_Snoc :: Prism (Seq a) (Seq b) (Seq a, a) (Seq b, b)
_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b)
_Snoc :: Prism' String (String, Char)
_Snoc :: Prism' Text (Text, Char)
_Snoc :: Prism' ByteString (ByteString, Word8)
Instances
Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Snoc Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

Snoc [a] [b] a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism [a] [b] ([a], a) ([b], b) #

Snoc (ZipList a) (ZipList b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (ZipList a) (ZipList b) (ZipList a, a) (ZipList b, b) #

Snoc (Seq a) (Seq b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Seq a) (Seq b) (Seq a, a) (Seq b, b) #

(Prim a, Prim b) => Snoc (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(Storable a, Storable b) => Snoc (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(Unbox a, Unbox b) => Snoc (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

Snoc (Vector a) (Vector b) a b 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism (Vector a) (Vector b) (Vector a, a) (Vector b, b) #

(|>) :: Snoc s s a a => s -> a -> s infixl 5 #

snoc an element onto the end of a container.

This is an infix alias for snoc.

>>> Seq.fromList [] |> a
fromList [a]
>>> Seq.fromList [b, c] |> a
fromList [b,c,a]
>>> LazyT.pack "hello" |> '!'
"hello!"

snoc :: Snoc s s a a => s -> a -> s infixl 5 #

snoc an element onto the end of a container.

>>> snoc (Seq.fromList []) a
fromList [a]
>>> snoc (Seq.fromList [b, c]) a
fromList [b,c,a]
>>> snoc (LazyT.pack "hello") '!'
"hello!"

unsnoc :: Snoc s s a a => s -> Maybe (s, a) #

Attempt to extract the right-most element from a container, and a version of the container without that element.

>>> unsnoc (LazyT.pack "hello!")
Just ("hello",'!')
>>> unsnoc (LazyT.pack "")
Nothing
>>> unsnoc (Seq.fromList [b,c,a])
Just (fromList [b,c],a)
>>> unsnoc (Seq.fromList [])
Nothing

_init :: Snoc s s a a => Traversal' s s #

A Traversal reading and replacing all but the a last element of a non-empty container.

>>> [a,b,c,d]^?_init
Just [a,b,c]
>>> []^?_init
Nothing
>>> [a,b] & _init .~ [c,d,e]
[c,d,e,b]
>>> [] & _init .~ [a,b]
[]
>>> [a,b,c,d] & _init.traverse %~ f
[f a,f b,f c,d]
>>> [1,2,3]^?_init
Just [1,2]
>>> [1,2,3,4]^?!_init
[1,2,3]
>>> "hello"^._init
"hell"
>>> ""^._init
""
_init :: Traversal' [a] [a]
_init :: Traversal' (Seq a) (Seq a)
_init :: Traversal' (Vector a) (Vector a)

_last :: Snoc s s a a => Traversal' s a #

A Traversal reading and writing to the last element of a non-empty container.

>>> [a,b,c]^?!_last
c
>>> []^?_last
Nothing
>>> [a,b,c] & _last %~ f
[a,b,f c]
>>> [1,2]^?_last
Just 2
>>> [] & _last .~ 1
[]
>>> [0] & _last .~ 2
[2]
>>> [0,1] & _last .~ 2
[0,2]

This Traversal is not limited to lists, however. We can also work with other containers, such as a Vector.

>>> Vector.fromList "abcde" ^? _last
Just 'e'
>>> Vector.empty ^? _last
Nothing
>>> (Vector.fromList "abcde" & _last .~ 'Q') == Vector.fromList "abcdQ"
True
_last :: Traversal' [a] a
_last :: Traversal' (Seq a) a
_last :: Traversal' (Vector a) a

pattern (:>) :: forall a b. Snoc a a b b => a -> b -> a infixl 5 #

Empty

class AsEmpty a where #

Methods

_Empty :: Prism' a () #

>>> isn't _Empty [1,2,3]
True
Instances
AsEmpty Ordering 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Ordering () #

AsEmpty () 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' () () #

AsEmpty ByteString 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' ByteString () #

AsEmpty ByteString 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' ByteString () #

AsEmpty Text 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Text () #

AsEmpty Text 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Text () #

AsEmpty Event 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Event () #

AsEmpty All 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' All () #

AsEmpty Any 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Any () #

AsEmpty IntSet 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' IntSet () #

AsEmpty [a] 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' [a] () #

AsEmpty (Maybe a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Maybe a) () #

AsEmpty (ZipList a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (ZipList a) () #

AsEmpty (First a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (First a) () #

AsEmpty (Last a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Last a) () #

AsEmpty a => AsEmpty (Dual a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Dual a) () #

(Eq a, Num a) => AsEmpty (Sum a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Sum a) () #

(Eq a, Num a) => AsEmpty (Product a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Product a) () #

AsEmpty (IntMap a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (IntMap a) () #

AsEmpty (Seq a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Seq a) () #

AsEmpty (Set a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Set a) () #

Storable a => AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

Unbox a => AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

AsEmpty (HashSet a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (HashSet a) () #

AsEmpty (Vector a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Vector a) () #

(AsEmpty a, AsEmpty b) => AsEmpty (a, b) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (a, b) () #

AsEmpty (HashMap k a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (HashMap k a) () #

AsEmpty (Map k a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (Map k a) () #

(AsEmpty a, AsEmpty b, AsEmpty c) => AsEmpty (a, b, c) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (a, b, c) () #

pattern Empty :: forall s. AsEmpty s => s #