Copyright | (c) Amy de Buitléir 2013-2016 |
---|---|
License | BSD-style |
Maintainer | amy@nualeargais.ie |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Utilities for working with genes that are encoded as a sequence of bytes, using a Binary Reflected Gray Code (BRGC).
A Gray code maps values to codes in a way that guarantees that the codes for two consecutive values will differ by only one bit. This feature can be useful in evolutionary programming because the genes resulting from a crossover operation are likely to be similar to the inputs. This helps to ensure that offspring are similar to their parents, as any radical changes from one generation to the next are the result of mutation alone.
- class Genetic g where
- type Sequence = [Word8]
- type Writer = StateT (Sequence, [String]) Identity
- write :: Genetic x => x -> Sequence
- runWriter :: Writer () -> (Sequence, [String])
- type Reader = StateT (Sequence, Int, [String]) Identity
- read :: Genetic g => Sequence -> Either [String] g
- runReader :: Reader (Either [String] g) -> Sequence -> (Either [String] g, [String])
- copy :: Reader Sequence
- consumed :: Reader Sequence
- type DiploidSequence = (Sequence, Sequence)
- type DiploidReader = StateT ((Sequence, Int, [String]), (Sequence, Int, [String])) Identity
- readAndExpress :: (Genetic g, Diploid g) => DiploidSequence -> Either [String] g
- runDiploidReader :: DiploidReader g -> DiploidSequence -> g
- getAndExpress :: (Genetic g, Diploid g) => DiploidReader (Either [String] g)
- getAndExpressWithDefault :: (Genetic g, Diploid g) => g -> DiploidReader g
- copy2 :: DiploidReader DiploidSequence
- consumed2 :: DiploidReader DiploidSequence
- putAndReport :: [Word8] -> String -> Writer ()
- getAndReport :: Int -> ([Word8] -> Either String (g, String)) -> Reader (Either [String] g)
- putRawWord8 :: Word8 -> Writer ()
- getRawWord8 :: Reader (Either [String] Word8)
- putRawWord8s :: [Word8] -> Writer ()
- getRawWord8s :: Int -> Reader (Either [String] [Word8])
Documentation
class Genetic g where Source #
A class representing anything which is represented in, and determined by, an agent's genome. This might include traits, parameters, "organs" (components of agents), or even entire agents. Instances of this class can be thought of as genes, i.e., instructions for building an agent.
put :: g -> Writer () Source #
Writes a gene to a sequence.
put :: (Generic g, GGenetic (Rep g)) => g -> Writer () Source #
Writes a gene to a sequence.
get :: Reader (Either [String] g) Source #
Reads the next gene in a sequence.
get :: (Generic g, GGenetic (Rep g)) => Reader (Either [String] g) Source #
Reads the next gene in a sequence.
getWithDefault :: g -> Reader g Source #
Genetic Bool Source # | |
Genetic Char Source # | |
Genetic Double Source # | |
Genetic Int Source # | |
Genetic Integer Source # | |
Genetic Word8 Source # | |
Genetic Word16 Source # | |
Genetic Word32 Source # | |
Genetic Word64 Source # | |
Genetic a => Genetic [a] Source # | |
Genetic a => Genetic (Maybe a) Source # | |
(Genetic a, Genetic b) => Genetic (Either a b) Source # | |
(Genetic a, Genetic b) => Genetic (a, b) Source # | |
type DiploidSequence = (Sequence, Sequence) Source #
type DiploidReader = StateT ((Sequence, Int, [String]), (Sequence, Int, [String])) Identity Source #
readAndExpress :: (Genetic g, Diploid g) => DiploidSequence -> Either [String] g Source #
runDiploidReader :: DiploidReader g -> DiploidSequence -> g Source #
getAndExpress :: (Genetic g, Diploid g) => DiploidReader (Either [String] g) Source #
Read the next pair of genes from twin sequences of genetic information, and return the resulting gene (after taking into account any dominance relationship) and the remaining (unread) portion of the two nucleotide strands.
getAndExpressWithDefault :: (Genetic g, Diploid g) => g -> DiploidReader g Source #
copy2 :: DiploidReader DiploidSequence Source #
Return the entire genome.
consumed2 :: DiploidReader DiploidSequence Source #
Return the portion of the genome that has been read.
getAndReport :: Int -> ([Word8] -> Either String (g, String)) -> Reader (Either [String] g) Source #
putRawWord8 :: Word8 -> Writer () Source #
Write a Word8 value to the genome without encoding it
getRawWord8 :: Reader (Either [String] Word8) Source #
Read a Word8 value from the genome without decoding it
putRawWord8s :: [Word8] -> Writer () Source #
Write a raw sequence of Word8 values to the genome