arduino-copilot-1.5.5: Arduino programming in haskell using the Copilot stream DSL
Safe HaskellNone
LanguageHaskell2010

Copilot.Arduino.Library.EEPROMex

Description

EEPROMex library for arduino-copilot.

This module is designed to be imported qualified.

This is an interface to the C EEPROMex library, which will need to be installed in your Arduino development environment. https://playground.arduino.cc/Code/EEPROMex/

Synopsis

Configuration

maxAllowedWrites :: Word16 -> Sketch () Source #

Set the maximum number of writes to EEPROM that can be made while the Arduino is running. When too many writes have been made, it will no longer write to the EEPROM, and will send warning messages to the serial port.

This is a strongly encouraged safety measure to use, because the Arduino's EEPROM can only endure around 100,000 writes, and a Sketch that's constantly writing to EEPROM, without a well chosen :@ rate limit or delay, could damage your hardware in just a few minutes.

Note that this module uses EEPROMex's update facility for all writes to EEPROM. That avoids writing a byte when its current value is the same as what needed to be written. That prevents excessive wear in some cases, but you should still use maxAllowedWrites too.

For this to work, CPPFLAGS needs to include "-D_EEPROMEX_DEBUG" when the EEPROMex C library gets built. When you use this, it generates C code that makes sure that is enabled.

memPool :: StartAddress -> EndAddress -> Sketch () Source #

Configure the EEPROM memory pool that the program can use.

EEPROM.memPool 0 (EndAddress sizeOfEEPROM)

newtype StartAddress Source #

The address of the first byte of the EEPROM that will be allocated by alloc. The default is to start allocation from 0.

Picking a different StartAddress can avoid overwriting the part of the EEPROM that is used by some other program.

Constructors

StartAddress Word16 

Instances

Instances details
Bounded StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Enum StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Eq StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Integral StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Num StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Ord StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Read StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Real StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Show StartAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

newtype EndAddress Source #

The address of the last byte of the EEPROM that can be allocated by alloc. The default is to allow allocating 512 bytes.

Modules for particular boards, such as Copilot.Arduino.Library.Uno, each define a sizeOfEEPROM value, so to use the entire EEPROM, use:

EndAddress sizeOfEEPROM

Constructors

EndAddress Word16 

Instances

Instances details
Bounded EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Enum EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Eq EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Integral EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Num EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Ord EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Read EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Real EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Show EndAddress Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

class (ShowCType t, Typed t) => EEPROMable t Source #

Minimal complete definition

readValue, writeValue, factoryValue

Instances

Instances details
EEPROMable Bool Source #

This instance is not efficient; a whole byte is read/written rather than a single bit.

Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Double Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Float Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Int8 Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Int16 Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Int32 Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Word8 Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Word16 Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable Word32 Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Single values

alloc :: forall t. EEPROMable t => Sketch (Behavior t, Location t) Source #

Allocates a location in the EEPROM.

Two things are returned; first a Behavior which contains a value read from the EEPROM at boot; and secondly a Location that can be written to later on.

Here's an example of using it, to remember the maximum value read from a1, persistently across power cycles.

EEPROM.maxAllowedWrites 100
(bootval, eepromloc) <- EEPROM.alloc
currval <- input a1 :: Sketch (Behavior ADC)
let maxval = [maxBound] ++ if currval > bootval then currval else bootval
eepromloc =: currval @: (currval > maxval)
delay =: MilliSeconds (constant 10000)

Of course, the EEPROM could already contain any value at the allocated location to start with (either some default value or something written by another program). So you'll need to first boot up a sketch that zeros it out before using the sketch above. Here's a simple sketch that zeros two values:

EEPROM.maxAllowedWrites 100
(_, eepromloc1) <- EEPROM.alloc
(_, eepromloc2) <- EEPROM.alloc
eepromloc1 =: constant (0 :: ADC) :@ firstIteration
eepromloc2 =: constant (0 :: Word16) :@ firstIteration

alloc can be used as many times as you want, storing multiple values in the EEPROM, up to the limit of the size of the EEPROM. (Which is not statically checked.)

Do note that the EEPROM layout is controlled by the order of calls to alloc, so take care when reordering or deleting calls.

