plutus-ledger-api-1.40.0.0: Interface to the Plutus ledger for the Cardano ledger.
Safe HaskellSafe-Inferred
LanguageHaskell2010

PlutusLedgerApi.V1.Data.Interval

Description

A type for intervals and associated functions.

Synopsis

Documentation

data Interval a Source #

An interval of as.

The interval may be either closed or open at either end, meaning that the endpoints may or may not be included in the interval.

The interval can also be unbounded on either side.

The Eq instance gives equality of the intervals, not structural equality. There is no Ord instance, but contains gives a partial order.

Note that some of the functions on Interval rely on Enum in order to handle non-inclusive endpoints. For this reason, it may not be safe to use Intervals with non-inclusive endpoints on types whose Enum instances have partial methods.

Instances

Instances details
Lift DefaultUni (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

lift :: Interval a -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Generic (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Rep (Interval a) :: Type -> Type Source #

Methods

from :: Interval a -> Rep (Interval a) x Source #

to :: Rep (Interval a) x -> Interval a Source #

Show (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

NFData (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

rnf :: Interval a -> () Source #

(Enum a, Ord a, ToData a, UnsafeFromData a) => Eq (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(==) :: Interval a -> Interval a -> Bool Source #

(/=) :: Interval a -> Interval a -> Bool Source #

HasBlueprintDefinition a => HasBlueprintDefinition (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Unroll (Interval a) :: [Type]

Methods

definitionId :: DefinitionId

(Enum a, Ord a, ToData a, UnsafeFromData a) => Eq (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(==) :: Interval a -> Interval a -> Bool

FromData (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

ToData (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

UnsafeFromData (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Enum a, Ord a, ToData a, UnsafeFromData a) => BoundedJoinSemiLattice (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

bottom :: Interval a

(Enum a, Ord a, ToData a, UnsafeFromData a) => BoundedMeetSemiLattice (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

top :: Interval a

(Enum a, Ord a, ToData a, UnsafeFromData a) => JoinSemiLattice (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(\/) :: Interval a -> Interval a -> Interval a

(Enum a, Ord a, ToData a, UnsafeFromData a) => MeetSemiLattice (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(/\) :: Interval a -> Interval a -> Interval a

(Pretty a, ToData a, UnsafeFromData a) => Pretty (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: Interval a -> Doc ann

prettyList :: [Interval a] -> Doc ann

(HasBlueprintDefinition a, HasSchemaDefinition (LowerBound a) referencedTypes, HasSchemaDefinition (UpperBound a) referencedTypes) => HasBlueprintSchema (Interval a) referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

schema :: Schema referencedTypes

Typeable DefaultUni Interval Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

typeRep :: Proxy Interval -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Rep (Interval a) = D1 ('MetaData "Interval" "PlutusLedgerApi.V1.Data.Interval" "plutus-ledger-api-1.40.0.0-EwL3g0rD7enBEzHV6wRFG7" 'True) (C1 ('MetaCons "Interval_6989586621679173162" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinData)))
type Unroll (Interval a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Unroll (Interval a) = Nub (Interval a ': (Unrolled (LowerBound a) ++ Unrolled (UpperBound a)))

pattern Interval :: forall a. (ToData a, UnsafeFromData a) => LowerBound a -> UpperBound a -> Interval a Source #

data UpperBound a Source #

The upper bound of an interval.

Instances

Instances details
Lift DefaultUni (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

lift :: UpperBound a -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Generic (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Rep (UpperBound a) :: Type -> Type Source #

Methods

from :: UpperBound a -> Rep (UpperBound a) x Source #

to :: Rep (UpperBound a) x -> UpperBound a Source #

Show (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

NFData (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

rnf :: UpperBound a -> () Source #

(Enum a, Eq a, ToData a, UnsafeFromData a) => Eq (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Enum a, Ord a, ToData a, UnsafeFromData a) => Ord (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

HasBlueprintDefinition (Extended a) => HasBlueprintDefinition (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Unroll (UpperBound a) :: [Type]

Methods

definitionId :: DefinitionId

(Enum a, Eq a, ToData a, UnsafeFromData a) => Eq (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(==) :: UpperBound a -> UpperBound a -> Bool

FromData (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

ToData (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

UnsafeFromData (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Enum a, Ord a, ToData a, UnsafeFromData a) => Ord (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Pretty a, ToData a, UnsafeFromData a) => Pretty (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: UpperBound a -> Doc ann

prettyList :: [UpperBound a] -> Doc ann

(HasSchemaDefinition a referencedTypes, HasBlueprintDefinition a, HasSchemaDefinition (Extended a) referencedTypes, HasSchemaDefinition Closure referencedTypes) => HasBlueprintSchema (UpperBound a) referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

schema :: Schema referencedTypes

Typeable DefaultUni UpperBound Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

typeRep :: Proxy UpperBound -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Rep (UpperBound a) = D1 ('MetaData "UpperBound" "PlutusLedgerApi.V1.Data.Interval" "plutus-ledger-api-1.40.0.0-EwL3g0rD7enBEzHV6wRFG7" 'True) (C1 ('MetaCons "UpperBound_6989586621679172081" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinData)))
type Unroll (UpperBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Unroll (UpperBound a) = UpperBound a ': (Unrolled Closure ++ Unrolled (Extended a))

pattern UpperBound :: forall a. (ToData a, UnsafeFromData a) => Extended a -> Closure -> UpperBound a Source #

data LowerBound a Source #

The lower bound of an interval.

Instances

Instances details
Lift DefaultUni (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

lift :: LowerBound a -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Generic (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Rep (LowerBound a) :: Type -> Type Source #

Methods

from :: LowerBound a -> Rep (LowerBound a) x Source #

to :: Rep (LowerBound a) x -> LowerBound a Source #

Show (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

NFData (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

rnf :: LowerBound a -> () Source #

(Enum a, Eq a, ToData a, UnsafeFromData a) => Eq (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Enum a, Ord a, ToData a, UnsafeFromData a) => Ord (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

HasBlueprintDefinition (Extended a) => HasBlueprintDefinition (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Unroll (LowerBound a) :: [Type]

Methods

definitionId :: DefinitionId

(Enum a, Eq a, ToData a, UnsafeFromData a) => Eq (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(==) :: LowerBound a -> LowerBound a -> Bool

FromData (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

ToData (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

UnsafeFromData (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Enum a, Ord a, ToData a, UnsafeFromData a) => Ord (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Pretty a, ToData a, UnsafeFromData a) => Pretty (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: LowerBound a -> Doc ann

prettyList :: [LowerBound a] -> Doc ann

(HasSchemaDefinition a referencedTypes, HasBlueprintDefinition a, HasSchemaDefinition (Extended a) referencedTypes, HasSchemaDefinition Closure referencedTypes) => HasBlueprintSchema (LowerBound a) referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

schema :: Schema referencedTypes

Typeable DefaultUni LowerBound Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

typeRep :: Proxy LowerBound -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Rep (LowerBound a) = D1 ('MetaData "LowerBound" "PlutusLedgerApi.V1.Data.Interval" "plutus-ledger-api-1.40.0.0-EwL3g0rD7enBEzHV6wRFG7" 'True) (C1 ('MetaCons "LowerBound_6989586621679172613" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinData)))
type Unroll (LowerBound a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Unroll (LowerBound a) = LowerBound a ': (Unrolled Closure ++ Unrolled (Extended a))

pattern LowerBound :: forall a. (ToData a, UnsafeFromData a) => Extended a -> Closure -> LowerBound a Source #

data Extended a Source #

A set extended with a positive and negative infinity.

Instances

Instances details
Lift DefaultUni (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

lift :: Extended a -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Generic (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Rep (Extended a) :: Type -> Type Source #

Methods

from :: Extended a -> Rep (Extended a) x Source #

to :: Rep (Extended a) x -> Extended a Source #

Show (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

NFData (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

rnf :: Extended a -> () Source #

(Eq a, ToData a, UnsafeFromData a) => Eq (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(==) :: Extended a -> Extended a -> Bool Source #

(/=) :: Extended a -> Extended a -> Bool Source #

(Ord a, ToData a, UnsafeFromData a) => Ord (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

HasBlueprintDefinition a => HasBlueprintDefinition (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Associated Types

type Unroll (Extended a) :: [Type]

Methods

definitionId :: DefinitionId

(Eq a, ToData a, UnsafeFromData a) => Eq (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

(==) :: Extended a -> Extended a -> Bool

FromData (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

ToData (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

UnsafeFromData (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

(Ord a, ToData a, UnsafeFromData a) => Ord (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

compare :: Extended a -> Extended a -> Ordering

(<) :: Extended a -> Extended a -> Bool

(<=) :: Extended a -> Extended a -> Bool

(>) :: Extended a -> Extended a -> Bool

(>=) :: Extended a -> Extended a -> Bool

max :: Extended a -> Extended a -> Extended a

min :: Extended a -> Extended a -> Extended a

(Pretty a, ToData a, UnsafeFromData a) => Pretty (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: Extended a -> Doc ann

prettyList :: [Extended a] -> Doc ann

Typeable DefaultUni Extended Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

typeRep :: Proxy Extended -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Rep (Extended a) = D1 ('MetaData "Extended" "PlutusLedgerApi.V1.Data.Interval" "plutus-ledger-api-1.40.0.0-EwL3g0rD7enBEzHV6wRFG7" 'True) (C1 ('MetaCons "Extended_6989586621679171410" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinData)))
type Unroll (Extended a) Source # 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

type Unroll (Extended a) = Extended a ': Unrolled a

pattern NegInf :: forall a. Extended a Source #

pattern Finite :: forall a. (ToData a, UnsafeFromData a) => a -> Extended a Source #

pattern PosInf :: forall a. Extended a Source #

type Closure = Bool Source #

Whether a bound is inclusive or not.

member :: (Enum a, Ord a, ToData a, UnsafeFromData a) => a -> Interval a -> Bool Source #

Check whether a value is in an interval.

interval :: (ToData a, UnsafeFromData a) => a -> a -> Interval a Source #

interval a b includes all values that are greater than or equal to a and smaller than or equal to b. Therefore it includes a and b. In math. notation: [a,b]

from :: (ToData a, UnsafeFromData a) => a -> Interval a Source #

from a is an Interval that includes all values that are greater than or equal to a. In math. notation: [a,+∞]

to :: (ToData a, UnsafeFromData a) => a -> Interval a Source #

to a is an Interval that includes all values that are smaller than or equal to a. In math. notation: [-∞,a]

always :: (ToData a, UnsafeFromData a) => Interval a Source #

An Interval that covers every slot. In math. notation [-∞,+∞]

never :: (ToData a, UnsafeFromData a) => Interval a Source #

An Interval that is empty. There can be many empty intervals, see isEmpty. The empty interval never is arbitrarily set to [+∞,-∞].

singleton :: (ToData a, UnsafeFromData a) => a -> Interval a Source #

Create an interval that includes just a single concrete point a, i.e. having the same non-strict lower and upper bounds. In math.notation: [a,a]

hull :: (Enum a, Ord a, ToData a, UnsafeFromData a) => Interval a -> Interval a -> Interval a Source #

'hull a b' is the smallest interval containing a and b.

intersection :: (Enum a, Ord a, ToData a, UnsafeFromData a) => Interval a -> Interval a -> Interval a Source #

'intersection a b' is the largest interval that is contained in a and in b, if it exists.

overlaps :: (Enum a, Ord a, ToData a, UnsafeFromData a) => Interval a -> Interval a -> Bool Source #

Check whether two intervals overlap, that is, whether there is a value that is a member of both intervals.

contains :: (Enum a, Ord a, ToData a, UnsafeFromData a) => Interval a -> Interval a -> Bool Source #

a contains b is true if the Interval b is entirely contained in a. That is, a contains b if for every entry s, if member s b then member s a.

isEmpty :: (Enum a, Ord a, ToData a, UnsafeFromData a) => Interval a -> Bool Source #

Check if an Interval is empty.

before :: (Enum a, Ord a, ToData a, UnsafeFromData a) => a -> Interval a -> Bool Source #

Check if a value is earlier than the beginning of an Interval.

after :: (Enum a, Ord a, ToData a, UnsafeFromData a) => a -> Interval a -> Bool Source #

Check if a value is later than the end of an Interval.

lowerBound :: (ToData a, UnsafeFromData a) => a -> LowerBound a Source #

Construct a lower bound from a value. The resulting bound includes all values that are equal or greater than the input value.

upperBound :: (ToData a, UnsafeFromData a) => a -> UpperBound a Source #

Construct an upper bound from a value. The resulting bound includes all values that are equal or smaller than the input value.

strictLowerBound :: (ToData a, UnsafeFromData a) => a -> LowerBound a Source #

Construct a strict lower bound from a value. The resulting bound includes all values that are (strictly) greater than the input value.

strictUpperBound :: (ToData a, UnsafeFromData a) => a -> UpperBound a Source #

Construct a strict upper bound from a value. The resulting bound includes all values that are (strictly) smaller than the input value.

mapInterval :: (ToData a1, ToData a2, UnsafeFromData a1, UnsafeFromData a2) => (a1 -> a2) -> Interval a1 -> Interval a2 Source #