hocd: OpenOCD Haskell interface

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Warnings:

Support for OpenOCDs TCL interface


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.0.0, 0.1.1.0, 0.1.1.1, 0.1.2.0, 0.1.3.0
Change log CHANGELOG.md
Dependencies base (>=4.12 && <5), binary, bytestring, data-default-class, exceptions, hocd, mtl, network, network-run, text, transformers [details]
License BSD-3-Clause
Copyright 2023 sorki
Author sorki
Maintainer srk@48.io
Category Embedded
Home page https://github.com/DistRap/hocd
Source repo head: git clone https://github.com/DistRap/hocd
Uploaded by srk at 2023-12-26T17:52:57Z

Modules

[Index] [Quick Jump]

Flags

Automatic Flags
NameDescriptionDefault
build-readme

Build README.lhs example

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for hocd-0.1.0.0

[back to package description]

GitHub Workflow Status Hackage version Dependencies

hocd

OpenOCD RPC service client.

API

See Haddocks or HOCD.Monad

Example

{-# LANGUAGE TypeApplications #-}

import Data.Word (Word32)
import HOCD

main :: IO ()
main = runOCD example >>= print

-- | For STM32G474
example
  :: MonadOCD m
  => m ([Word32], Word32)
example = do
  halt'

  -- Read RCC.CR register
  rccCr <- readMemCount @Word32 0x40021000 2

  -- Read and increment GPIOA.ODR register
  let gpioaOdr = 0x48000014
  odr <- readMem32 gpioaOdr
  writeMem gpioaOdr [odr+1]
  r <- readMem32 gpioaOdr

  pure (rccCr, r)

This example is runnable from git repository using:

openocd -f nucleo.cfg
cabal run hocd-readme

Executable

hocd-read-mem can be used to read a single or multiple addresses:

cabal run hocd-read-mem -- 0x40021000 0x48000014

Outputs:

0x40021000: 0x3030500
0x48000014: 0x9