| Copyright | (C) 2012-14 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | experimental | 
| Portability | LiberalTypeSynonyms | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell98 | 
Data.Bits.Lens
Description
- (.|.~) :: 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
- bitAt :: Bits b => Int -> IndexedLens' Int b Bool
- bits :: (Num b, Bits b) => IndexedTraversal' Int b Bool
- byteAt :: (Integral b, Bits b) => Int -> IndexedLens' Int b Word8
- bytewise :: (Integral b, Bits b) => IndexedTraversal' Int b Word8
Documentation
(<.|.~) :: Bits a => LensLike ((,) a) s t a a -> a -> s -> (a, t) infixr 4 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,Monoida) =>Traversals 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 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,Monoida) =>Traversals 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', Setter or Traversal 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 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) =>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
bytewise :: (Integral b, Bits b) => IndexedTraversal' Int b Word8 Source
Traverse over all the bytes in an integral type, from the low end.
The byte position is available as the index.
>>>toListOf bytewise (1312301580 :: Word32)[12,34,56,78]
If you supply this an Integer, the result will be an infinite Traversal,
 which can be productively consumed, but not reassembled.
Why is'nt this function called bytes to match bits? Alas, there
 is already a function by that name in Data.ByteString.Lens.