risk-weaver-0.1.0.2: A DSL for Risk-oriented Object Detection Requirements
Safe HaskellSafe-Inferred
LanguageGHC2021

RiskWeaver.DSL.Core

Synopsis

Documentation

class (Eq (ClassG a), Eq (ClassD a)) => BoundingBox a where Source #

Bounding box type class of ground truth

Associated Types

data Detection a :: Type Source #

Detection type

type ClassG a :: Type Source #

Ground truth class type

type ClassD a :: Type Source #

Detection class type

data ErrorType a :: Type Source #

Error type

type InterestArea a :: Type Source #

Interest area type

type InterestObject a :: Type Source #

Interest object type

data Env a :: Type Source #

Environment type of the image

type Idx a :: Type Source #

Index type of bounding box annotations

type ImgIdx a :: Type Source #

Image index type of bounding box annotations

data Risk a :: Type Source #

Risk type

Methods

riskE :: Env a -> [Risk a] Source #

Risk of the environment

riskForGroundTruth :: Monad m => ReaderT (Env a) m [Risk a] Source #

Risk of groundtruth

riskForDetection :: Monad m => ReaderT (Env a) m [Risk a] Source #

Risk of detection

interestArea :: Env a -> InterestArea a Source #

Interest area of the environment

interestObject :: Env a -> InterestObject a Source #

Interest object of the environment

groundTruth :: Env a -> Vector a Source #

Ground truth of the environment

detection :: Env a -> Vector (Detection a) Source #

Detection of the environment

confidenceScoreThresh :: Env a -> Double Source #

Confidence score threshold

ioUThresh :: Env a -> Double Source #

IoU threshold

scoreD :: Detection a -> Double Source #

Confidence score of the detection

sizeD :: Detection a -> Double Source #

Size of the detection

classD :: Detection a -> ClassG a Source #

Class of the detection

idD :: Detection a -> Idx a Source #

Index of the detection

imageId :: Env a -> ImgIdx a Source #

Index of the image

isFrontD :: Detection a -> Detection a -> Bool Source #

True if the detection is in front of the other detection

isBackD :: Detection a -> Detection a -> Bool Source #

True if the detection is in back of the other detection

isLeftD :: Detection a -> Detection a -> Bool Source #

True if the detection is in left of the other detection

isRightD :: Detection a -> Detection a -> Bool Source #

True if the detection is in right of the other detection

isTopD :: Detection a -> Detection a -> Bool Source #

True if the detection is in top of the other detection

isBottomD :: Detection a -> Detection a -> Bool Source #

True if the detection is in bottom of the other detection

isBackGroundD :: ClassD a -> Bool Source #

True if the detection is background

detectD :: Env a -> Detection a -> Maybe a Source #

Detect the ground truth of the detection

toErrorType :: Risk a -> ErrorType a Source #

Get error type from risk

toRiskScore :: Risk a -> Double Source #

Get a score from risk

sizeG :: a -> Double Source #

Size of the ground truth

default sizeG :: Rectangle a => a -> Double Source #

classG :: a -> ClassG a Source #

Class of the ground truth

angle :: a -> Detection a -> Double Source #

Angle of detection to the ground truth

idG :: a -> Idx a Source #

Index of the ground truth

ioU :: a -> Detection a -> Double Source #

IoU(Intersection Over Union) of the ground truth and the detection

default ioU :: (Rectangle a, Rectangle (Detection a)) => a -> Detection a -> Double Source #

ioG :: a -> Detection a -> Double Source #

IoG(Intersection Over Ground truth) of the ground truth and the detection

default ioG :: (Rectangle a, Rectangle (Detection a)) => a -> Detection a -> Double Source #

ioD :: a -> Detection a -> Double Source #

IoD(Intersection Over Detection) of the ground truth and the detection

default ioD :: (Rectangle a, Rectangle (Detection a)) => a -> Detection a -> Double Source #

detectG :: Env a -> a -> Maybe (Detection a) Source #

Detect the detection of the ground truth

isInIeterestAreaD :: InterestArea a -> Detection a -> Bool Source #

True if the detection is in the interest area

isInIeterestAreaG :: InterestArea a -> a -> Bool Source #

True if the ground truth is in the interest area

isInterestObjectD :: InterestObject a -> Detection a -> Bool Source #

True if the detection is in the interest object

isInterestObjectG :: InterestObject a -> a -> Bool Source #

True if the ground truth is in the interest object

Instances

Instances details
BoundingBox BoundingBoxGT Source # 
Instance details

Defined in RiskWeaver.DSL.BDD

Methods

riskE :: Env BoundingBoxGT -> [Risk BoundingBoxGT] Source #

riskForGroundTruth :: forall (m :: Type -> Type). Monad m => ReaderT (Env BoundingBoxGT) m [Risk BoundingBoxGT] Source #