alloc' :: forall t. EEPROMable t => t -> Sketch (Behavior t, Location t) Source #

Same as alloc`, but with a value which will be used as the EEPROM's boot value when interpreting the Sketch, instead of the default of acting as if all bits of the EEPROM are set.

data Location t Source #

Instances

Instances details
EEPROMable t => Output (Location t) (Event () (Stream t)) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Location t -> Event () (Stream t) -> Sketch () Source #

Ranges

data Range t Source #

A range of values in the EEPROM.

Instances

Instances details
EEPROMable t => Output (Range t) (RangeWrites t) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Range t -> RangeWrites t -> Sketch () Source #

EEPROMable t => Output (Range t) (Event () (RangeWrites t)) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Range t -> Event () (RangeWrites t) -> Sketch () Source #

type RangeIndex = Word16 Source #

An index into a Range. 0 is the first value in the Range.

Indexes larger than the size of the Range will not overflow it, instead they loop back to the start of the Range.

allocRange :: EEPROMable t => Word16 -> Sketch (Range t) Source #

Allocates a Range in the EEPROM, which stores the specified number of items of some type.

This is an example of using a range of the EEPROM as a ring buffer, to store the last 100 values read from a1.

EEPROM.maxAllowedWrites 1000
range <- EEPROM.allocRange 100 :: Sketch (EEPROM.Range ADC)
currval <- input a1 :: Sketch (Behavior ADC)
range =: EEPROM.sweepRange 0 currval
delay =: MilliSeconds (constant 10000)

allocRange can be used as many times as you want, and combined with uses of alloc, up to the size of the EEPROM. (Which is not statically checked.)

Do note that the EEPROM layout is controlled by the order of calls to allocRange and alloc, so take care when reordering or deleting calls.

sweepRange :: RangeIndex -> Behavior t -> RangeWrites t Source #

Treat the Range as a ring buffer, and starting with the specified RangeIndex, sweep over the Range writing values from the Behavior.

sweepRange' :: RangeIndex -> Behavior Bool -> Behavior RangeIndex Source #

This is actually just a simple counter that increments on each write to the range. That's sufficient, because writes that overflow the end of the range wrap back to the start.

data RangeWrites t Source #

Description of writes made to a Range.

This can be turned into an Event by using @: with it, and that's what the Behavior Bool is needed for. Consider this example, that ignores the Behavior Bool, and just uses a counter for the RangeIndex:

range =: EEPROM.RangeWrites (\_ -> counter) (constant 0) @: blinking

The use of @: blinking makes an Event that only occurs on every other iteration of the Sketch. But, the counter increases on every iteration of the Sketch. So that will only write to every other value in the Range.

The Behavior Bool is only True when an event occurs, and so it can be used to avoid incrementing the counter otherwise. See sweepRange` for an example.

Instances

Instances details
EEPROMable t => IsBehavior (RangeWrites t) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

EEPROMable t => Output (Range t) (RangeWrites t) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Range t -> RangeWrites t -> Sketch () Source #

EEPROMable t => Output (Range t) (Event () (RangeWrites t)) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Range t -> Event () (RangeWrites t) -> Sketch () Source #

type BehaviorToEvent (RangeWrites t) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

scanRange :: Range t -> RangeIndex -> RangeReads t Source #

Scan through the Range, starting with the specified RangeIndex.

range <- EEPROM.allocRange 100 :: Sketch (EEPROM.Range ADC)
v <- input $ scanRange range 0

Once the end of the Range is reached, input continues from the start of the Range.

It's fine to write and read from the same range in the same Sketch, but if the RangeIndex being read and written is the same, it's not defined in what order the two operations will happen.

Also, when interpreting a Sketch that both reads and writes to a range, the input from that range won't reflect the writes made to it, but will instead come from the list of values passed to input`.

data RangeReads t Source #

Description of how to read a` Range`.

The first read is made at the specified RangeIndex, and the location to read from subsequently comes from the Behavior RangeIndex.

Instances

Instances details
(ShowCType t, EEPROMable t) => Input (RangeReads t) t Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

input' :: RangeReads t -> [t] -> Sketch (Behavior t) Source #