lens-4.0.7: Lenses, Folds and Traversals

PortabilityLiberalTypeSynonyms
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Data.Bits.Lens

Description

 

Synopsis

Documentation

(.|.~) :: Bits a => ASetter s t a a -> a -> s -> tSource

Bitwise .|. the target(s) of a Lens or Setter.

>>> _2 .|.~ 6 $ ("hello",3)
("hello",7)
 (.|.~) :: Bits a             => Setter s t a a    -> a -> s -> t
 (.|.~) :: Bits a             => Iso s t a a       -> a -> s -> t
 (.|.~) :: Bits a             => Lens s t a a      -> a -> s -> t
 (.|.~) :: (Monoid a, Bits a) => Traversal s t a a -> a -> s -> t

(.&.~) :: Bits a => ASetter s t a a -> a -> s -> tSource

Bitwise .&. the target(s) of a Lens or Setter.

>>> _2 .&.~ 7 $ ("hello",254)
("hello",6)
 (.&.~) :: Bits a             => Setter s t a a    -> a -> s -> t
 (.&.~) :: Bits a             => Iso s t a a       -> a -> s -> t
 (.&.~) :: Bits a             => Lens s t a a      -> a -> s -> t
 (.&.~) :: (Monoid a, Bits a) => Traversal s t a a -> a -> s -> 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 <.|.~ 6 $ ("hello",3)
(7,("hello",7))
 (<.|.~) :: Bits a             => Iso s t a a       -> a -> s -> (a, t)
 (<.|.~) :: Bits a             => Lens s t a a      -> a -> s -> (a, t)
 (<.|.~) :: (Bits a, Monoid a) => Traversal s 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))
 (<.&.~) :: Bits a             => Iso       s t a a -> a -> s -> (a, t)
 (<.&.~) :: Bits a             => Lens      s t a a -> a -> s -> (a, t)
 (<.&.~) :: (Bits a, Monoid a) => Traversal s t a a -> a -> s -> (a, t)

(<<.|.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)Source

(<<.&.~) :: Bits a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)Source

(.|.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m ()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)
 (.|.=) :: (MonadState s m, Bits a) => Setter' s a    -> a -> m ()
 (.|.=) :: (MonadState s m, Bits a) => Iso' s a       -> a -> m ()
 (.|.=) :: (MonadState s m, Bits a) => Lens' s a      -> a -> m ()
 (.|.=) :: (MonadState s m, Bits a) => Traversal' s a -> a -> m ()

(.&.=) :: (MonadState s m, Bits a) => ASetter' s a -> a -> m ()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)
 (.&.=) :: (MonadState s m, Bits a) => Setter' s a    -> a -> m ()
 (.&.=) :: (MonadState s m, Bits a) => Iso' s a       -> a -> m ()
 (.&.=) :: (MonadState s m, Bits a) => Lens' s a      -> a -> m ()
 (.&.=) :: (MonadState s m, Bits a) => Traversal' s a -> a -> m ()

(<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m aSource

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))
 (<.|.=) :: (MonadState s m, Bits a)           => Lens' s a      -> a -> m a
 (<.|.=) :: (MonadState s m, Bits a, Monoid a) => Traversal' s a -> a -> m a

(<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m aSource

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))
 (<.&.=) :: (MonadState s m, Bits a)           => Lens' s a      -> a -> m a
 (<.&.=) :: (MonadState s m, Bits a, Monoid a) => Traversal' s a -> a -> m a

(<<.|.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m aSource

(<<.&.=) :: (MonadState s m, Bits a) => LensLike' ((,) a) s a -> a -> m aSource

bitAt :: Bits b => Int -> IndexedLens' Int b BoolSource

This Lens can be used to access the value of the nth bit in a number.

bitAt n is only a legal Lens into b if 0 <= n < bitSize (undefined :: b).

>>> 16^.bitAt 4
True
>>> 15^.bitAt 4
False
>>> 15 & bitAt 4 .~ True
31
>>> 16 & bitAt 4 .~ False
0

bits :: (Num b, Bits b) => IndexedTraversal' Int b BoolSource

Traverse over all bits in a numeric type.

The bit position is available as the index.

>>> toListOf bits (5 :: Word8)
[True,False,True,False,False,False,False,False]

If you supply this an Integer, the result will be an infinite Traversal, which can be productively consumed, but not reassembled.

byteAt :: (Integral b, Bits b) => Int -> IndexedLens' Int b Word8Source

Get the nth byte, counting from the low end.

byteAt n is a legal Lens into b iff 0 <= n < div (bitSize (undefined :: b)) 8

>>> (0xff00 :: Word16)^.byteAt 0
0
>>> (0xff00 :: Word16)^.byteAt 1
255
>>> byteAt 1 .~ 0 $ 0xff00 :: Word16
0
>>> byteAt 0 .~ 0xff $ 0 :: Word16
255