nat-optics-1.0.0.3: Refinement types for natural numbers with an optics interface
Safe HaskellTrustworthy
LanguageHaskell2010

NatOptics.NonNegative

Synopsis

Type constructor

data NonNegative number Source #

Instances

Instances details
Show number => Show (NonNegative number) Source # 
Instance details

Defined in NatOptics.NonNegative.Unsafe

Methods

showsPrec :: Int -> NonNegative number -> ShowS #

show :: NonNegative number -> String #

showList :: [NonNegative number] -> ShowS #

Eq number => Eq (NonNegative number) Source # 
Instance details

Defined in NatOptics.NonNegative.Unsafe

Methods

(==) :: NonNegative number -> NonNegative number -> Bool #

(/=) :: NonNegative number -> NonNegative number -> Bool #

Ord number => Ord (NonNegative number) Source # 
Instance details

Defined in NatOptics.NonNegative.Unsafe

Methods

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 #

Optics

refine :: (Num n, Ord n) => Prism' n (NonNegative n) Source #

For any numeric type n, NonNegative n is a subset of n.

Examples:

natPrism :: (Integral n, Bits n) => Prism' Natural (NonNegative n) Source #

For any integral type n, NonNegative n is a subset of Natural.

intPrism :: (Integral n, Bits n) => Prism' Integer (NonNegative n) Source #

For any integral type n, NonNegative n is a subset of Integer.

Re-exports

data Natural #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Instances

Instances details
Bits Natural

Since: base-4.8.0

Instance details

Defined in Data.Bits

Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Ix Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Ix

Num Natural

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Real Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Eq Natural 
Instance details

Defined in GHC.Num.Natural

Methods

(==) :: Natural -> Natural -> Bool #

(/=) :: Natural -> Natural -> Bool #

Ord Natural 
Instance details

Defined in GHC.Num.Natural

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Natural -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Natural -> Code m Natural #

data Integer #

Arbitrary precision integers. In contrast with fixed-size integral types such as Int, the Integer type represents the entire infinite range of integers.

Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.

If the value is small (fit into an Int), IS constructor is used. Otherwise IP and IN constructors are used to store a BigNat representing respectively the positive or the negative value magnitude.

Invariant: IP and IN are used iff value doesn't fit in IS

Instances

Instances details
Bits Integer

Since: base-2.1

Instance details

Defined in Data.Bits

Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Ix Integer

Since: base-2.1

Instance details

Defined in GHC.Ix

Num Integer

Since: base-2.1

Instance details

Defined in GHC.Num

Read Integer

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Real Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Methods

(==) :: Integer -> Integer -> Bool #

(/=) :: Integer -> Integer -> Bool #

Ord Integer 
Instance details

Defined in GHC.Num.Integer

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Integer -> Code m Integer #

type Prism' s a = Optic' A_Prism NoIx s a #

Type synonym for a type-preserving prism.

type Iso' s a = Optic' An_Iso NoIx s a #

Type synonym for a type-preserving iso.

view :: forall k (is :: IxList) s a. Is k A_Getter => Optic' k is s a -> s -> a #

View the value pointed to by a getter.

If you want to view a type-modifying optic that is insufficiently polymorphic to be type-preserving, use getting.

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