| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
OpenCV.Extra.ArUco
Contents
- data Dictionary
- data PredefinedDictionaryName
- getPredefinedDictionary :: PredefinedDictionaryName -> Dictionary
- detectMarkers :: Dictionary -> Mat (S '[h, w]) channels depth -> Maybe ArUcoMarkers
- data ArUcoMarkers
- drawDetectedMarkers :: PrimMonad m => Mut (Mat (S [h, w]) channels depth) (PrimState m) -> ArUcoMarkers -> m ()
- data ChArUcoBoard
- createChArUcoBoard :: Int -> Int -> Double -> Double -> Dictionary -> ChArUcoBoard
- drawChArUcoBoard :: (ToInt32 w, ToInt32 h) => ChArUcoBoard -> w -> h -> Mat (S '[DSNat h, DSNat w]) (S 1) (S Word8)
- interpolateChArUcoMarkers :: ChArUcoBoard -> Mat (S '[h, w]) channels depth -> ArUcoMarkers -> Maybe ChArUcoMarkers
- estimatePoseChArUcoBoard :: ChArUcoBoard -> ChArUcoMarkers -> (Matx33d, Matx51d) -> Maybe (Vec3d, Vec3d)
- calibrateCameraFromFrames :: ChArUcoBoard -> Int -> Int -> [(ArUcoMarkers, ChArUcoMarkers)] -> CvExcept (Matx33d, Matx51d)
- drawDetectedCornersCharuco :: PrimMonad m => Mut (Mat (S '[h, w]) channels depth) (PrimState m) -> ChArUcoMarkers -> m ()
- drawEstimatedPose :: PrimMonad m => Matx33d -> Matx51d -> (Vec3d, Vec3d) -> Mut (Mat (S '[h, w]) channels depth) (PrimState m) -> m ()
ArUco markers
Dictionaries
data Dictionary Source #
A Dictionary describes the possible QR codes used for ArUco markers. Use
getPredefinedDictionary to lookup known dictionaries.
Instances
| WithPtr Dictionary Source # | |
| FromPtr Dictionary Source # | |
| type C Dictionary Source # | |
data PredefinedDictionaryName Source #
The set of predefined ArUco dictionaries known to OpenCV.
Constructors
Instances
getPredefinedDictionary :: PredefinedDictionaryName -> Dictionary Source #
Turn a predefined dictionary name into a ArUco dictionary.
Detecting markers
Arguments
| :: Dictionary | A dictionary describing ArUco markers. |
| -> Mat (S '[h, w]) channels depth | The matrix to detect markers from. |
| -> Maybe ArUcoMarkers |
Perform ArUco marker detection.
data ArUcoMarkers Source #
The result of calling detectMarkers on an image.
Visualising ArUco markers
Arguments
| :: PrimMonad m | |
| => Mut (Mat (S [h, w]) channels depth) (PrimState m) | The image to draw detected markers onto. Usually the same image you detected markers from. |
| -> ArUcoMarkers | The ArUco markers to draw. |
| -> m () |
Given a frame, overlay the result of ArUco marker detection.
ChArUco markers
data ChArUcoBoard Source #
A ChArUco board is used to perform camera calibration from ArUco markers
overlaid on a chess board of known size. Use createChArUcoBoard to create
values of this type.
Instances
Arguments
| :: Int | The amount of squares along the X-axis. |
| -> Int | The amount of squares along the Y-axis. |
| -> Double | The length of a side of a chess-board square. |
| -> Double | The length of a marker's side within a chess-board square. |
| -> Dictionary | The dictionary of ArUco markers. |
| -> ChArUcoBoard |
Create a new ChArUco board configuration.
Arguments
| :: (ToInt32 w, ToInt32 h) | |
| => ChArUcoBoard | |
| -> w | width |
| -> h | height |
| -> Mat (S '[DSNat h, DSNat w]) (S 1) (S Word8) |
Draw a ChArUco board, ready to be printed and used for calibration/marke detection.
Example:
drawChArUcoBoardImg
:: forall (w :: Nat) (h :: Nat)
. (w ~ 500, h ~ 500)
=> Mat ('S '[ 'S h, 'S w]) ('S 1) ('S Word8)
drawChArUcoBoardImg =
drawChArUcoBoard charucoBoard (Proxy :: Proxy w) (Proxy :: Proxy h)
where
charucoBoard :: ChArUcoBoard
charucoBoard = createChArUcoBoard 10 10 20 5 dictionary
dictionary :: Dictionary
dictionary = getPredefinedDictionary DICT_7X7_1000

Detecting markers
interpolateChArUcoMarkers Source #
Arguments
| :: ChArUcoBoard | The ChArUco board to interpolate markers for. |
| -> Mat (S '[h, w]) channels depth | A view of a ChArUco board. |
| -> ArUcoMarkers | The ArUco markers detected in the same image. |
| -> Maybe ChArUcoMarkers |
Given an image and the detected ArUco markers in that image, attempt to perform ChAruco calibration.
estimatePoseChArUcoBoard Source #
Arguments
| :: ChArUcoBoard | The ChArUco board parameters. |
| -> ChArUcoMarkers | Detected ChArUco markers. |
| -> (Matx33d, Matx51d) | A pair of the camera intrinsic parameters and a 5 dimensional vector of distortion coefficients. |
| -> Maybe (Vec3d, Vec3d) |
Given an image, the ChArUco markers in that image, and the camera calibration, estimate the pose of the board.
Camera calibration
calibrateCameraFromFrames :: ChArUcoBoard -> Int -> Int -> [(ArUcoMarkers, ChArUcoMarkers)] -> CvExcept (Matx33d, Matx51d) Source #
Given a list of ChArUco calibration results, combine all results into camera calibration.
Debugging and visualiation utilities
drawDetectedCornersCharuco Source #
Arguments
| :: PrimMonad m | |
| => Mut (Mat (S '[h, w]) channels depth) (PrimState m) | The image to draw detected corners. |
| -> ChArUcoMarkers | The ChArUco markers corners to draw. |
| -> m () |
Given a frame, overlay the result of ChArUco marker detection.
Arguments
| :: PrimMonad m | |
| => Matx33d | The matrix of intrinsic parameters of a camera. |
| -> Matx51d | A 5-dimensional vector of distortion coefficients. |
| -> (Vec3d, Vec3d) | The transposition and rotation matrices from local to camera space, respectively. |
| -> Mut (Mat (S '[h, w]) channels depth) (PrimState m) | An image to draw the axis onto. |
| -> m () |
Given an estimated pose for a board, draw the axis over an image.