Lambdaya-0.3.0.0.0: Library for RedPitaya

Safe HaskellSafe
LanguageHaskell2010

System.RedPitaya.Fpga

Contents

Description

Red Pitaya library for accessing Fpga

Synopsis

Documentation

type Registry = Word32 Source #

type representing fpga registry

data Channel Source #

Redpitaya Channel A or B.

Constructors

A 
B 

Housekeeping

various housekeeping and Gpio functions

fpgaId :: FpgaSetGet a => a Registry Source #

get ID , 0 prototype , 1 release

dna :: FpgaSetGet a => a Integer Source #

get DNA

setExpDirP :: FpgaSetGet a => Registry -> a () Source #

set expansion connector direction P registry

1 out , 0 in

getExpDirP :: FpgaSetGet a => a Registry Source #

get expansion connector direction P registry

1 out , 0 in

setExpDirN :: FpgaSetGet a => Registry -> a () Source #

set expansion connector direction N registry

1 out , 0 in

getExpDirN :: FpgaSetGet a => a Registry Source #

get expansion connector direction N registry

1 out , 0 in

setExpOutP :: FpgaSetGet a => Registry -> a () Source #

expansion connector P output registry value

setExpOutN :: FpgaSetGet a => Registry -> a () Source #

expansion connector N output registry value

getExpInP :: FpgaSetGet a => a Registry Source #

expansion connector P input registry value

getExpInN :: FpgaSetGet a => a Registry Source #

expansion connector N input registry value

data GpioType Source #

type of gpio can be either P on N

Constructors

P

P gpio

N

N gpio

data GpioDirection Source #

represent gpio direction, that can be either Input or Output

Constructors

Input 
Output 

type PinNum = Int Source #

type representing pin number

setExpDir :: (FpgaSetGet m, ToBool b) => GpioType -> b -> Int -> m () Source #

Sets direction of pin

data GpioValue Source #

represent gpio value that can be either Hi or Low

Constructors

Low 
Hi 

setExpOut :: (FpgaSetGet m, ToBool b) => GpioType -> b -> Int -> m () Source #

Sets outout value of pin read using getExpOutN , fmap over setBitValue and bind in setExpOutX

getExpOut :: FpgaSetGet f => GpioType -> Int -> f GpioValue Source #

Sets output value of single pin

setLed :: FpgaSetGet f => Registry -> f () Source #

write in led registry

getLed :: FpgaSetGet f => f Registry Source #

read in led registry

Oscilloscope

functions for accessing oscilloscope features

resetWriteSM :: FpgaSetGet a => a () Source #

reset write state machine for oscilloscope

triggerNow :: FpgaSetGet a => a () Source #

start writing data into memory (ARM trigger).

data TriggerSource Source #

oscilloscope trigger selection

Constructors

Immediately

trig immediately

ChAPositiveEdge

ch A threshold positive edge

ChANegativeEdge

ch A threshold negative edge

ChBPositiveEdge

ch B threshold positive edge

ChBNegativeEdge

ch B threshold negative edge

ExtPositiveEdge

external trigger positive edge - DIO0_P pin

ExtNegaitveEdge

external trigger negative edge

AWGPositiveEdge

arbitrary wave generator application positive edge

AWGNegativeEdge

arbitrary wave generator application negative edge

setOscTrigger :: FpgaSetGet a => TriggerSource -> a () Source #

set oscilloscope trigger

triggerDelayEnded :: FpgaSetGet a => a Bool Source #

when trigger delay is value becomes True

setTreshold :: FpgaSetGet a => Channel -> Registry -> a () Source #

Ch x threshold, makes trigger when ADC value cross this value

getTreshold :: FpgaSetGet a => Channel -> a Registry Source #

gets ch x threshold

setDelayAfterTrigger :: FpgaSetGet a => Registry -> a () Source #

Number of decimated data after trigger written into memory

getDelayAfterTrigger :: FpgaSetGet a => a Registry Source #

gets delay after trigger value

setOscDecimationRaw :: FpgaSetGet a => Registry -> a () Source #

sets oscilloscope decimation registry, allows only 1,8, 64,1024,8192,65536. If other value is written data will NOT be correct.

getOscDecimationRaw :: FpgaSetGet a => a Registry Source #

oscilloscope decimation registry value

setOscDecimation :: FpgaSetGet a => OscDecimation -> a () Source #

set oscilloscope decimation

getOscWpCurrent :: FpgaSetGet a => a Registry Source #

write pointer - current

getOscWpTrigger :: FpgaSetGet a => a Registry Source #

write pointer - trigger

getOscHysteresis :: FpgaSetGet a => Channel -> a Registry Source #

ch x hysteresis

setOscHysteresis :: FpgaSetGet a => Channel -> Registry -> a () Source #

set ch x hysteresis

enableOscDecimationAvarage :: FpgaSetGet a => Bool -> a () Source #

Enable signal average at decimation True enables, False disables

setEqualFilter :: FpgaSetGet a => Channel -> [Registry] -> a () Source #

set ch A equalization filter, takes array with coefficients [AA,BB,KK,PP]

getEqualFilter :: FpgaSetGet a => Channel -> a [Registry] Source #

