Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data NonNegative number
- refine :: (Num n, Ord n) => Prism' n (NonNegative n)
- natPrism :: (Integral n, Bits n) => Prism' Natural (NonNegative n)
- intPrism :: (Integral n, Bits n) => Prism' Integer (NonNegative n)
- natIso :: Iso' Natural (NonNegative Natural)
- textPrism :: (Integral n, Bits n) => Prism' Text (NonNegative n)
- stringPrism :: (Integral n, Bits n) => Prism' String (NonNegative n)
- data Natural
- data Integer
- type Prism' s a = Optic' A_Prism NoIx s a
- type Iso' s a = Optic' An_Iso NoIx s a
- view :: forall k (is :: IxList) s a. Is k A_Getter => Optic' k is s a -> s -> a
- review :: forall k (is :: IxList) t b. Is k A_Review => Optic' k is t b -> b -> t
- preview :: forall k (is :: IxList) s a. Is k An_AffineFold => Optic' k is s a -> s -> Maybe a
Type constructor
data NonNegative number Source #
Instances
Eq number => Eq (NonNegative number) Source # | |
Defined in NatOptics.NonNegative (==) :: NonNegative number -> NonNegative number -> Bool # (/=) :: NonNegative number -> NonNegative number -> Bool # | |
Ord number => Ord (NonNegative number) Source # | |
Defined in NatOptics.NonNegative compare :: NonNegative number -> NonNegative number -> Ordering # (<) :: NonNegative number -> NonNegative number -> Bool # (<=) :: NonNegative number -> NonNegative number -> Bool # (>) :: NonNegative number -> NonNegative number -> Bool # (>=) :: NonNegative number -> NonNegative number -> Bool # max :: NonNegative number -> NonNegative number -> NonNegative number # min :: NonNegative number -> NonNegative number -> NonNegative number # | |
Show number => Show (NonNegative number) Source # | |
Defined in NatOptics.NonNegative showsPrec :: Int -> NonNegative number -> ShowS # show :: NonNegative number -> String # showList :: [NonNegative number] -> ShowS # |
Optics
natPrism :: (Integral n, Bits n) => Prism' Natural (NonNegative n) Source #
For any integral type n
,
is a subset of NonNegative
nNatural
.
intPrism :: (Integral n, Bits n) => Prism' Integer (NonNegative n) Source #
For any integral type n
,
is a subset of NonNegative
nInteger
.
natIso :: Iso' Natural (NonNegative Natural) Source #
Natural
and
are the same thing. NonNegative
Natural
stringPrism :: (Integral n, Bits n) => Prism' String (NonNegative n) Source #
Re-exports
Type representing arbitrary-precision non-negative integers.
>>>
2^100 :: Natural
1267650600228229401496703205376
Operations whose result would be negative
,throw
(Underflow
:: ArithException
)
>>>
-1 :: Natural
*** Exception: arithmetic underflow
Since: base-4.8.0.0
Instances
Arbitrary precision integers. In contrast with fixed-size integral types
such as Int
, the Integer
type represents the entire infinite range of
integers.
For more information about this type's representation, see the comments in its implementation.
Instances
Enum Integer | Since: base-2.1 |
Eq Integer | |
Integral Integer | Since: base-2.0.1 |
Defined in GHC.Real | |
Num Integer | Since: base-2.1 |
Ord Integer | |
Read Integer | Since: base-2.1 |
Real Integer | Since: base-2.0.1 |
Defined in GHC.Real toRational :: Integer -> Rational # | |
Show Integer | Since: base-2.1 |
Ix Integer | Since: base-2.1 |
Bits Integer | Since: base-2.1 |
Defined in Data.Bits (.&.) :: Integer -> Integer -> Integer # (.|.) :: Integer -> Integer -> Integer # xor :: Integer -> Integer -> Integer # complement :: Integer -> Integer # shift :: Integer -> Int -> Integer # rotate :: Integer -> Int -> Integer # setBit :: Integer -> Int -> Integer # clearBit :: Integer -> Int -> Integer # complementBit :: Integer -> Int -> Integer # testBit :: Integer -> Int -> Bool # bitSizeMaybe :: Integer -> Maybe Int # shiftL :: Integer -> Int -> Integer # unsafeShiftL :: Integer -> Int -> Integer # shiftR :: Integer -> Int -> Integer # unsafeShiftR :: Integer -> Int -> Integer # rotateL :: Integer -> Int -> Integer # |
review :: forall k (is :: IxList) t b. Is k A_Review => Optic' k is t b -> b -> t #
Retrieve the value targeted by a Review
.
>>>
review _Left "hi"
Left "hi"
preview :: forall k (is :: IxList) s a. Is k An_AffineFold => Optic' k is s a -> s -> Maybe a #
Retrieve the value targeted by an AffineFold
.
>>>
let _Right = prism Right $ either (Left . Left) Right
>>>
preview _Right (Right 'x')
Just 'x'
>>>
preview _Right (Left 'y')
Nothing