Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- data TensortProps = TensortProps {
- bytesize :: Int
- subAlgorithm :: SortAlg
- type Bit = Int
- type BitR = Record
- data SBit
- fromSBitBit :: SBit -> Bit
- fromSBitRec :: SBit -> Record
- type Byte = [Bit]
- type ByteR = [Record]
- type Address = Int
- type TopBit = Bit
- type TopBitR = Record
- type Record = (Address, TopBit)
- type RecordR = (Address, TopBitR)
- data SRecord
- fromSRecordBit :: SRecord -> Record
- fromSRecordRec :: SRecord -> RecordR
- data SRecords
- = SRecordsBit [Record]
- | SRecordsRec [RecordR]
- fromSRecordsBit :: SRecords -> [Record]
- fromSRecordsRec :: SRecords -> [RecordR]
- fromSRecordArrayBit :: [SRecord] -> [Record]
- fromSRecordArrayRec :: [SRecord] -> [RecordR]
- type Register = [Record]
- type RegisterR = [RecordR]
- data Sortable
- fromSortBit :: Sortable -> [Bit]
- fromSortRec :: Sortable -> [Record]
- fromSBitBits :: [SBit] -> Sortable
- fromSBitRecs :: [SBit] -> Sortable
- data SBytes
- fromSBytesBit :: SBytes -> [[Bit]]
- fromSBytesRec :: SBytes -> [[Record]]
- data STensor
- data STensors
- = STensorsBit [Tensor]
- | STensorsRec [TensorR]
- fromSTensorBit :: STensor -> Tensor
- fromSTensorRec :: STensor -> TensorR
- fromSTensorsBit :: STensors -> [Tensor]
- fromSTensorsRec :: STensors -> [TensorR]
- type SortAlg = Sortable -> Sortable
- type SupersortProps = (SortAlg, SortAlg, SortAlg, SupersortStrat)
- type SupersortStrat = (Sortable, Sortable, Sortable) -> Sortable
- data Memory
- data MemoryR
- = ByteMemR [ByteR]
- | TensorMemR [TensorR]
- data SMemory
- fromSMemoryBit :: SMemory -> Memory
- fromSMemoryRec :: SMemory -> MemoryR
- type Tensor = (Register, Memory)
- type TensorR = (RegisterR, MemoryR)
- type TensorStack = Tensor
- type TensorStackR = TensorR
- type STensorStack = STensor
- type STensorStacks = STensors
- fromJust :: Maybe a -> a
Documentation
data TensortProps Source #
TensortProps contains the Bytesize and SubAlgorithm used in a Tensort algorithm
Constructors
TensortProps | |
Fields
|
A Bit is a single element of the list to be sorted. For our current purposes that means it is an Int
This is a Bit
type that is used when sorting Records in a recursive
Tensort variant
This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants
fromSBitBit :: SBit -> Bit Source #
Converts an SBit to a Bit
fromSBitRec :: SBit -> Record Source #
Converts an SBit to a Record
A Byte is a list of Bits standardized to a fixed maximum length (Bytesize)
The length should be set either in or upstream of any function that uses Bytes
type ByteR = [Record] Source #
This is a Byte
type that is used when sorting Records in a recursive
Tensort variant
A TopBit contains a copy of the last (i.e. highest) Bit in a Byte or Tensor
type TopBitR = Record Source #
This is a TopBit
type that is used when sorting Records in a recursive
Tensort variant
type Record = (Address, TopBit) Source #
A Record is an element in a Tensor's Register containing an Address pointer and a TopBit value
A Record's Address is an index number pointing to a Byte or Tensor in the Tensor's Memory
A Record's TopBit is a copy of the last (i.e. highest) Bit in the Byte or Tensor that the Record references
type RecordR = (Address, TopBitR) Source #
This is a Record
type that is used when sorting Records in a recursive
Tensort variant
This is a conversion type that allows for sorting both Records and Bits. It is useful in recursive Tensort variants
Constructors
SRecordBit Record | |
SRecordRec RecordR |
fromSRecordBit :: SRecord -> Record Source #
Converts an SRecord to a Record
fromSRecordRec :: SRecord -> RecordR Source #
Converts an SRecord to a RecordR
This is a conversion type that allows for sorting both Records and Bits. It is useful in recursive Tensort variants
Constructors
SRecordsBit [Record] | |
SRecordsRec [RecordR] |
fromSRecordsBit :: SRecords -> [Record] Source #
Converts an SRecords to a list of Records
fromSRecordsRec :: SRecords -> [RecordR] Source #
Converts an SRecords 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 Register = [Record] Source #
A Register is a list of Records allowing for easy access to data in a Tensor's Memory
type RegisterR = [RecordR] Source #
This is a Register
type that is used when sorting Records in a recursive
Tensort variant
We use a Sortable type to sort Bits and Records
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
fromSBitBits :: [SBit] -> Sortable Source #
Converts a list of Bits to a Sortable
fromSBitRecs :: [SBit] -> Sortable Source #
Converts a list of Records to a Sortable
This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants
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
This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants
Constructors
STensorBit Tensor | |
STensorRec TensorR |
This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants
Constructors
STensorsBit [Tensor] | |
STensorsRec [TensorR] |
fromSTensorBit :: STensor -> Tensor Source #
Converts an STensor to a Tensor
fromSTensorRec :: STensor -> TensorR Source #
Converts an STensor to a TensorR
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 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
A Memory contains the data to be sorted, either in the form of Bytes or Tensors.
This is a Memory
type that is used when sorting Records in a recursive
Tensort variant
Constructors
ByteMemR [ByteR] | |
TensorMemR [TensorR] |
This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants
Constructors
SMemoryBit Memory | |
SMemoryRec MemoryR |
fromSMemoryBit :: SMemory -> Memory Source #
Converts an SMemory to a Memory
fromSMemoryRec :: SMemory -> MemoryR Source #
Converts an SMemory to a MemoryR
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.
The Memory is a list of the Bytes or other Tensors that this Tensor contains.
The Register is a list of Records referencing the top Bits in Memory.
type TensorR = (RegisterR, MemoryR) Source #
This is a Tensor
type that is used when sorting Records in a recursive
Tensort variant
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.
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