| Copyright | (C) 2012-16 Edward Kmett |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | LiberalTypeSynonyms |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Bits.Lens
Description
Synopsis
- (.|.~) :: Bits a => ASetter s t a a -> a -> s -> t
- (.&.~) :: Bits a => ASetter s t a a -> a -> s -> t
- (<.|.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<.&.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<<.|.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)
- (<<.&.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)
- (.|.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m ()
- (.&.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m ()
- (<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a
- (<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a
- (<<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a
- (<<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a
Documentation
(.|.~) :: Bits a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Bitwise .|. the target(s) of a ReifiedLens or ReifiedSetter.
>>>_2 .|.~ 6 $ ("hello",3)("hello",7)
(.|.~) ::Bitsa =>ReifiedSetters t a a -> a -> s -> t (.|.~) ::Bitsa =>ReifiedIsos t a a -> a -> s -> t (.|.~) ::Bitsa =>ReifiedLenss t a a -> a -> s -> t (.|.~) :: (Monoida,Bitsa) =>ReifiedTraversals t a a -> a -> s -> t
(.&.~) :: Bits a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Bitwise .&. the target(s) of a ReifiedLens or ReifiedSetter.
>>>_2 .&.~ 7 $ ("hello",254)("hello",6)
(.&.~) ::Bitsa =>ReifiedSetters t a a -> a -> s -> t (.&.~) ::Bitsa =>ReifiedIsos t a a -> a -> s -> t (.&.~) ::Bitsa =>ReifiedLenss t a a -> a -> s -> t (.&.~) :: (Monoida,Bitsa) =>ReifiedTraversals t a a -> a -> s -> t
(<.|.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t) infixr 4 Source #
Bitwise .|. the target(s) of a ReifiedLens (or ReifiedTraversal), returning the result
(or a monoidal summary of all of the results).
>>>_2 <.|.~ 6 $ ("hello",3)(7,("hello",7))
(<.|.~) ::Bitsa =>ReifiedIsos t a a -> a -> s -> (a, t) (<.|.~) ::Bitsa =>ReifiedLenss t a a -> a -> s -> (a, t) (<.|.~) :: (Bitsa,Monoida) =>ReifiedTraversals t a a -> a -> s -> (a, t)
(<.&.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t) infixr 4 Source #
Bitwise .&. the target(s) of a ReifiedLens or ReifiedTraversal, returning the result
(or a monoidal summary of all of the results).
>>>_2 <.&.~ 7 $ ("hello",254)(6,("hello",6))
(<.&.~) ::Bitsa =>ReifiedIsos t a a -> a -> s -> (a, t) (<.&.~) ::Bitsa =>ReifiedLenss t a a -> a -> s -> (a, t) (<.&.~) :: (Bitsa,Monoida) =>ReifiedTraversals t a a -> a -> s -> (a, t)
(<<.|.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) infixr 4 Source #
Bitwise .|. the target(s) of a ReifiedLens or ReifiedTraversal, and return the
original value, or a monoidal summary of the original values.
When you do not need the old value, (.|.~) is more flexible.
>>>_2 <<.|.~ 6 $ ("hello", 3)(3,("hello",7))
(<<.|.~) ::Bitsa =>ReifiedIsos t a a -> a -> s -> (a, t) (<<.|.~) ::Bitsa =>ReifiedLenss t a a -> a -> s -> (a, t) (<<.|.~) :: (Bitsa,Monoida) =>ReifiedTraversals t a a -> a -> s -> (a, t)
(<<.&.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) infixr 4 Source #
Bitwise .&. the target(s) of a ReifiedLens or ReifiedTraversal, and return the
original value, or a monoidal summary of the original values.
When you do not need the old value, (.&.~) is more flexible.
>>>_2 <<.&.~ 7 $ ("hello", 254)(254,("hello",6))
(<<.&.~) ::Bitsa =>ReifiedIsos t a a -> a -> s -> (a, t) (<<.&.~) ::Bitsa =>ReifiedLenss t a a -> a -> s -> (a, t) (<<.&.~) :: (Bitsa,Monoida) =>ReifiedTraversals t a a -> a -> s -> (a, t)
(.|.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m () infix 4 Source #
Modify the target(s) of a Lens', ReifiedSetter or ReifiedTraversal by computing its bitwise .|. with another value.
>>>execState (do _1 .|.= 15; _2 .|.= 3) (7,7)(15,7)
(.|.=) :: (MonadStates m,Bitsa) =>Setter's a -> a -> m () (.|.=) :: (MonadStates m,Bitsa) =>Iso's a -> a -> m () (.|.=) :: (MonadStates m,Bitsa) =>Lens's a -> a -> m () (.|.=) :: (MonadStates m,Bitsa) =>Traversal's a -> a -> m ()
(.&.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m () infix 4 Source #
Modify the target(s) of a Lens', Setter' or Traversal' by computing its bitwise .&. with another value.
>>>execState (do _1 .&.= 15; _2 .&.= 3) (7,7)(7,3)
(.&.=) :: (MonadStates m,Bitsa) =>Setter's a -> a -> m () (.&.=) :: (MonadStates m,Bitsa) =>Iso's a -> a -> m () (.&.=) :: (MonadStates m,Bitsa) =>Lens's a -> a -> m () (.&.=) :: (MonadStates m,Bitsa) =>Traversal's a -> a -> m ()
(<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source #
Modify the target(s) of a Lens', (or ReifiedTraversal) by computing its bitwise .|. with another value,
returning the result (or a monoidal summary of all of the results traversed).
>>>runState (_1 <.|.= 7) (28,0)(31,(31,0))
(<.|.=) :: (MonadStates m,Bitsa) =>Lens's a -> a -> m a (<.|.=) :: (MonadStates m,Bitsa,Monoida) =>Traversal's a -> a -> m a
(<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source #
Modify the target(s) of a Lens' (or Traversal') by computing its bitwise .&. with another value,
returning the result (or a monoidal summary of all of the results traversed).
>>>runState (_1 <.&.= 15) (31,0)(15,(15,0))
(<.&.=) :: (MonadStates m,Bitsa) =>Lens's a -> a -> m a (<.&.=) :: (MonadStates m,Bitsa,Monoida) =>Traversal's a -> a -> m a
(<<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source #
Modify the target(s) of a Lens', (or Traversal') by computing its
bitwise .|. with another value, returning the original value (or a
monoidal summary of all the original values).
When you do not need the old value, (.|.=) is more flexible.
>>>runState (_1 <<.|.= 7) (28,0)(28,(31,0))
(<<.|.=) :: (MonadStates m,Bitsa) =>Lens's a -> a -> m a (<<.|.=) :: (MonadStates m,Bitsa,Monoida) =>Traversal's a -> a -> m a
(<<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source #
Modify the target(s) of a Lens', (or Traversal') by computing its
bitwise .&. with another value, returning the original value (or a
monoidal summary of all the original values).
When you do not need the old value, (.&.=) is more flexible.
>>>runState (_1 <<.&.= 15) (31,0)(31,(15,0))
(<<.&.=) :: (MonadStates m,Bitsa) =>Lens's a -> a -> m a (<<.&.=) :: (MonadStates m,Bitsa,Monoida) =>Traversal's a -> a -> m a