get ch x equalization filter, return array with coefficients [AA,BB,KK,PP]

setAxiLowerAddress :: FpgaSetGet a => Channel -> Registry -> a () Source #

starting writing address ch x - CH x AXI lower address

getAxiLowerAddress :: FpgaSetGet a => Channel -> a Registry Source #

read - starting writing address ch x - CH x AXI lower address

setAxiUpperAddress :: FpgaSetGet a => Channel -> Registry -> a () Source #

starting writing address ch x - CH x AXI lower address

getAxiUpperAddress :: FpgaSetGet a => Channel -> a Registry Source #

read - starting writing address ch x - CH x AXI lower address

setAxiDelayAfterTrigger :: FpgaSetGet a => Channel -> Registry -> a () Source #

set umber of decimated data after trigger written into memory

getAxiDelayAfterTrigger :: FpgaSetGet a => Channel -> a Registry Source #

read - Number of decimated data after trigger written into memory

enableAxiMaster :: FpgaSetGet a => Channel -> Bool -> a () Source #

Enable AXI master

getAxiWritePtrTrigger :: FpgaSetGet a => Channel -> a Registry Source #

Write pointer for ch x at time when trigger arrived

getAxiWritePtrCurrent :: FpgaSetGet a => Channel -> a Registry Source #

current write pointer for ch x

getOscBuffer :: FpgaSetGet a => Channel -> Offset -> Int -> a [Registry] Source #

reads oscilloscope buffer for channel x from Fpga passing offset and length. buffer should fit within 16k sampling range. Returns less than requested data if trying to read over the bounds.

Arbitrary Signal Generator (ASG)

getAsgOption :: FpgaSetGet a => a Registry Source #

get ASGoption registry

setAsgOption :: FpgaSetGet a => Registry -> a () Source #

set ASG option registry

setAsgOptionBExtGatRep :: FpgaSetGet a => Registry -> a () Source #

ch B external gated repetitions, registry can be either 0x0 or 0x1

getAsgOptionBExtGatRep :: FpgaSetGet a => a Registry Source #

get ch B external gated repetitions, registry can be either 0x0 or 0x1

setAsgAmplitudeScale :: FpgaSetGet a => Channel -> Word32 -> a () Source #

TODO others

todo other registries

Ch x amplitude scale (14 bist) - out = (data*scale)/0x2000 + offset

setAsgAmplitudeOffset :: FpgaSetGet a => Channel -> Word32 -> a () Source #

Ch x amplitude offset (14 bits) - out = (data*scale)/0x2000 + offset

setAsgCounterWrap :: FpgaSetGet a => Channel -> Registry -> a () Source #

Ch x counter wrap - Value where counter wraps around. Depends on SM wrap setting. If it is 1 new value is get by wrap, if value is 0 counter goes to offset value. 16 bits for decimals.

setAsgCounterStartOffset :: FpgaSetGet a => Channel -> Registry -> a () Source #

Ch x Counter start offset. Start offset when trigger arrives. 16 bits for decimals.

setAsgCounterStep :: FpgaSetGet a => Channel -> Registry -> a () Source #

Ch x counter step. 16 bits for decimals.

getAsgCounterReadPtr :: FpgaSetGet a => Channel -> a Registry Source #

get ch x buffer current read pointer

setAsgCounterReadPtr :: FpgaSetGet a => Channel -> Registry -> a () Source #

set ch x buffer current read pointer

getAsgNumReadCycles :: FpgaSetGet a => Channel -> a Registry Source #

get ch x number of read cycles in one burst

setAsgNumReadCycles :: FpgaSetGet a => Channel -> Registry -> a () Source #

set ch x number of read cycles in one burst

getAsgNumRepetitions :: FpgaSetGet a => Channel -> a Registry Source #

get ch x number of read cycles in one burst

setAsgNumRepetitions :: FpgaSetGet a => Channel -> Registry -> a () Source #

set ch x number of read cycles in one burst

getAsgBurstDelay :: FpgaSetGet a => Channel -> a Registry Source #

get ch x delay between burst repetitions, granularity=1us

setAsgBurstDelay :: FpgaSetGet a => Channel -> Registry -> a () Source #

set ch x delay between burst repetitions, granularity=1us

Plumbing

low level helper functions, used to extend interface

type Page = Int Source #

type representing fpga memory page

type Offset = Int Source #

type representing fpga memory offset from page

fpgaRead :: FpgaSetGet m => Page -> Offset -> m Registry Source #

direct read from fpga registry fpgaRead :: Page -> Offset -> Fpga FpgaMmapM Registry

fpgaWrite :: FpgaSetGet m => Page -> Offset -> Registry -> m () Source #

direct write in fpga registry

fpgaFmap :: FpgaSetGet m => Page -> Offset -> (Registry -> Registry) -> m () Source #

apply transformation on fpga registry value

writeFpgaArray :: FpgaSetGet m => Page -> Offset -> [Registry] -> m () Source #

write array in fpga memory

readFpgaArray :: FpgaSetGet a => Page -> Offset -> Int -> a [Registry] Source #

read array from fpga memory, passing page, offset and length

fpgaPageSize :: Offset Source #

size of Fpga page