lens-5.2.3: Lenses, Folds and Traversals
Copyright(C) 2012-16 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
PortabilityLiberalTypeSynonyms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Bits.Lens

Description

 
Synopsis

Documentation

(.|.~) :: Bits a => ASetter s t a a -> a -> s -> t infixr 4 Source #

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 -> t infixr 4 Source #

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) 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))
(<.|.~) :: 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) 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))
(<.&.~) :: 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) infixr 4 Source #

Bitwise .|. the target(s) of a Lens or Traversal, 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))
(<<.|.~) ::  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) infixr 4 Source #

Bitwise .&. the target(s) of a Lens or Traversal, 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))
(<<.&.~) ::  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)

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

bitAt :: Bits b => Int -> IndexedLens' Int b Bool Source #

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 Bool Source #

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 Word8 Source #

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

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 isn't this function called bytes to match bits? Alas, there is already a function by that name in Data.ByteString.Lens.