{-# LANGUAGE Safe #-}
module Types.Pragma (
CodeVisibility(..),
Pragma(..),
TraceType(..),
WithVisibility(..),
getPragmaContext,
hasCodeVisibility,
isExprLookup,
isModuleOnly,
isNoTrace,
isSourceContext,
isTestsOnly,
isTraceCreation,
mapCodeVisibility,
updateCodeVisibility,
) where
import qualified Data.Set as Set
data CodeVisibility = ModuleOnly | TestsOnly | FromDependency deriving (CodeVisibility -> CodeVisibility -> Bool
(CodeVisibility -> CodeVisibility -> Bool)
-> (CodeVisibility -> CodeVisibility -> Bool) -> Eq CodeVisibility
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeVisibility -> CodeVisibility -> Bool
$c/= :: CodeVisibility -> CodeVisibility -> Bool
== :: CodeVisibility -> CodeVisibility -> Bool
$c== :: CodeVisibility -> CodeVisibility -> Bool
Eq,Eq CodeVisibility
Eq CodeVisibility
-> (CodeVisibility -> CodeVisibility -> Ordering)
-> (CodeVisibility -> CodeVisibility -> Bool)
-> (CodeVisibility -> CodeVisibility -> Bool)
-> (CodeVisibility -> CodeVisibility -> Bool)
-> (CodeVisibility -> CodeVisibility -> Bool)
-> (CodeVisibility -> CodeVisibility -> CodeVisibility)
-> (CodeVisibility -> CodeVisibility -> CodeVisibility)
-> Ord CodeVisibility
CodeVisibility -> CodeVisibility -> Bool
CodeVisibility -> CodeVisibility -> Ordering
CodeVisibility -> CodeVisibility -> CodeVisibility
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CodeVisibility -> CodeVisibility -> CodeVisibility
$cmin :: CodeVisibility -> CodeVisibility -> CodeVisibility
max :: CodeVisibility -> CodeVisibility -> CodeVisibility
$cmax :: CodeVisibility -> CodeVisibility -> CodeVisibility
>= :: CodeVisibility -> CodeVisibility -> Bool
$c>= :: CodeVisibility -> CodeVisibility -> Bool
> :: CodeVisibility -> CodeVisibility -> Bool
$c> :: CodeVisibility -> CodeVisibility -> Bool
<= :: CodeVisibility -> CodeVisibility -> Bool
$c<= :: CodeVisibility -> CodeVisibility -> Bool
< :: CodeVisibility -> CodeVisibility -> Bool
$c< :: CodeVisibility -> CodeVisibility -> Bool
compare :: CodeVisibility -> CodeVisibility -> Ordering
$ccompare :: CodeVisibility -> CodeVisibility -> Ordering
$cp1Ord :: Eq CodeVisibility
Ord,Int -> CodeVisibility -> ShowS
[CodeVisibility] -> ShowS
CodeVisibility -> String
(Int -> CodeVisibility -> ShowS)
-> (CodeVisibility -> String)
-> ([CodeVisibility] -> ShowS)
-> Show CodeVisibility
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeVisibility] -> ShowS
$cshowList :: [CodeVisibility] -> ShowS
show :: CodeVisibility -> String
$cshow :: CodeVisibility -> String
showsPrec :: Int -> CodeVisibility -> ShowS
$cshowsPrec :: Int -> CodeVisibility -> ShowS
Show)
data WithVisibility a =
WithVisibility {
WithVisibility a -> Set CodeVisibility
wvVisibility :: Set.Set CodeVisibility,
WithVisibility a -> a
wvData :: a
}
deriving (Int -> WithVisibility a -> ShowS
[WithVisibility a] -> ShowS
WithVisibility a -> String
(Int -> WithVisibility a -> ShowS)
-> (WithVisibility a -> String)
-> ([WithVisibility a] -> ShowS)
-> Show (WithVisibility a)
forall a. Show a => Int -> WithVisibility a -> ShowS
forall a. Show a => [WithVisibility a] -> ShowS
forall a. Show a => WithVisibility a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithVisibility a] -> ShowS
$cshowList :: forall a. Show a => [WithVisibility a] -> ShowS
show :: WithVisibility a -> String
$cshow :: forall a. Show a => WithVisibility a -> String
showsPrec :: Int -> WithVisibility a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> WithVisibility a -> ShowS
Show)
hasCodeVisibility :: CodeVisibility -> WithVisibility a -> Bool
hasCodeVisibility :: CodeVisibility -> WithVisibility a -> Bool
hasCodeVisibility CodeVisibility
v = CodeVisibility -> Set CodeVisibility -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member CodeVisibility
v (Set CodeVisibility -> Bool)
-> (WithVisibility a -> Set CodeVisibility)
-> WithVisibility a
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WithVisibility a -> Set CodeVisibility
forall a. WithVisibility a -> Set CodeVisibility
wvVisibility
mapCodeVisibility :: (a -> b) -> WithVisibility a -> WithVisibility b
mapCodeVisibility :: (a -> b) -> WithVisibility a -> WithVisibility b
mapCodeVisibility a -> b
f (WithVisibility Set CodeVisibility
v a
x) = Set CodeVisibility -> b -> WithVisibility b
forall a. Set CodeVisibility -> a -> WithVisibility a
WithVisibility Set CodeVisibility
v (a -> b
f a
x)
updateCodeVisibility :: (Set.Set CodeVisibility -> Set.Set CodeVisibility) ->
WithVisibility a -> WithVisibility a
updateCodeVisibility :: (Set CodeVisibility -> Set CodeVisibility)
-> WithVisibility a -> WithVisibility a
updateCodeVisibility Set CodeVisibility -> Set CodeVisibility
f (WithVisibility Set CodeVisibility
v a
x) = Set CodeVisibility -> a -> WithVisibility a
forall a. Set CodeVisibility -> a -> WithVisibility a
WithVisibility (Set CodeVisibility -> Set CodeVisibility
f Set CodeVisibility
v) a
x
data TraceType = NoTrace | TraceCreation deriving (Int -> TraceType -> ShowS
[TraceType] -> ShowS
TraceType -> String
(Int -> TraceType -> ShowS)
-> (TraceType -> String)
-> ([TraceType] -> ShowS)
-> Show TraceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TraceType] -> ShowS
$cshowList :: [TraceType] -> ShowS
show :: TraceType -> String
$cshow :: TraceType -> String
showsPrec :: Int -> TraceType -> ShowS
$cshowsPrec :: Int -> TraceType -> ShowS
Show)
data Pragma c =
PragmaVisibility {
Pragma c -> [c]
pvContext :: [c],
Pragma c -> CodeVisibility
pvScopes :: CodeVisibility
} |
PragmaExprLookup {
Pragma c -> [c]
pelContext :: [c],
Pragma c -> String
pelName :: String
} |
PragmaSourceContext {
Pragma c -> c
pscContext :: c
} |
PragmaTracing {
Pragma c -> [c]
ptContext :: [c],
Pragma c -> TraceType
ptType :: TraceType
} |
{
Pragma c -> [c]
pcContext :: [c],
:: String
}
deriving (Int -> Pragma c -> ShowS
[Pragma c] -> ShowS
Pragma c -> String
(Int -> Pragma c -> ShowS)
-> (Pragma c -> String) -> ([Pragma c] -> ShowS) -> Show (Pragma c)
forall c. Show c => Int -> Pragma c -> ShowS
forall c. Show c => [Pragma c] -> ShowS
forall c. Show c => Pragma c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pragma c] -> ShowS
$cshowList :: forall c. Show c => [Pragma c] -> ShowS
show :: Pragma c -> String
$cshow :: forall c. Show c => Pragma c -> String
showsPrec :: Int -> Pragma c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> Pragma c -> ShowS
Show)
getPragmaContext :: Pragma c -> [c]
getPragmaContext :: Pragma c -> [c]
getPragmaContext (PragmaVisibility [c]
c CodeVisibility
_) = [c]
c
getPragmaContext (PragmaExprLookup [c]
c String
_) = [c]
c
getPragmaContext (PragmaSourceContext c
c) = [c
c]
getPragmaContext (PragmaTracing [c]
c TraceType
_) = [c]
c
getPragmaContext (PragmaComment [c]
c String
_) = [c]
c
isModuleOnly :: Pragma c -> Bool
isModuleOnly :: Pragma c -> Bool
isModuleOnly (PragmaVisibility [c]
_ CodeVisibility
ModuleOnly) = Bool
True
isModuleOnly Pragma c
_ = Bool
False
isExprLookup :: Pragma c -> Bool
isExprLookup :: Pragma c -> Bool
isExprLookup (PragmaExprLookup [c]
_ String
_) = Bool
True
isExprLookup Pragma c
_ = Bool
False
isSourceContext :: Pragma c -> Bool
isSourceContext :: Pragma c -> Bool
isSourceContext (PragmaSourceContext c
_) = Bool
True
isSourceContext Pragma c
_ = Bool
False
isNoTrace :: Pragma c -> Bool
isNoTrace :: Pragma c -> Bool
isNoTrace (PragmaTracing [c]
_ TraceType
NoTrace) = Bool
True
isNoTrace Pragma c
_ = Bool
False
isTraceCreation :: Pragma c -> Bool
isTraceCreation :: Pragma c -> Bool
isTraceCreation (PragmaTracing [c]
_ TraceType
TraceCreation) = Bool
True
isTraceCreation Pragma c
_ = Bool
False
isTestsOnly :: Pragma c -> Bool
isTestsOnly :: Pragma c -> Bool
isTestsOnly (PragmaVisibility [c]
_ CodeVisibility
TestsOnly) = Bool
True
isTestsOnly Pragma c
_ = Bool
False