riskForDetection :: forall (m :: Type -> Type). Monad m => ReaderT (Env BoundingBoxGT) m [Risk BoundingBoxGT] Source #

interestArea :: Env BoundingBoxGT -> InterestArea BoundingBoxGT Source #

interestObject :: Env BoundingBoxGT -> InterestObject BoundingBoxGT Source #

groundTruth :: Env BoundingBoxGT -> Vector BoundingBoxGT Source #

detection :: Env BoundingBoxGT -> Vector (Detection BoundingBoxGT) Source #

confidenceScoreThresh :: Env BoundingBoxGT -> Double Source #

ioUThresh :: Env BoundingBoxGT -> Double Source #

scoreD :: Detection BoundingBoxGT -> Double Source #

sizeD :: Detection BoundingBoxGT -> Double Source #

classD :: Detection BoundingBoxGT -> ClassG BoundingBoxGT Source #

idD :: Detection BoundingBoxGT -> Idx BoundingBoxGT Source #

imageId :: Env BoundingBoxGT -> ImgIdx BoundingBoxGT Source #

isFrontD :: Detection BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isBackD :: Detection BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isLeftD :: Detection BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isRightD :: Detection BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isTopD :: Detection BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isBottomD :: Detection BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isBackGroundD :: ClassD BoundingBoxGT -> Bool Source #

detectD :: Env BoundingBoxGT -> Detection BoundingBoxGT -> Maybe BoundingBoxGT Source #

toErrorType :: Risk BoundingBoxGT -> ErrorType BoundingBoxGT Source #

toRiskScore :: Risk BoundingBoxGT -> Double Source #

sizeG :: BoundingBoxGT -> Double Source #

classG :: BoundingBoxGT -> ClassG BoundingBoxGT Source #

angle :: BoundingBoxGT -> Detection BoundingBoxGT -> Double Source #

idG :: BoundingBoxGT -> Idx BoundingBoxGT Source #

ioU :: BoundingBoxGT -> Detection BoundingBoxGT -> Double Source #

ioG :: BoundingBoxGT -> Detection BoundingBoxGT -> Double Source #

ioD :: BoundingBoxGT -> Detection BoundingBoxGT -> Double Source #

detectG :: Env BoundingBoxGT -> BoundingBoxGT -> Maybe (Detection BoundingBoxGT) Source #

isInIeterestAreaD :: InterestArea BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isInIeterestAreaG :: InterestArea BoundingBoxGT -> BoundingBoxGT -> Bool Source #

isInterestObjectD :: InterestObject BoundingBoxGT -> Detection BoundingBoxGT -> Bool Source #

isInterestObjectG :: InterestObject BoundingBoxGT -> BoundingBoxGT -> Bool Source #

class (NFData (ImgIdx a), NFData (Risk a), BoundingBox a) => World b a where Source #

b includes ground-truth images and detection images.

Methods

envs :: b -> [Env a] Source #

Environments of the image

toEnv :: b -> ImgIdx a -> Env a Source #

An environment of the image

toImageIds :: b -> [ImgIdx a] Source #

An environment of the image

mAP :: b -> Double Source #

mAP of the images

ap :: b -> Map (ClassG a) Double Source #

AP of the images for each class

mF1 :: b -> Double Source #

mF1 of the images

f1 :: b -> Map (ClassG a) Double Source #

F1 of the images for each class

risk :: b -> [Risk a] Source #

Risk of the images

confusionMatrixRecall :: b -> Map (ClassG a, ClassD a) [Risk a] Source #

Confusion matrix of recall

confusionMatrixPrecision :: b -> Map (ClassD a, ClassG a) [Risk a] Source #

Confusion matrix of precision

loopG :: forall a m b. (BoundingBox a, Monad m) => (b -> b -> b) -> b -> (a -> ReaderT (Env a) m b) -> ReaderT (Env a) m b Source #

Loop for ground truth

loopD :: forall a m b. (BoundingBox a, Monad m) => (b -> b -> b) -> b -> (Detection a -> ReaderT (Env a) m b) -> ReaderT (Env a) m b Source #

Loop for detection

whenInterestAreaD :: forall m a b. (Monad m, BoundingBox a) => Bool -> Detection a -> ReaderT (Env a) m [b] -> ReaderT (Env a) m [b] Source #

whenInterestAreaG :: forall m a b. (Monad m, BoundingBox a) => Bool -> a -> ReaderT (Env a) m [b] -> ReaderT (Env a) m [b] Source #

runRisk :: forall context a. World context a => context -> [(ImgIdx a, Double)] Source #

runRiskWithError :: forall context a. World context a => context -> [(ImgIdx a, [Risk a])] Source #

generateRiskWeightedImages :: forall b a. World b a => b -> [ImgIdx a] Source #