sdp-0.2.1.1: Simple Data Processing
Copyright(c) Andrey Mulik 2019-2021
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe
LanguageHaskell2010

SDP.Estimate

Description

SDP.Estimate provides Estimate class, type synonyms and some common comparators. This module is exported by SDP.SafePrelude.

Synopsis

Exports

Estimate

class Estimate e where Source #

Estimate class provides the lazy comparsion structures by length.

For some types (e.g., lists), this allows you to speed up the comparison or make it finite. For others (e.g., arrays), it may be convenient abbreviation.

Minimal complete definition

(<.=>), (<==>)

Methods

(<.=>) :: e -> Int -> Ordering infixl 4 Source #

Compare structure length with given number.

(<==>) :: Compare e infixl 4 Source #

Compare pair of structures by length.

(.==) :: e -> Int -> Bool infixl 4 Source #

Compare structure length with given number.

(./=) :: e -> Int -> Bool infixl 4 Source #

Compare structure length with given number.

(.<=) :: e -> Int -> Bool infixl 4 Source #

Compare structure length with given number.

(.>=) :: e -> Int -> Bool infixl 4 Source #

Compare structure length with given number.

(.<) :: e -> Int -> Bool infixl 4 Source #

Compare structure length with given number.

(.>) :: e -> Int -> Bool infixl 4 Source #

Compare structure length with given number.

(.<.) :: e -> e -> Bool infixl 4 Source #

Compare pair of structures by length.

(.>.) :: e -> e -> Bool infixl 4 Source #

Compare pair of structures by length.

(.<=.) :: e -> e -> Bool infixl 4 Source #

Compare pair of structures by length.

(.>=.) :: e -> e -> Bool infixl 4 Source #

Compare pair of structures by length.

(.==.) :: e -> e -> Bool infixl 4 Source #

Compare pair of structures by length.

(./=.) :: e -> e -> Bool infixl 4 Source #

Compare pair of structures by length.

Instances

Instances details
Estimate [a] Source # 
Instance details

Defined in SDP.Estimate

Methods

(<.=>) :: [a] -> Int -> Ordering Source #

(<==>) :: Compare [a] Source #

(.==) :: [a] -> Int -> Bool Source #

(./=) :: [a] -> Int -> Bool Source #

(.<=) :: [a] -> Int -> Bool Source #

(.>=) :: [a] -> Int -> Bool Source #

(.<) :: [a] -> Int -> Bool Source #

(.>) :: [a] -> Int -> Bool Source #

(.<.) :: [a] -> [a] -> Bool Source #

(.>.) :: [a] -> [a] -> Bool Source #

(.<=.) :: [a] -> [a] -> Bool Source #

(.>=.) :: [a] -> [a] -> Bool Source #

(.==.) :: [a] -> [a] -> Bool Source #

(./=.) :: [a] -> [a] -> Bool Source #

