tensort-1.0.1.0: Tunable sorting for responsive robustness and beyond
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Tensort.Utils.Types

Description

This module provides types used in the Tensort package

Since these packages are only for sorting Ints currently, every data type is a structure of Ints

Synopsis

Documentation

data TensortProps Source #

TensortProps contains the Bytesize and SubAlgorithm used in a Tensort algorithm

Constructors

TensortProps 

type Bit = Int Source #

A Bit is a single element of the list to be sorted. For our current purposes that means it is an Int

type Byte = [Bit] Source #

A Byte is a list of Bits standardized to a fixed maximum length (Bytesize)

type Address = Int Source #

An Address is a index number pointing to data stored in Memory

type TopBit = Bit Source #

A TopBit contains a copy of the last (i.e. highest) Bit in a Byte or Tensor

type Record = (Address, TopBit) Source #

A Record is an element in a Tensor's Register containing an Address pointer and a TopBit value

type Register = [Record] Source #

A Register is a list of Records allowing for easy access to data in a Tensor's Memory

data Memory Source #

A Memory contains the data to be sorted, either in the form of Bytes or Tensors.

Constructors

ByteMem [Byte] 
TensorMem [Tensor] 

Instances

Instances details
Show Memory Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq Memory Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

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

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

Ord Memory Source # 
Instance details

Defined in Data.Tensort.Utils.Types

type Tensor = (Register, Memory) Source #

A Tensor contains data to be sorted in a structure allowing for easy access. It consists of a Register and its Memory.

type TensorStack = Tensor Source #

A TensorStack is a top-level Tensor. In the final stages of Tensort, the number of TensorStacks will be equal to (or sometimes less than) the bytesize, but before that time there are expected to be many more TensorStacks.

data Sortable Source #

We use a Sortable type to sort Bits and Records

Constructors

SortBit [Bit] 
SortRec [Record] 

Instances

Instances details
Show Sortable Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq Sortable Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Ord Sortable Source # 
Instance details

Defined in Data.Tensort.Utils.Types

fromSortBit :: Sortable -> [Bit] Source #

Converts a Sortable list to a list of Bits

fromSortRec :: Sortable -> [Record] Source #

Converts a Sortable list to a list of Records

type SortAlg = Sortable -> Sortable Source #

A sorting algorithm is a function that takes a Sortable and returns a sorted Sortable

type SupersortProps = (SortAlg, SortAlg, SortAlg, SupersortStrat) Source #

SupersortProps consist of three sorting algorithms to adjuditcate between and a SupersortStrat that does the adjudication

type SupersortStrat = (Sortable, Sortable, Sortable) -> Sortable Source #

A SupersortStrat takes three Sortables and determines which of the three is most likely to be in the correct order

fromJust :: Maybe a -> a Source #

Convers a Maybe into a value or throws an error if the Maybe is Nothing

type BitR = Record Source #

This is a Bit type that is used when sorting Records in a recursive Tensort variant

data SBit Source #

This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants

Constructors

SBitBit Bit 
SBitRec Record 

Instances

Instances details
Show SBit Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

showsPrec :: Int -> SBit -> ShowS #

show :: SBit -> String #

showList :: [SBit] -> ShowS #

Eq SBit Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

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

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

Ord SBit Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

compare :: SBit -> SBit -> Ordering #

(<) :: SBit -> SBit -> Bool #

(<=) :: SBit -> SBit -> Bool #

(>) :: SBit -> SBit -> Bool #

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

max :: SBit -> SBit -> SBit #

min :: SBit -> SBit -> SBit #

fromSBitBit :: SBit -> Bit Source #

Converts an SBit to a Bit

fromSBitRec :: SBit -> Record Source #

Converts an SBit to a Record

fromSBitBits :: [SBit] -> Sortable Source #

Converts a list of Bits to a Sortable

fromSBitRecs :: [SBit] -> Sortable Source #

Converts a list of Records to a Sortable

type ByteR = [Record] Source #

This is a Byte type that is used when sorting Records in a recursive Tensort variant

data SBytes Source #

This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants

Constructors

