{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
module Copilot.Arduino.Library.EEPROMex (
maxAllowedWrites,
memPool,
StartAddress(..),
EndAddress(..),
EEPROMable,
alloc,
alloc',
Location,
Range,
RangeIndex,
allocRange,
sweepRange,
sweepRange',
RangeWrites(..),
scanRange,
RangeReads(..),
) where
import Copilot.Arduino
import Copilot.Arduino.Internals
import Control.Monad.Writer
import Data.Proxy
import qualified Prelude
maxAllowedWrites :: Word16 -> Sketch ()
maxAllowedWrites :: Word16 -> Sketch ()
maxAllowedWrites Word16
n = [(TriggerLimit -> WriterT [SpecItem] Identity (),
TriggerLimit -> Framework)]
-> Sketch ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [(\TriggerLimit
_ -> () -> WriterT [SpecItem] Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return (), \TriggerLimit
_ -> Framework
f)]
where
f :: Framework
f = Framework
forall a. Monoid a => a
mempty
{ earlySetups :: [CChunk]
earlySetups = [CLine] -> [CChunk]
mkCChunk
[ String -> CLine
CLine String
"#ifdef _EEPROMEX_DEBUG"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"EEPROM.setMaxAllowedWrites(" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Word16 -> String
forall a. Show a => a -> String
show Word16
n String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
");"
, String -> CLine
CLine String
"#else"
, String -> CLine
CLine String
"#error \"maxAllowedWrites cannot be checked because _EEPROMEX_DEBUG is not set.\""
, String -> CLine
CLine String
"#endif"
]
, defines :: [CChunk]
defines = [CLine] -> [CChunk]
mkCChunk [ CLine
includeCLine ]
}
newtype StartAddress = StartAddress Word16
deriving (Integer -> StartAddress
StartAddress -> StartAddress
StartAddress -> StartAddress -> StartAddress
(StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress)
-> (StartAddress -> StartAddress)
-> (StartAddress -> StartAddress)
-> (Integer -> StartAddress)
-> Num StartAddress
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> StartAddress
$cfromInteger :: Integer -> StartAddress
signum :: StartAddress -> StartAddress
$csignum :: StartAddress -> StartAddress
abs :: StartAddress -> StartAddress
$cabs :: StartAddress -> StartAddress
negate :: StartAddress -> StartAddress
$cnegate :: StartAddress -> StartAddress
* :: StartAddress -> StartAddress -> StartAddress
$c* :: StartAddress -> StartAddress -> StartAddress
- :: StartAddress -> StartAddress -> StartAddress
$c- :: StartAddress -> StartAddress -> StartAddress
+ :: StartAddress -> StartAddress -> StartAddress
$c+ :: StartAddress -> StartAddress -> StartAddress
Num, StartAddress -> StartAddress -> Bool
(StartAddress -> StartAddress -> Bool)
-> (StartAddress -> StartAddress -> Bool) -> Eq StartAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartAddress -> StartAddress -> Bool
$c/= :: StartAddress -> StartAddress -> Bool
== :: StartAddress -> StartAddress -> Bool
$c== :: StartAddress -> StartAddress -> Bool
Eq, Eq StartAddress
Eq StartAddress
-> (StartAddress -> StartAddress -> Ordering)
-> (StartAddress -> StartAddress -> Bool)
-> (StartAddress -> StartAddress -> Bool)
-> (StartAddress -> StartAddress -> Bool)
-> (StartAddress -> StartAddress -> Bool)
-> (StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress -> StartAddress)
-> Ord StartAddress
StartAddress -> StartAddress -> Bool
StartAddress -> StartAddress -> Ordering
StartAddress -> StartAddress -> StartAddress
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StartAddress -> StartAddress -> StartAddress
$cmin :: StartAddress -> StartAddress -> StartAddress
max :: StartAddress -> StartAddress -> StartAddress
$cmax :: StartAddress -> StartAddress -> StartAddress
>= :: StartAddress -> StartAddress -> Bool
$c>= :: StartAddress -> StartAddress -> Bool
> :: StartAddress -> StartAddress -> Bool
$c> :: StartAddress -> StartAddress -> Bool
<= :: StartAddress -> StartAddress -> Bool
$c<= :: StartAddress -> StartAddress -> Bool
< :: StartAddress -> StartAddress -> Bool
$c< :: StartAddress -> StartAddress -> Bool
compare :: StartAddress -> StartAddress -> Ordering
$ccompare :: StartAddress -> StartAddress -> Ordering
$cp1Ord :: Eq StartAddress
Ord, Int -> StartAddress
StartAddress -> Int
StartAddress -> [StartAddress]
StartAddress -> StartAddress
StartAddress -> StartAddress -> [StartAddress]
StartAddress -> StartAddress -> StartAddress -> [StartAddress]
(StartAddress -> StartAddress)
-> (StartAddress -> StartAddress)
-> (Int -> StartAddress)
-> (StartAddress -> Int)
-> (StartAddress -> [StartAddress])
-> (StartAddress -> StartAddress -> [StartAddress])
-> (StartAddress -> StartAddress -> [StartAddress])
-> (StartAddress -> StartAddress -> StartAddress -> [StartAddress])
-> Enum StartAddress
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: StartAddress -> StartAddress -> StartAddress -> [StartAddress]
$cenumFromThenTo :: StartAddress -> StartAddress -> StartAddress -> [StartAddress]
enumFromTo :: StartAddress -> StartAddress -> [StartAddress]
$cenumFromTo :: StartAddress -> StartAddress -> [StartAddress]
enumFromThen :: StartAddress -> StartAddress -> [StartAddress]
$cenumFromThen :: StartAddress -> StartAddress -> [StartAddress]
enumFrom :: StartAddress -> [StartAddress]
$cenumFrom :: StartAddress -> [StartAddress]
fromEnum :: StartAddress -> Int
$cfromEnum :: StartAddress -> Int
toEnum :: Int -> StartAddress
$ctoEnum :: Int -> StartAddress
pred :: StartAddress -> StartAddress
$cpred :: StartAddress -> StartAddress
succ :: StartAddress -> StartAddress
$csucc :: StartAddress -> StartAddress
Enum, Int -> StartAddress -> String -> String
[StartAddress] -> String -> String
StartAddress -> String
(Int -> StartAddress -> String -> String)
-> (StartAddress -> String)
-> ([StartAddress] -> String -> String)
-> Show StartAddress
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StartAddress] -> String -> String
$cshowList :: [StartAddress] -> String -> String
show :: StartAddress -> String
$cshow :: StartAddress -> String
showsPrec :: Int -> StartAddress -> String -> String
$cshowsPrec :: Int -> StartAddress -> String -> String
Show, ReadPrec [StartAddress]
ReadPrec StartAddress
Int -> ReadS StartAddress
ReadS [StartAddress]
(Int -> ReadS StartAddress)
-> ReadS [StartAddress]
-> ReadPrec StartAddress
-> ReadPrec [StartAddress]
-> Read StartAddress
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartAddress]
$creadListPrec :: ReadPrec [StartAddress]
readPrec :: ReadPrec StartAddress
$creadPrec :: ReadPrec StartAddress
readList :: ReadS [StartAddress]
$creadList :: ReadS [StartAddress]
readsPrec :: Int -> ReadS StartAddress
$creadsPrec :: Int -> ReadS StartAddress
Read, StartAddress
StartAddress -> StartAddress -> Bounded StartAddress
forall a. a -> a -> Bounded a
maxBound :: StartAddress
$cmaxBound :: StartAddress
minBound :: StartAddress
$cminBound :: StartAddress
Bounded, Enum StartAddress
Real StartAddress
Real StartAddress
-> Enum StartAddress
-> (StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress -> StartAddress)
-> (StartAddress -> StartAddress -> (StartAddress, StartAddress))
-> (StartAddress -> StartAddress -> (StartAddress, StartAddress))
-> (StartAddress -> Integer)
-> Integral StartAddress
StartAddress -> Integer
StartAddress -> StartAddress -> (StartAddress, StartAddress)
StartAddress -> StartAddress -> StartAddress
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: StartAddress -> Integer
$ctoInteger :: StartAddress -> Integer
divMod :: StartAddress -> StartAddress -> (StartAddress, StartAddress)
$cdivMod :: StartAddress -> StartAddress -> (StartAddress, StartAddress)
quotRem :: StartAddress -> StartAddress -> (StartAddress, StartAddress)
$cquotRem :: StartAddress -> StartAddress -> (StartAddress, StartAddress)
mod :: StartAddress -> StartAddress -> StartAddress
$cmod :: StartAddress -> StartAddress -> StartAddress
div :: StartAddress -> StartAddress -> StartAddress
$cdiv :: StartAddress -> StartAddress -> StartAddress
rem :: StartAddress -> StartAddress -> StartAddress
$crem :: StartAddress -> StartAddress -> StartAddress
quot :: StartAddress -> StartAddress -> StartAddress
$cquot :: StartAddress -> StartAddress -> StartAddress
$cp2Integral :: Enum StartAddress
$cp1Integral :: Real StartAddress
Integral, Num StartAddress
Ord StartAddress
Num StartAddress
-> Ord StartAddress
-> (StartAddress -> Rational)
-> Real StartAddress
StartAddress -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: StartAddress -> Rational
$ctoRational :: StartAddress -> Rational
$cp2Real :: Ord StartAddress
$cp1Real :: Num StartAddress
Real)
newtype EndAddress = EndAddress Word16
deriving (Integer -> EndAddress
EndAddress -> EndAddress
EndAddress -> EndAddress -> EndAddress
(EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress)
-> (EndAddress -> EndAddress)
-> (EndAddress -> EndAddress)
-> (Integer -> EndAddress)
-> Num EndAddress
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> EndAddress
$cfromInteger :: Integer -> EndAddress
signum :: EndAddress -> EndAddress
$csignum :: EndAddress -> EndAddress
abs :: EndAddress -> EndAddress
$cabs :: EndAddress -> EndAddress
negate :: EndAddress -> EndAddress
$cnegate :: EndAddress -> EndAddress
* :: EndAddress -> EndAddress -> EndAddress
$c* :: EndAddress -> EndAddress -> EndAddress
- :: EndAddress -> EndAddress -> EndAddress
$c- :: EndAddress -> EndAddress -> EndAddress
+ :: EndAddress -> EndAddress -> EndAddress
$c+ :: EndAddress -> EndAddress -> EndAddress
Num, EndAddress -> EndAddress -> Bool
(EndAddress -> EndAddress -> Bool)
-> (EndAddress -> EndAddress -> Bool) -> Eq EndAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EndAddress -> EndAddress -> Bool
$c/= :: EndAddress -> EndAddress -> Bool
== :: EndAddress -> EndAddress -> Bool
$c== :: EndAddress -> EndAddress -> Bool
Eq, Eq EndAddress
Eq EndAddress
-> (EndAddress -> EndAddress -> Ordering)
-> (EndAddress -> EndAddress -> Bool)
-> (EndAddress -> EndAddress -> Bool)
-> (EndAddress -> EndAddress -> Bool)
-> (EndAddress -> EndAddress -> Bool)
-> (EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress -> EndAddress)
-> Ord EndAddress
EndAddress -> EndAddress -> Bool
EndAddress -> EndAddress -> Ordering
EndAddress -> EndAddress -> EndAddress
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EndAddress -> EndAddress -> EndAddress
$cmin :: EndAddress -> EndAddress -> EndAddress
max :: EndAddress -> EndAddress -> EndAddress
$cmax :: EndAddress -> EndAddress -> EndAddress
>= :: EndAddress -> EndAddress -> Bool
$c>= :: EndAddress -> EndAddress -> Bool
> :: EndAddress -> EndAddress -> Bool
$c> :: EndAddress -> EndAddress -> Bool
<= :: EndAddress -> EndAddress -> Bool
$c<= :: EndAddress -> EndAddress -> Bool
< :: EndAddress -> EndAddress -> Bool
$c< :: EndAddress -> EndAddress -> Bool
compare :: EndAddress -> EndAddress -> Ordering
$ccompare :: EndAddress -> EndAddress -> Ordering
$cp1Ord :: Eq EndAddress
Ord, Int -> EndAddress
EndAddress -> Int
EndAddress -> [EndAddress]
EndAddress -> EndAddress
EndAddress -> EndAddress -> [EndAddress]
EndAddress -> EndAddress -> EndAddress -> [EndAddress]
(EndAddress -> EndAddress)
-> (EndAddress -> EndAddress)
-> (Int -> EndAddress)
-> (EndAddress -> Int)
-> (EndAddress -> [EndAddress])
-> (EndAddress -> EndAddress -> [EndAddress])
-> (EndAddress -> EndAddress -> [EndAddress])
-> (EndAddress -> EndAddress -> EndAddress -> [EndAddress])
-> Enum EndAddress
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: EndAddress -> EndAddress -> EndAddress -> [EndAddress]
$cenumFromThenTo :: EndAddress -> EndAddress -> EndAddress -> [EndAddress]
enumFromTo :: EndAddress -> EndAddress -> [EndAddress]
$cenumFromTo :: EndAddress -> EndAddress -> [EndAddress]
enumFromThen :: EndAddress -> EndAddress -> [EndAddress]
$cenumFromThen :: EndAddress -> EndAddress -> [EndAddress]
enumFrom :: EndAddress -> [EndAddress]
$cenumFrom :: EndAddress -> [EndAddress]
fromEnum :: EndAddress -> Int
$cfromEnum :: EndAddress -> Int
toEnum :: Int -> EndAddress
$ctoEnum :: Int -> EndAddress
pred :: EndAddress -> EndAddress
$cpred :: EndAddress -> EndAddress
succ :: EndAddress -> EndAddress
$csucc :: EndAddress -> EndAddress
Enum, Int -> EndAddress -> String -> String
[EndAddress] -> String -> String
EndAddress -> String
(Int -> EndAddress -> String -> String)
-> (EndAddress -> String)
-> ([EndAddress] -> String -> String)
-> Show EndAddress
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EndAddress] -> String -> String
$cshowList :: [EndAddress] -> String -> String
show :: EndAddress -> String
$cshow :: EndAddress -> String
showsPrec :: Int -> EndAddress -> String -> String
$cshowsPrec :: Int -> EndAddress -> String -> String
Show, ReadPrec [EndAddress]
ReadPrec EndAddress
Int -> ReadS EndAddress
ReadS [EndAddress]
(Int -> ReadS EndAddress)
-> ReadS [EndAddress]
-> ReadPrec EndAddress
-> ReadPrec [EndAddress]
-> Read EndAddress
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EndAddress]
$creadListPrec :: ReadPrec [EndAddress]
readPrec :: ReadPrec EndAddress
$creadPrec :: ReadPrec EndAddress
readList :: ReadS [EndAddress]
$creadList :: ReadS [EndAddress]
readsPrec :: Int -> ReadS EndAddress
$creadsPrec :: Int -> ReadS EndAddress
Read, EndAddress
EndAddress -> EndAddress -> Bounded EndAddress
forall a. a -> a -> Bounded a
maxBound :: EndAddress
$cmaxBound :: EndAddress
minBound :: EndAddress
$cminBound :: EndAddress
Bounded, Enum EndAddress
Real EndAddress
Real EndAddress
-> Enum EndAddress
-> (EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress -> EndAddress)
-> (EndAddress -> EndAddress -> (EndAddress, EndAddress))
-> (EndAddress -> EndAddress -> (EndAddress, EndAddress))
-> (EndAddress -> Integer)
-> Integral EndAddress
EndAddress -> Integer
EndAddress -> EndAddress -> (EndAddress, EndAddress)
EndAddress -> EndAddress -> EndAddress
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: EndAddress -> Integer
$ctoInteger :: EndAddress -> Integer
divMod :: EndAddress -> EndAddress -> (EndAddress, EndAddress)
$cdivMod :: EndAddress -> EndAddress -> (EndAddress, EndAddress)
quotRem :: EndAddress -> EndAddress -> (EndAddress, EndAddress)
$cquotRem :: EndAddress -> EndAddress -> (EndAddress, EndAddress)
mod :: EndAddress -> EndAddress -> EndAddress
$cmod :: EndAddress -> EndAddress -> EndAddress
div :: EndAddress -> EndAddress -> EndAddress
$cdiv :: EndAddress -> EndAddress -> EndAddress
rem :: EndAddress -> EndAddress -> EndAddress
$crem :: EndAddress -> EndAddress -> EndAddress
quot :: EndAddress -> EndAddress -> EndAddress
$cquot :: EndAddress -> EndAddress -> EndAddress
$cp2Integral :: Enum EndAddress
$cp1Integral :: Real EndAddress
Integral, Num EndAddress
Ord EndAddress
Num EndAddress
-> Ord EndAddress -> (EndAddress -> Rational) -> Real EndAddress
EndAddress -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: EndAddress -> Rational
$ctoRational :: EndAddress -> Rational
$cp2Real :: Ord EndAddress
$cp1Real :: Num EndAddress
Real)
memPool :: StartAddress -> EndAddress -> Sketch ()
memPool :: StartAddress -> EndAddress -> Sketch ()
memPool (StartAddress Word16
start) (EndAddress Word16
end) =
[(TriggerLimit -> WriterT [SpecItem] Identity (),
TriggerLimit -> Framework)]
-> Sketch ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [(\TriggerLimit
_ -> () -> WriterT [SpecItem] Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return (), \TriggerLimit
_ -> Framework
f)]
where
f :: Framework
f = Framework
forall a. Monoid a => a
mempty
{ earlySetups :: [CChunk]
earlySetups = [CLine] -> [CChunk]
mkCChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"EEPROM.setMemPool("
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Word16 -> String
forall a. Show a => a -> String
show Word16
start
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", "
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Word16 -> String
forall a. Show a => a -> String
show Word16
end
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
");"
]
, defines :: [CChunk]
defines = [CLine] -> [CChunk]
mkCChunk [ CLine
includeCLine ]
}
alloc :: forall t. (EEPROMable t) => Sketch (Behavior t, Location t)
alloc :: Sketch (Behavior t, Location t)
alloc = t -> Sketch (Behavior t, Location t)
forall t. EEPROMable t => t -> Sketch (Behavior t, Location t)
alloc' (Proxy t -> t
forall t. EEPROMable t => Proxy t -> t
factoryValue (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
alloc' :: forall t. (EEPROMable t) => t -> Sketch (Behavior t, Location t)
alloc' :: t -> Sketch (Behavior t, Location t)
alloc' t
interpretval = do
UniqueId
i <- String -> Sketch UniqueId
getUniqueId String
"eeprom"
let addrvarname :: String
addrvarname = String -> UniqueId -> String
uniqueName String
"eeprom_address" UniqueId
i
let bootvarname :: String
bootvarname = String -> UniqueId -> String
uniqueName String
"eeprom_boot_val" UniqueId
i
let proxy :: Proxy t
proxy = Proxy t
forall k (t :: k). Proxy t
Proxy @t
Behavior t
bootval <- InputSource t -> Sketch (Behavior t)
forall t. InputSource t -> Sketch (Behavior t)
mkInput (InputSource t -> Sketch (Behavior t))
-> InputSource t -> Sketch (Behavior t)
forall a b. (a -> b) -> a -> b
$ InputSource :: forall t.
[CChunk]
-> [CChunk]
-> Map PinId PinMode
-> [CChunk]
-> Stream t
-> InputSource t
InputSource
{ defineVar :: [CChunk]
defineVar =
[ [CLine] -> CChunk
CChunk [CLine
includeCLine]
, [CLine] -> CChunk
CChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"int " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
addrvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
";"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
bootvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
";"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"void " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> UniqueId -> String
eepromWriterName UniqueId
i
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"(" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" value) {"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
" EEPROM." String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall t. EEPROMable t => Proxy t -> String
writeValue Proxy t
proxy
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"(" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
addrvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", value);"
, String -> CLine
CLine String
"}"
]
]
, setupInput :: [CChunk]
setupInput = [CLine] -> [CChunk]
mkCChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
addrvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<>
String
" = EEPROM.getAddress(sizeof("
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"));"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
bootvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<>
String
" = EEPROM."
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall t. EEPROMable t => Proxy t -> String
readValue Proxy t
proxy String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"(" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
addrvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
");"
]
, readInput :: [CChunk]
readInput = []
, inputStream :: Behavior t
inputStream = String -> Maybe [t] -> Behavior t
forall a. Typed a => String -> Maybe [a] -> Stream a
extern String
bootvarname ([t] -> Maybe [t]
forall a. a -> Maybe a
Just (t -> [t]
forall a. a -> [a]
repeat t
interpretval))
, inputPinmode :: Map PinId PinMode
inputPinmode = Map PinId PinMode
forall a. Monoid a => a
mempty
}
(Behavior t, Location t) -> Sketch (Behavior t, Location t)
forall (m :: * -> *) a. Monad m => a -> m a
return (Behavior t
bootval, UniqueId -> Location t
forall t. UniqueId -> Location t
Location UniqueId
i)
eepromWriterName :: UniqueId -> String
eepromWriterName :: UniqueId -> String
eepromWriterName = String -> UniqueId -> String
uniqueName' String
"eeprom_write"
data Location t = Location UniqueId
instance EEPROMable t => Output (Location t) (Event () (Stream t)) where
Location UniqueId
i =: :: Location t -> Event () (Stream t) -> Sketch ()
=: (Event Stream t
v Stream Bool
c) = do
(Framework
f, String
triggername) <- String -> Framework -> Sketch (Framework, String)
defineTriggerAlias (UniqueId -> String
eepromWriterName UniqueId
i) Framework
forall a. Monoid a => a
mempty
[(TriggerLimit -> WriterT [SpecItem] Identity (),
TriggerLimit -> Framework)]
-> Sketch ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [(String -> TriggerLimit -> WriterT [SpecItem] Identity ()
go String
triggername, \TriggerLimit
_ -> Framework
f)]
where
go :: String -> TriggerLimit -> WriterT [SpecItem] Identity ()
go String
triggername TriggerLimit
tl =
let c' :: Stream Bool
c' = TriggerLimit -> Stream Bool -> Stream Bool
addTriggerLimit TriggerLimit
tl Stream Bool
c
in String -> Stream Bool -> [Arg] -> WriterT [SpecItem] Identity ()
trigger String
triggername Stream Bool
c' [Stream t -> Arg
forall a. Typed a => Stream a -> Arg
arg Stream t
v]
data Range t = Range
{ Range t -> Location (Range t)
rangeLocation :: Location (Range t)
, Range t -> Word16
rangeSize :: Word16
}
allocRange :: (EEPROMable t) => Word16 -> Sketch (Range t)
allocRange :: Word16 -> Sketch (Range t)
allocRange Word16
sz = do
UniqueId
i <- String -> Sketch UniqueId
getUniqueId String
"eeprom"
Range t -> Sketch (Range t)
forall (m :: * -> *) a. Monad m => a -> m a
return (Location (Range t) -> Word16 -> Range t
forall t. Location (Range t) -> Word16 -> Range t
Range (UniqueId -> Location (Range t)
forall t. UniqueId -> Location t
Location UniqueId
i) Word16
sz)
data RangeWrites t = RangeWrites
(Behavior Bool -> Behavior RangeIndex)
(Behavior t)
type RangeIndex = Word16
instance EEPROMable t => Output (Range t) (RangeWrites t) where
=: :: Range t -> RangeWrites t -> Sketch ()
(=:) = Stream Bool -> Range t -> RangeWrites t -> Sketch ()
forall t.
EEPROMable t =>
Stream Bool -> Range t -> RangeWrites t -> Sketch ()
writeRange Stream Bool
true
instance EEPROMable t => Output (Range t) (Event () (RangeWrites t)) where
Range t
range =: :: Range t -> Event () (RangeWrites t) -> Sketch ()
=: Event RangeWrites t
ws Stream Bool
c =
Stream Bool -> Range t -> RangeWrites t -> Sketch ()
forall t.
EEPROMable t =>
Stream Bool -> Range t -> RangeWrites t -> Sketch ()
writeRange Stream Bool
c Range t
range RangeWrites t
ws
instance EEPROMable t => IsBehavior (RangeWrites t) where
@: :: RangeWrites t -> Stream Bool -> BehaviorToEvent (RangeWrites t)
(@:) = RangeWrites t -> Stream Bool -> BehaviorToEvent (RangeWrites t)
forall k (p :: k) v. v -> Stream Bool -> Event p v
Event
type instance BehaviorToEvent (RangeWrites t) = Event () (RangeWrites t)
writeRange :: forall t. EEPROMable t => Behavior Bool -> Range t -> RangeWrites t -> Sketch()
writeRange :: Stream Bool -> Range t -> RangeWrites t -> Sketch ()
writeRange Stream Bool
c Range t
range (RangeWrites Stream Bool -> Behavior Word16
idx Behavior t
v) = do
(Framework
f', String
triggername) <- String -> Framework -> Sketch (Framework, String)
defineTriggerAlias String
writername Framework
f
[(TriggerLimit -> WriterT [SpecItem] Identity (),
TriggerLimit -> Framework)]
-> Sketch ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [(String -> TriggerLimit -> WriterT [SpecItem] Identity ()
spec String
triggername, \TriggerLimit
_ -> Framework
f')]
where
Location UniqueId
i = Range t -> Location (Range t)
forall t. Range t -> Location (Range t)
rangeLocation Range t
range
idx' :: Behavior Word16
idx' = Stream Bool -> Behavior Word16
idx Stream Bool
c Behavior Word16 -> Behavior Word16 -> Behavior Word16
forall a. (Typed a, Integral a) => Stream a -> Stream a -> Stream a
`mod` Word16 -> Behavior Word16
forall a. Typed a => a -> Stream a
constant (Range t -> Word16
forall t. Range t -> Word16
rangeSize Range t
range)
startaddrvarname :: String
startaddrvarname = UniqueId -> String
eepromRangeStartAddrName UniqueId
i
writername :: String
writername = String -> UniqueId -> String
uniqueName String
"eeprom_range_write" UniqueId
i
proxy :: Proxy t
proxy = Proxy t
forall k (t :: k). Proxy t
Proxy @t
f :: Framework
f = Framework :: [CChunk]
-> [CChunk]
-> [CChunk]
-> Map PinId (Set PinMode)
-> [CChunk]
-> Framework
Framework
{ defines :: [CChunk]
defines =
[ [CLine] -> CChunk
CChunk [CLine
includeCLine]
, [CLine] -> CChunk
CChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"int " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
startaddrvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
";"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"void " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
writername
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"(" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" value"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy Word16 -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType (Proxy Word16
forall k (t :: k). Proxy t
Proxy @Word16) String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" offset"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
") {"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
" EEPROM." String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall t. EEPROMable t => Proxy t -> String
writeValue Proxy t
proxy
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"(" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
startaddrvarname
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" + offset*sizeof("
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
")"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", value);"
, String -> CLine
CLine String
"}"
]
]
, setups :: [CChunk]
setups = [CLine] -> [CChunk]
mkCChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
startaddrvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" = EEPROM.getAddress"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"(sizeof(" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
")"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" * " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Word16 -> String
forall a. Show a => a -> String
show (Range t -> Word16
forall t. Range t -> Word16
rangeSize Range t
range)
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
");"
]
, earlySetups :: [CChunk]
earlySetups = []
, pinmodes :: Map PinId (Set PinMode)
pinmodes = Map PinId (Set PinMode)
forall a. Monoid a => a
mempty
, loops :: [CChunk]
loops = [CChunk]
forall a. Monoid a => a
mempty
}
spec :: String -> TriggerLimit -> WriterT [SpecItem] Identity ()
spec String
triggername TriggerLimit
tl =
let c' :: Stream Bool
c' = TriggerLimit -> Stream Bool -> Stream Bool
addTriggerLimit TriggerLimit
tl Stream Bool
c
in String -> Stream Bool -> [Arg] -> WriterT [SpecItem] Identity ()
trigger String
triggername Stream Bool
c' [Behavior Word16 -> Arg
forall a. Typed a => Stream a -> Arg
arg Behavior Word16
idx', Behavior t -> Arg
forall a. Typed a => Stream a -> Arg
arg Behavior t
v]
eepromRangeStartAddrName :: UniqueId -> String
eepromRangeStartAddrName :: UniqueId -> String
eepromRangeStartAddrName = String -> UniqueId -> String
uniqueName String
"eeprom_range_address"
sweepRange :: RangeIndex -> Behavior t -> RangeWrites t
sweepRange :: Word16 -> Behavior t -> RangeWrites t
sweepRange Word16
start = (Stream Bool -> Behavior Word16) -> Behavior t -> RangeWrites t
forall t.
(Stream Bool -> Behavior Word16) -> Behavior t -> RangeWrites t
RangeWrites (Word16 -> Stream Bool -> Behavior Word16
sweepRange' Word16
start)
sweepRange' :: RangeIndex -> Behavior Bool -> Behavior RangeIndex
sweepRange' :: Word16 -> Stream Bool -> Behavior Word16
sweepRange' Word16
start Stream Bool
c = Behavior Word16
cnt
where
cnt :: Behavior Word16
cnt = [Word16
start] [Word16] -> Behavior Word16 -> Behavior Word16
forall a. Typed a => [a] -> Stream a -> Stream a
++ Behavior Word16
rest
rest :: Behavior Word16
rest = if Stream Bool
c then Behavior Word16
cnt Behavior Word16 -> Behavior Word16 -> Behavior Word16
forall a. Num a => a -> a -> a
+ Behavior Word16
1 else Behavior Word16
cnt
data RangeReads t = RangeReads (Range t) RangeIndex (Behavior RangeIndex)
scanRange :: Range t -> RangeIndex -> RangeReads t
scanRange :: Range t -> Word16 -> RangeReads t
scanRange Range t
r Word16
startidx = Range t -> Word16 -> Behavior Word16 -> RangeReads t
forall t. Range t -> Word16 -> Behavior Word16 -> RangeReads t
RangeReads Range t
r Word16
startidx Behavior Word16
cnt
where
cnt :: Behavior Word16
cnt = [Word16
startidxWord16 -> Word16 -> Word16
forall a. Num a => a -> a -> a
+Word16
1] [Word16] -> Behavior Word16 -> Behavior Word16
forall a. Typed a => [a] -> Stream a -> Stream a
++ Behavior Word16
rest
rest :: Behavior Word16
rest = Behavior Word16
cnt Behavior Word16 -> Behavior Word16 -> Behavior Word16
forall a. Num a => a -> a -> a
+ Behavior Word16
1
instance (ShowCType t, EEPROMable t) => Input (RangeReads t) t where
input' :: RangeReads t -> [t] -> Sketch (Behavior t)
input' (RangeReads Range t
range Word16
startidx Behavior Word16
idx) [t]
interpretvalues = do
(Framework
f, String
triggername) <- String -> Framework -> Sketch (Framework, String)
defineTriggerAlias String
indexvarupdatername Framework
forall a. Monoid a => a
mempty
let t :: TriggerLimit -> WriterT [SpecItem] Identity ()
t TriggerLimit
tl =
let c :: Stream Bool
c = TriggerLimit -> Stream Bool
getTriggerLimit TriggerLimit
tl
in String -> Stream Bool -> [Arg] -> WriterT [SpecItem] Identity ()
trigger String
triggername Stream Bool
c [Behavior Word16 -> Arg
forall a. Typed a => Stream a -> Arg
arg Behavior Word16
idx']
[(TriggerLimit -> WriterT [SpecItem] Identity (),
TriggerLimit -> Framework)]
-> Sketch ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [(TriggerLimit -> WriterT [SpecItem] Identity ()
t, \TriggerLimit
_ -> Framework
f)]
InputSource t -> Sketch (Behavior t)
forall t. InputSource t -> Sketch (Behavior t)
mkInput (InputSource t -> Sketch (Behavior t))
-> InputSource t -> Sketch (Behavior t)
forall a b. (a -> b) -> a -> b
$ InputSource :: forall t.
[CChunk]
-> [CChunk]
-> Map PinId PinMode
-> [CChunk]
-> Stream t
-> InputSource t
InputSource
{ defineVar :: [CChunk]
defineVar = [CLine] -> [CChunk]
mkCChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
valname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
";"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"int " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
indexvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
";"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"void " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
indexvarupdatername String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" (int idx) {"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
" " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
indexvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" = idx;"
, String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
"}"
]
, setupInput :: [CChunk]
setupInput = [CLine] -> [CChunk]
mkCChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
indexvarname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" = " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Word16 -> String
forall a. Show a => a -> String
show Word16
startidx' String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
";" ]
, readInput :: [CChunk]
readInput = [CLine] -> [CChunk]
mkCChunk
[ String -> CLine
CLine (String -> CLine) -> String -> CLine
forall a b. (a -> b) -> a -> b
$ String
valname String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" = EEPROM." String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall t. EEPROMable t => Proxy t -> String
readValue Proxy t
proxy
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"("
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> UniqueId -> String
eepromRangeStartAddrName UniqueId
i
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" + " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
indexvarname
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"*sizeof("
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Proxy t -> String
forall k (t :: k). ShowCType t => Proxy t -> String
showCType Proxy t
proxy
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
")"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
");"
]
, inputStream :: Behavior t
inputStream = String -> Maybe [t] -> Behavior t
forall a. Typed a => String -> Maybe [a] -> Stream a
extern String
valname Maybe [t]
interpretvalues'
, inputPinmode :: Map PinId PinMode
inputPinmode = Map PinId PinMode
forall a. Monoid a => a
mempty
}
where
Location UniqueId
i = Range t -> Location (Range t)
forall t. Range t -> Location (Range t)
rangeLocation Range t
range
idx' :: Behavior Word16
idx' = Behavior Word16
idx Behavior Word16 -> Behavior Word16 -> Behavior Word16
forall a. (Typed a, Integral a) => Stream a -> Stream a -> Stream a
`mod` Word16 -> Behavior Word16
forall a. Typed a => a -> Stream a
constant (Range t -> Word16
forall t. Range t -> Word16
rangeSize Range t
range)
startidx' :: Word16
startidx' = Word16
startidx Word16 -> Word16 -> Word16
forall a. Integral a => a -> a -> a
`Prelude.mod` Range t -> Word16
forall t. Range t -> Word16
rangeSize Range t
range
proxy :: Proxy t
proxy = Proxy t
forall k (t :: k). Proxy t
Proxy @t
indexvarname :: String
indexvarname = String -> UniqueId -> String
uniqueName String
"eeprom_range_read_index" UniqueId
i
indexvarupdatername :: String
indexvarupdatername = String -> UniqueId -> String
uniqueName String
"eeprom_range_read" UniqueId
i
valname :: String
valname = String -> UniqueId -> String
uniqueName String
"eeprom_range_val" UniqueId
i
interpretvalues' :: Maybe [t]
interpretvalues'
| [t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
interpretvalues = Maybe [t]
forall a. Maybe a
Nothing
| Bool
otherwise = [t] -> Maybe [t]
forall a. a -> Maybe a
Just [t]
interpretvalues
class (ShowCType t, Typed t) => EEPROMable t where
readValue :: Proxy t -> String
writeValue :: Proxy t -> String
factoryValue :: Proxy t -> t
instance EEPROMable Bool where
readValue :: Proxy Bool -> String
readValue Proxy Bool
_ = String
"readByte"
writeValue :: Proxy Bool -> String
writeValue Proxy Bool
_ = String
"updateByte"
factoryValue :: Proxy Bool -> Bool
factoryValue Proxy Bool
_ = Bool
True
instance EEPROMable Int8 where
readValue :: Proxy Int8 -> String
readValue Proxy Int8
_ = String
"readByte"
writeValue :: Proxy Int8 -> String
writeValue Proxy Int8
_ = String
"updateByte"
factoryValue :: Proxy Int8 -> Int8
factoryValue Proxy Int8
_ = Int8
forall a. Bounded a => a
minBound
instance EEPROMable Int16 where
readValue :: Proxy Int16 -> String
readValue Proxy Int16
_ = String
"readInt"
writeValue :: Proxy Int16 -> String
writeValue Proxy Int16
_ = String
"updateInt"
factoryValue :: Proxy Int16 -> Int16
factoryValue Proxy Int16
_= Int16
forall a. Bounded a => a
minBound
instance EEPROMable Int32 where
readValue :: Proxy Int32 -> String
readValue Proxy Int32
_ = String
"readLong"
writeValue :: Proxy Int32 -> String
writeValue Proxy Int32
_ = String
"updateLong"
factoryValue :: Proxy Int32 -> Int32
factoryValue Proxy Int32
_= Int32
forall a. Bounded a => a
minBound
instance EEPROMable Word8 where
readValue :: Proxy Word8 -> String
readValue Proxy Word8
_ = String
"readByte"
writeValue :: Proxy Word8 -> String
writeValue Proxy Word8
_ = String
"updateByte"
factoryValue :: Proxy Word8 -> Word8
factoryValue Proxy Word8
_ = Word8
forall a. Bounded a => a
maxBound
instance EEPROMable Word16 where
readValue :: Proxy Word16 -> String
readValue Proxy Word16
_ = String
"readInt"
writeValue :: Proxy Word16 -> String
writeValue Proxy Word16
_ = String
"updateInt"
factoryValue :: Proxy Word16 -> Word16
factoryValue Proxy Word16
_ = Word16
forall a. Bounded a => a
maxBound
instance EEPROMable Word32 where
readValue :: Proxy Word32 -> String
readValue Proxy Word32
_ = String
"readLong"
writeValue :: Proxy Word32 -> String
writeValue Proxy Word32
_ = String
"updateLong"
factoryValue :: Proxy Word32 -> Word32
factoryValue Proxy Word32
_ = Word32
forall a. Bounded a => a
maxBound
instance EEPROMable Float where
readValue :: Proxy Float -> String
readValue Proxy Float
_ = String
"readFloat"
writeValue :: Proxy Float -> String
writeValue Proxy Float
_ = String
"updateFloat"
factoryValue :: Proxy Float -> Float
factoryValue Proxy Float
_ = Float
0Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/Float
0
instance EEPROMable Double where
readValue :: Proxy Double -> String
readValue Proxy Double
_ = String
"readDouble"
writeValue :: Proxy Double -> String
writeValue Proxy Double
_ = String
"updateDOuble"
factoryValue :: Proxy Double -> Double
factoryValue Proxy Double
_ = Double
0Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
0
includeCLine :: CLine
includeCLine :: CLine
includeCLine = String -> CLine
CLine String
"#include <EEPROMex.h>"