Estimate (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Estimate (SArray# e) Source # 
Instance details

Defined in SDP.Prim.SArray

Estimate (TArray# e) Source # 
Instance details

Defined in SDP.Prim.TArray

Index i => Estimate (i, i) Source # 
Instance details

Defined in SDP.Index

Methods

(<.=>) :: (i, i) -> Int -> Ordering Source #

(<==>) :: Compare (i, i) Source #

(.==) :: (i, i) -> Int -> Bool Source #

(./=) :: (i, i) -> Int -> Bool Source #

(.<=) :: (i, i) -> Int -> Bool Source #

(.>=) :: (i, i) -> Int -> Bool Source #

(.<) :: (i, i) -> Int -> Bool Source #

(.>) :: (i, i) -> Int -> Bool Source #

(.<.) :: (i, i) -> (i, i) -> Bool Source #

(.>.) :: (i, i) -> (i, i) -> Bool Source #

(.<=.) :: (i, i) -> (i, i) -> Bool Source #

(.>=.) :: (i, i) -> (i, i) -> Bool Source #

(.==.) :: (i, i) -> (i, i) -> Bool Source #

(./=.) :: (i, i) -> (i, i) -> Bool Source #

Estimate (MIOBytes# io e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(<.=>) :: MIOBytes# io e -> Int -> Ordering Source #

(<==>) :: Compare (MIOBytes# io e) Source #

(.==) :: MIOBytes# io e -> Int -> Bool Source #

(./=) :: MIOBytes# io e -> Int -> Bool Source #

(.<=) :: MIOBytes# io e -> Int -> Bool Source #

(.>=) :: MIOBytes# io e -> Int -> Bool Source #

(.<) :: MIOBytes# io e -> Int -> Bool Source #

(.>) :: MIOBytes# io e -> Int -> Bool Source #

(.<.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.>.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.<=.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.>=.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.==.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(./=.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

Estimate (STBytes# s e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(<.=>) :: STBytes# s e -> Int -> Ordering Source #

(<==>) :: Compare (STBytes# s e) Source #

(.==) :: STBytes# s e -> Int -> Bool Source #

(./=) :: STBytes# s e -> Int -> Bool Source #

(.<=) :: STBytes# s e -> Int -> Bool Source #

(.>=) :: STBytes# s e -> Int -> Bool Source #

(.<) :: STBytes# s e -> Int -> Bool Source #

(.>) :: STBytes# s e -> Int -> Bool Source #

(.<.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.>.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.<=.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.>=.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.==.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(./=.) :: STBytes# s e -> STBytes# s e -> Bool Source #

Estimate (MIOArray# io e) Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

(<.=>) :: MIOArray# io e -> Int -> Ordering Source #

(<==>) :: Compare (MIOArray# io e) Source #

(.==) :: MIOArray# io e -> Int -> Bool Source #

(./=) :: MIOArray# io e -> Int -> Bool Source #

(.<=) :: MIOArray# io e -> Int -> Bool Source #

(.>=) :: MIOArray# io e -> Int -> Bool Source #

(.<) :: MIOArray# io e -> Int -> Bool Source #

(.>) :: MIOArray# io e -> Int -> Bool Source #

(.<.) :: MIOArray# io e -> MIOArray# io e -> Bool Source #

(.>.) :: MIOArray# io e -> MIOArray# io e -> Bool Source #

(.<=.) :: MIOArray# io e -> MIOArray# io e -> Bool Source #

(.>=.) :: MIOArray# io e -> MIOArray# io e -> Bool Source #

(.==.) :: MIOArray# io e -> MIOArray# io e -> Bool Source #

(./=.) :: MIOArray# io e -> MIOArray# io e -> Bool Source #

Estimate (STArray# s e) Source # 
Instance details

Defined in SDP.Prim.SArray

Methods

(<.=>) :: STArray# s e -> Int -> Ordering Source #

(<==>) :: Compare (STArray# s e) Source #

(.==) :: STArray# s e -> Int -> Bool Source #

(./=) :: STArray# s e -> Int -> Bool Source #

(.<=) :: STArray# s e -> Int -> Bool Source #

(.>=) :: STArray# s e -> Int -> Bool Source #

(.<) :: STArray# s e -> Int -> Bool Source #

(.>) :: STArray# s e -> Int -> Bool Source #

(.<.) :: STArray# s e -> STArray# s e -> Bool Source #

(.>.) :: STArray# s e -> STArray# s e -> Bool Source #

(.<=.) :: STArray# s e -> STArray# s e -> Bool Source #

(.>=.) :: STArray# s e -> STArray# s e -> Bool Source #

(.==.) :: STArray# s e -> STArray# s e -> Bool Source #

(./=.) :: STArray# s e -> STArray# s e -> Bool Source #

Bordered1 rep Int e => Estimate (AnyChunks rep e) Source # 
Instance details

Defined in SDP.Templates.AnyChunks

Methods

(<.=>) :: AnyChunks rep e -> Int -> Ordering Source #

(<==>) :: Compare (AnyChunks rep e) Source #

(.==) :: AnyChunks rep e -> Int -> Bool Source #

(./=) :: AnyChunks rep e -> Int -> Bool Source #

(.<=) :: AnyChunks rep e -> Int -> Bool Source #

(.>=) :: AnyChunks rep e -> Int -> Bool Source #

(.<) :: AnyChunks rep e -> Int -> Bool Source #

(.>) :: AnyChunks rep e -> Int -> Bool Source #

(.<.) :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

(.>.) :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

(.<=.) :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

(.>=.) :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

(.==.) :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

(./=.) :: AnyChunks rep e -> AnyChunks rep e -> Bool Source #

Index i => Estimate (AnyBorder rep i e) Source # 
Instance details

Defined in SDP.Templates.AnyBorder

Methods

(<.=>) :: AnyBorder rep i e -> Int -> Ordering Source #

(<==>) :: Compare (AnyBorder rep i e) Source #

(.==) :: AnyBorder rep i e -> Int -> Bool Source #

(./=) :: AnyBorder rep i e -> Int -> Bool Source #

(.<=) :: AnyBorder rep i e -> Int -> Bool Source #

(.>=) :: AnyBorder rep i e -> Int -> Bool Source #

(.<) :: AnyBorder rep i e -> Int -> Bool Source #

(.>) :: AnyBorder rep i e -> Int -> Bool Source #

(.<.) :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

(.>.) :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

(.<=.) :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

(.>=.) :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

(.==.) :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

(./=.) :: AnyBorder rep i e -> AnyBorder rep i e -> Bool Source #

type Estimate1 rep e = Estimate (rep e) Source #

(Type -> Type) kind Estimate.

type Estimate2 rep i e = Estimate (rep i e) Source #

(Type -> Type -> Type) kind Estimate.

Rank 2 quantified constraints

GHC 8.6.1+ only

type Estimate' rep = forall e. Estimate (rep e) Source #

Estimate quantified contraint for (Type -> Type)-kind types.

type Estimate'' rep = forall i e. Estimate (rep i e) Source #

Estimate quantified contraint for (Type -> Type -> Type)-kind types.

Right-side Estimate functions.

(<=.>) :: Estimate e => Int -> e -> Ordering infixl 4 Source #

Compare given number with structure length.

(<.) :: Estimate e => Int -> e -> Bool infixl 4 Source #

Compare given number with structure length.

(>.) :: Estimate e => Int -> e -> Bool infixl 4 Source #

Compare given number with structure length.

(<=.) :: Estimate e => Int -> e -> Bool infixl 4 Source #

Compare given number with structure length.

(>=.) :: Estimate e => Int -> e -> Bool infixl 4 Source #

Compare given number with structure length.

(==.) :: Estimate e => Int -> e -> Bool infixl 4 Source #

Compare given number with structure length.

(/=.) :: Estimate e => Int -> e -> Bool infixl 4 Source #

Compare given number with structure length.