Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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 Byte = [Bit]
- type Address = Int
- type TopBit = Bit
- type Record = (Address, TopBit)
- type Register = [Record]
- data Memory
- type Tensor = (Register, Memory)
- type TensorStack = Tensor
- data Sortable
- fromSortBit :: Sortable -> [Bit]
- fromSortRec :: Sortable -> [Record]
- type SortAlg = Sortable -> Sortable
- type SupersortProps = (SortAlg, SortAlg, SortAlg, SupersortStrat)
- type SupersortStrat = (Sortable, Sortable, Sortable) -> Sortable
- fromJust :: Maybe a -> a
- type BitR = Record
- data SBit
- fromSBitBit :: SBit -> Bit
- fromSBitRec :: SBit -> Record
- fromSBitBits :: [SBit] -> Sortable
- fromSBitRecs :: [SBit] -> Sortable
- type ByteR = [Record]
- data SBytes
- fromSBytesBit :: SBytes -> [[Bit]]
- fromSBytesRec :: SBytes -> [[Record]]
- type TopBitR = Record
- 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 RegisterR = [RecordR]
- data MemoryR
- = ByteMemR [ByteR]
- | TensorMemR [TensorR]
- data SMemory
- fromSMemoryBit :: SMemory -> Memory
- fromSMemoryRec :: SMemory -> MemoryR
- type TensorR = (RegisterR, MemoryR)
- data STensor
- fromSTensorBit :: STensor -> Tensor
- fromSTensorRec :: STensor -> TensorR
- data STensors
- = STensorsBit [Tensor]
- | STensorsRec [TensorR]
- fromSTensorsBit :: STensors -> [Tensor]
- fromSTensorsRec :: STensors -> [TensorR]
- type TensorStackR = TensorR
- type STensorStack = STensor
- type STensorStacks = STensors
Documentation
data TensortProps Source #
TensortProps contains the Bytesize and SubAlgorithm used in a Tensort algorithm.
A Bit is a single element of the list to be sorted. For our current purposes that means it is an Int.
A Byte is a list of Bits standardized to a fixed maximum length (Bytesize).
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.
A Memory contains the data to be sorted, either in the form of Bytes or Tensors.
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.
We use a Sortable type to sort list of Bits and lists of 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.
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 #
Converts a Maybe into a value or throws an error if the Maybe is Nothing.
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 into a Bit.
fromSBitRec :: SBit -> Record Source #
Converts an SBit into a Record.
fromSBitBits :: [SBit] -> Sortable Source #
Converts a list of Bits into a Sortable.
fromSBitRecs :: [SBit] -> Sortable Source #
Converts a list of Records into a Sortable.
type ByteR = [Record] Source #
This is a Byte
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.
fromSBytesBit :: SBytes -> [[Bit]] Source #
Converts an SBytes list into a list of Bytes.
fromSBytesRec :: SBytes -> [[Record]] Source #
Converts an SBytes list into 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.
This is a conversion type that allows for sorting both Records and Bits. It is useful in recursive Tensort variants.
fromSRecordBit :: SRecord -> Record Source #
Converts an SRecord into a Record.
fromSRecordRec :: SRecord -> RecordR Source #
Converts an SRecord into a RecordR.
This is a conversion type that allows for sorting both Records and Bits. It is useful in recursive Tensort variants.
fromSRecordsBit :: SRecords -> [Record] Source #
Converts an SRecords list into a list of Records.
fromSRecordsRec :: SRecords -> [RecordR] Source #
Converts an SRecords list into a list of RecordRs.
fromSRecordArrayBit :: [SRecord] -> [Record] Source #
Converts a list of SRecords into a list of Records.
fromSRecordArrayRec :: [SRecord] -> [RecordR] Source #
Converts a list of SRecords into a list of RecordRs.
type RegisterR = [RecordR] Source #
This is a Register
type that is used when sorting Records in a recursive
Tensort variant.
This is a Memory
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.
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.
This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants.
fromSTensorBit :: STensor -> Tensor Source #
Converts an STensor into a Tensor.
fromSTensorRec :: STensor -> TensorR Source #
Converts an STensor into a TensorR.
This is a conversion type that allows for sorting both Bits and Records. It is useful in recursive Tensort variants.
fromSTensorsBit :: STensors -> [Tensor] Source #
Converts an STensors list into a list of Tensors.
fromSTensorsRec :: STensors -> [TensorR] Source #
Converts an STensors list into 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.