| Portability | LiberalTypeSynonyms | 
|---|---|
| Stability | experimental | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Safe-Inferred | 
Data.Bits.Lens
Description
- (.|.~) :: Bits a => Setting s t a a -> a -> s -> t
 - (.&.~) :: Bits a => Setting 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)
 - (.|.=) :: (MonadState s m, Bits a) => Simple Setting s a -> a -> m ()
 - (.&.=) :: (MonadState s m, Bits a) => Simple Setting s a -> a -> m ()
 - (<.|.=) :: (MonadState s m, Bits a) => SimpleLensLike ((,) a) s a -> a -> m a
 - (<.&.=) :: (MonadState s m, Bits a) => SimpleLensLike ((,) a) s a -> a -> m a
 - bitAt :: Bits b => Int -> SimpleIndexedLens Int b Bool
 - bits :: (Num b, Bits b) => SimpleIndexedTraversal Int b Bool
 
Documentation
(<.|.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t)Source
Bitwise .|. the target(s) of a Lens (or Traversal), returning the result
 (or a monoidal summary of all of the results).
>>>_2 <.|.~ 6 $ ("hello",3)(7,("hello",7))
(<.|.~) ::Bitsa =>Isos t a a -> a -> s -> (a, t) (<.|.~) ::Bitsa =>Lenss t a a -> a -> s -> (a, t) (<.|.~) :: (Bitsa, 'Monoid a) =>Traversals t a a -> a -> s -> (a, t)
(<.&.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t)Source
Bitwise .&. the target(s) of a Lens or Traversal, returning the result
 (or a monoidal summary of all of the results).
>>>_2 <.&.~ 7 $ ("hello",254)(6,("hello",6))
(<.&.~) ::Bitsa =>Isos t a a -> a -> s -> (a, t) (<.&.~) ::Bitsa =>Lenss t a a -> a -> s -> (a, t) (<.&.~) :: (Bitsa, 'Monoid a) =>Traversals t a a -> a -> s -> (a, t)
(.|.=) :: (MonadState s m, Bits a) => Simple Setting s a -> a -> m ()Source
Modify the target(s) of a Simple Lens, Setter or Traversal by computing its bitwise .|. with another value.
>>>execState (do _1 .|.= 15; _2 .|.= 3) (7,7)(15,7)
(.|.=) :: (MonadStates m,Bitsa) =>SimpleSetters a -> a -> m () (.|.=) :: (MonadStates m,Bitsa) =>SimpleIsos a -> a -> m () (.|.=) :: (MonadStates m,Bitsa) =>SimpleLenss a -> a -> m () (.|.=) :: (MonadStates m,Bitsa) =>SimpleTraversals a -> a -> m ()
(.&.=) :: (MonadState s m, Bits a) => Simple Setting s a -> a -> m ()Source
Modify the target(s) of a Simple Lens, Setter or Traversal by computing its bitwise .&. with another value.
>>>execState (do _1 .&.= 15; _2 .&.= 3) (7,7)(7,3)
(.&.=) :: (MonadStates m,Bitsa) =>SimpleSetters a -> a -> m () (.&.=) :: (MonadStates m,Bitsa) =>SimpleIsos a -> a -> m () (.&.=) :: (MonadStates m,Bitsa) =>SimpleLenss a -> a -> m () (.&.=) :: (MonadStates m,Bitsa) =>SimpleTraversals a -> a -> m ()
(<.|.=) :: (MonadState s m, Bits a) => SimpleLensLike ((,) a) s a -> a -> m aSource
Modify the target(s) of a Simple 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 <.|.= 7) (28,0)(31,(31,0))
(<.|.=) :: (MonadStates m,Bitsa) =>SimpleLenss a -> a -> m a (<.|.=) :: (MonadStates m,Bitsa,Monoida) =>SimpleTraversals a -> a -> m a
(<.&.=) :: (MonadState s m, Bits a) => SimpleLensLike ((,) a) s a -> a -> m aSource
Modify the target(s) of a Simple 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) =>SimpleLenss a -> a -> m a (<.&.=) :: (MonadStates m,Bitsa,Monoida) =>SimpleTraversals a -> a -> m a