{-# LANGUAGE OverloadedStrings #-}
module Tokstyle.Analysis.SecurityRank.Lattice
( SecurityRank(..)
, mergeRank
, TaintState
) where
import Data.Map.Strict (Map)
import Data.Text (Text)
import Tokstyle.Analysis.Types (AbstractLocation)
data SecurityRank
= Bottom
| Safe
| Rank Int
deriving (SecurityRank -> SecurityRank -> Bool
(SecurityRank -> SecurityRank -> Bool)
-> (SecurityRank -> SecurityRank -> Bool) -> Eq SecurityRank
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecurityRank -> SecurityRank -> Bool
$c/= :: SecurityRank -> SecurityRank -> Bool
== :: SecurityRank -> SecurityRank -> Bool
$c== :: SecurityRank -> SecurityRank -> Bool
Eq, Int -> SecurityRank -> ShowS
[SecurityRank] -> ShowS
SecurityRank -> String
(Int -> SecurityRank -> ShowS)
-> (SecurityRank -> String)
-> ([SecurityRank] -> ShowS)
-> Show SecurityRank
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SecurityRank] -> ShowS
$cshowList :: [SecurityRank] -> ShowS
show :: SecurityRank -> String
$cshow :: SecurityRank -> String
showsPrec :: Int -> SecurityRank -> ShowS
$cshowsPrec :: Int -> SecurityRank -> ShowS
Show)
instance Ord SecurityRank where
compare :: SecurityRank -> SecurityRank -> Ordering
compare SecurityRank
Bottom SecurityRank
Bottom = Ordering
EQ
compare SecurityRank
Bottom SecurityRank
_ = Ordering
LT
compare SecurityRank
_ SecurityRank
Bottom = Ordering
GT
compare SecurityRank
Safe SecurityRank
Safe = Ordering
EQ
compare SecurityRank
Safe SecurityRank
_ = Ordering
GT
compare SecurityRank
_ SecurityRank
Safe = Ordering
LT
compare (Rank Int
a) (Rank Int
b) = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
a Int
b
mergeRank :: SecurityRank -> SecurityRank -> SecurityRank
mergeRank :: SecurityRank -> SecurityRank -> SecurityRank
mergeRank = SecurityRank -> SecurityRank -> SecurityRank
forall a. Ord a => a -> a -> a
min
type TaintState = Map AbstractLocation SecurityRank