SBytesBit [Byte] 
SBytesRec [ByteR] 

Instances

Instances details
Show SBytes Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq SBytes Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

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

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

Ord SBytes Source # 
Instance details

Defined in Data.Tensort.Utils.Types

fromSBytesBit :: SBytes -> [[Bit]] Source #

Converts an SBytes list to a list of Bytes

fromSBytesRec :: SBytes -> [[Record]] Source #

Converts an SBytes list to a list of ByteRs

type TopBitR = Record Source #

This is a TopBit type that is used when sorting Records in a recursive Tensort variant

type RecordR = (Address, TopBitR) Source #

This is a Record type that is used when sorting Records in a recursive Tensort variant

data SRecord Source #

This is a conversion type that allows for sorting both Records and Bits. It is useful in recursive Tensort variants

Instances

Instances details
Show SRecord Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq SRecord Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

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

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

Ord SRecord Source # 
Instance details

Defined in Data.Tensort.Utils.Types

fromSRecordBit :: SRecord -> Record Source #

Converts an SRecord to a Record

fromSRecordRec :: SRecord -> RecordR Source #

Converts an SRecord to a RecordR

data SRecords Source #

This is a conversion type that allows for sorting both Records and Bits. It is useful in recursive Tensort variants

Instances

Instances details
Show SRecords Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq SRecords Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Ord SRecords Source # 
Instance details

Defined in Data.Tensort.Utils.Types

fromSRecordsBit :: SRecords -> [Record] Source #

Converts an SRecords list to a list of Records

fromSRecordsRec :: SRecords -> [RecordR] Source #

Converts an SRecords list to a list of RecordRs

fromSRecordArrayBit :: [SRecord] -> [Record] Source #

Converts a list of SRecords to a list of Records

fromSRecordArrayRec :: [SRecord] -> [RecordR] Source #

Converts a list of SRecords to a list of RecordRs

type RegisterR = [RecordR] Source #

This is a Register type that is used when sorting Records in a recursive Tensort variant

data MemoryR Source #

This is a Memory type that is used when sorting Records in a recursive Tensort variant

Constructors

ByteMemR [ByteR] 
TensorMemR [TensorR] 

Instances

Instances details
Show MemoryR Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq MemoryR Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

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

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

Ord MemoryR Source # 
Instance details

Defined in Data.Tensort.Utils.Types

data SMemory Source #

This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants

Instances

Instances details
Show SMemory Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq SMemory Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

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

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

Ord SMemory Source # 
Instance details

Defined in Data.Tensort.Utils.Types

fromSMemoryBit :: SMemory -> Memory Source #

Converts an SMemory to a Memory

fromSMemoryRec :: SMemory -> MemoryR Source #

Converts an SMemory to a MemoryR

type TensorR = (RegisterR, MemoryR) Source #

This is a Tensor type that is used when sorting Records in a recursive Tensort variant

data STensor Source #

This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants

Instances

Instances details
Show STensor Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq STensor Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Methods

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

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

Ord STensor Source # 
Instance details

Defined in Data.Tensort.Utils.Types

fromSTensorBit :: STensor -> Tensor Source #

Converts an STensor to a Tensor

fromSTensorRec :: STensor -> TensorR Source #

Converts an STensor to a TensorR

data STensors Source #

This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants

Instances

Instances details
Show STensors Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Eq STensors Source # 
Instance details

Defined in Data.Tensort.Utils.Types

Ord STensors Source # 
Instance details

Defined in Data.Tensort.Utils.Types

fromSTensorsBit :: STensors -> [Tensor] Source #

Converts an STensors list to a list of Tensors

fromSTensorsRec :: STensors -> [TensorR] Source #

Converts an STensors list to a list of TensorRs

type TensorStackR = TensorR Source #

This is a TensorStack type that is used when sorting Records in a recursive Tensort variant

type STensorStack = STensor Source #

This is a conversion type that allows for sorting both Tensors and Records. It is useful in recursive Tensort variants

type STensorStacks = STensors Source #

This is a conversion type that allows for sorting both Tensors and Records. It is useful in recursive Tensort variants