{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE Safe #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Annotations.Primitive
( dontTranslate
, hasBlackBox
, warnNonSynthesizable
, warnAlways
, Primitive(..)
, HDL(..)
, PrimitiveGuard(..)
, PrimitiveWarning(..)
, extractPrim
, extractWarnings
) where
import Control.DeepSeq (NFData)
import Data.Binary (Binary)
import Data.Data
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
dontTranslate :: PrimitiveGuard ()
dontTranslate :: PrimitiveGuard ()
dontTranslate = PrimitiveGuard ()
forall a. PrimitiveGuard a
DontTranslate
hasBlackBox :: PrimitiveGuard ()
hasBlackBox :: PrimitiveGuard ()
hasBlackBox = [PrimitiveWarning] -> () -> PrimitiveGuard ()
forall a. [PrimitiveWarning] -> a -> PrimitiveGuard a
HasBlackBox [] ()
warnNonSynthesizable :: String -> PrimitiveGuard ()
warnNonSynthesizable :: String -> PrimitiveGuard ()
warnNonSynthesizable String
s = [PrimitiveWarning] -> () -> PrimitiveGuard ()
forall a. [PrimitiveWarning] -> a -> PrimitiveGuard a
HasBlackBox [String -> PrimitiveWarning
WarnNonSynthesizable String
s] ()
warnAlways :: String -> PrimitiveGuard ()
warnAlways :: String -> PrimitiveGuard ()
warnAlways String
s = [PrimitiveWarning] -> () -> PrimitiveGuard ()
forall a. [PrimitiveWarning] -> a -> PrimitiveGuard a
HasBlackBox [String -> PrimitiveWarning
WarnAlways String
s] ()
data HDL
= SystemVerilog
| Verilog
| VHDL
deriving (HDL -> HDL -> Bool
(HDL -> HDL -> Bool) -> (HDL -> HDL -> Bool) -> Eq HDL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HDL -> HDL -> Bool
$c/= :: HDL -> HDL -> Bool
== :: HDL -> HDL -> Bool
$c== :: HDL -> HDL -> Bool
Eq, Int -> HDL -> ShowS
[HDL] -> ShowS
HDL -> String
(Int -> HDL -> ShowS)
-> (HDL -> String) -> ([HDL] -> ShowS) -> Show HDL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HDL] -> ShowS
$cshowList :: [HDL] -> ShowS
show :: HDL -> String
$cshow :: HDL -> String
showsPrec :: Int -> HDL -> ShowS
$cshowsPrec :: Int -> HDL -> ShowS
Show, ReadPrec [HDL]
ReadPrec HDL
Int -> ReadS HDL
ReadS [HDL]
(Int -> ReadS HDL)
-> ReadS [HDL] -> ReadPrec HDL -> ReadPrec [HDL] -> Read HDL
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HDL]
$creadListPrec :: ReadPrec [HDL]
readPrec :: ReadPrec HDL
$creadPrec :: ReadPrec HDL
readList :: ReadS [HDL]
$creadList :: ReadS [HDL]
readsPrec :: Int -> ReadS HDL
$creadsPrec :: Int -> ReadS HDL
Read, Typeable HDL
DataType
Constr
Typeable HDL
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HDL -> c HDL)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HDL)
-> (HDL -> Constr)
-> (HDL -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HDL))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HDL))
-> ((forall b. Data b => b -> b) -> HDL -> HDL)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r)
-> (forall u. (forall d. Data d => d -> u) -> HDL -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> HDL -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL)
-> Data HDL
HDL -> DataType
HDL -> Constr
(forall b. Data b => b -> b) -> HDL -> HDL
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HDL -> c HDL
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HDL
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> HDL -> u
forall u. (forall d. Data d => d -> u) -> HDL -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HDL
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HDL -> c HDL
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HDL)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HDL)
$cVHDL :: Constr
$cVerilog :: Constr
$cSystemVerilog :: Constr
$tHDL :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> HDL -> m HDL
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL
gmapMp :: (forall d. Data d => d -> m d) -> HDL -> m HDL
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL
gmapM :: (forall d. Data d => d -> m d) -> HDL -> m HDL
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> HDL -> m HDL
gmapQi :: Int -> (forall d. Data d => d -> u) -> HDL -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HDL -> u
gmapQ :: (forall d. Data d => d -> u) -> HDL -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HDL -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HDL -> r
gmapT :: (forall b. Data b => b -> b) -> HDL -> HDL
$cgmapT :: (forall b. Data b => b -> b) -> HDL -> HDL
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HDL)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HDL)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c HDL)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HDL)
dataTypeOf :: HDL -> DataType
$cdataTypeOf :: HDL -> DataType
toConstr :: HDL -> Constr
$ctoConstr :: HDL -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HDL
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HDL
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HDL -> c HDL
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HDL -> c HDL
$cp1Data :: Typeable HDL
Data, (forall x. HDL -> Rep HDL x)
-> (forall x. Rep HDL x -> HDL) -> Generic HDL
forall x. Rep HDL x -> HDL
forall x. HDL -> Rep HDL x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HDL x -> HDL
$cfrom :: forall x. HDL -> Rep HDL x
Generic, HDL -> ()
(HDL -> ()) -> NFData HDL
forall a. (a -> ()) -> NFData a
rnf :: HDL -> ()
$crnf :: HDL -> ()
NFData, Eq HDL
Eq HDL -> (Int -> HDL -> Int) -> (HDL -> Int) -> Hashable HDL
Int -> HDL -> Int
HDL -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: HDL -> Int
$chash :: HDL -> Int
hashWithSalt :: Int -> HDL -> Int
$chashWithSalt :: Int -> HDL -> Int
$cp1Hashable :: Eq HDL
Hashable, Int -> HDL
HDL -> Int
HDL -> [HDL]
HDL -> HDL
HDL -> HDL -> [HDL]
HDL -> HDL -> HDL -> [HDL]
(HDL -> HDL)
-> (HDL -> HDL)
-> (Int -> HDL)
-> (HDL -> Int)
-> (HDL -> [HDL])
-> (HDL -> HDL -> [HDL])
-> (HDL -> HDL -> [HDL])
-> (HDL -> HDL -> HDL -> [HDL])
-> Enum HDL
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: HDL -> HDL -> HDL -> [HDL]
$cenumFromThenTo :: HDL -> HDL -> HDL -> [HDL]
enumFromTo :: HDL -> HDL -> [HDL]
$cenumFromTo :: HDL -> HDL -> [HDL]
enumFromThen :: HDL -> HDL -> [HDL]
$cenumFromThen :: HDL -> HDL -> [HDL]
enumFrom :: HDL -> [HDL]
$cenumFrom :: HDL -> [HDL]
fromEnum :: HDL -> Int
$cfromEnum :: HDL -> Int
toEnum :: Int -> HDL
$ctoEnum :: Int -> HDL
pred :: HDL -> HDL
$cpred :: HDL -> HDL
succ :: HDL -> HDL
$csucc :: HDL -> HDL
Enum, HDL
HDL -> HDL -> Bounded HDL
forall a. a -> a -> Bounded a
maxBound :: HDL
$cmaxBound :: HDL
minBound :: HDL
$cminBound :: HDL
Bounded)
data Primitive
= Primitive [HDL] FilePath
| InlinePrimitive [HDL] String
deriving (Int -> Primitive -> ShowS
[Primitive] -> ShowS
Primitive -> String
(Int -> Primitive -> ShowS)
-> (Primitive -> String)
-> ([Primitive] -> ShowS)
-> Show Primitive
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Primitive] -> ShowS
$cshowList :: [Primitive] -> ShowS
show :: Primitive -> String
$cshow :: Primitive -> String
showsPrec :: Int -> Primitive -> ShowS
$cshowsPrec :: Int -> Primitive -> ShowS
Show, ReadPrec [Primitive]
ReadPrec Primitive
Int -> ReadS Primitive
ReadS [Primitive]
(Int -> ReadS Primitive)
-> ReadS [Primitive]
-> ReadPrec Primitive
-> ReadPrec [Primitive]
-> Read Primitive
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Primitive]
$creadListPrec :: ReadPrec [Primitive]
readPrec :: ReadPrec Primitive
$creadPrec :: ReadPrec Primitive
readList :: ReadS [Primitive]
$creadList :: ReadS [Primitive]
readsPrec :: Int -> ReadS Primitive
$creadsPrec :: Int -> ReadS Primitive
Read, Typeable Primitive
DataType
Constr
Typeable Primitive
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive)
-> (Primitive -> Constr)
-> (Primitive -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Primitive))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive))
-> ((forall b. Data b => b -> b) -> Primitive -> Primitive)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r)
-> (forall u. (forall d. Data d => d -> u) -> Primitive -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Primitive -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive)
-> Data Primitive
Primitive -> DataType
Primitive -> Constr
(forall b. Data b => b -> b) -> Primitive -> Primitive
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Primitive -> u
forall u. (forall d. Data d => d -> u) -> Primitive -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Primitive)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive)
$cInlinePrimitive :: Constr
$cPrimitive :: Constr
$tPrimitive :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Primitive -> m Primitive
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
gmapMp :: (forall d. Data d => d -> m d) -> Primitive -> m Primitive
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
gmapM :: (forall d. Data d => d -> m d) -> Primitive -> m Primitive
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Primitive -> m Primitive
gmapQi :: Int -> (forall d. Data d => d -> u) -> Primitive -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Primitive -> u
gmapQ :: (forall d. Data d => d -> u) -> Primitive -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Primitive -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Primitive -> r
gmapT :: (forall b. Data b => b -> b) -> Primitive -> Primitive
$cgmapT :: (forall b. Data b => b -> b) -> Primitive -> Primitive
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Primitive)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Primitive)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Primitive)
dataTypeOf :: Primitive -> DataType
$cdataTypeOf :: Primitive -> DataType
toConstr :: Primitive -> Constr
$ctoConstr :: Primitive -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Primitive
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Primitive -> c Primitive
$cp1Data :: Typeable Primitive
Data, (forall x. Primitive -> Rep Primitive x)
-> (forall x. Rep Primitive x -> Primitive) -> Generic Primitive
forall x. Rep Primitive x -> Primitive
forall x. Primitive -> Rep Primitive x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Primitive x -> Primitive
$cfrom :: forall x. Primitive -> Rep Primitive x
Generic, Primitive -> ()
(Primitive -> ()) -> NFData Primitive
forall a. (a -> ()) -> NFData a
rnf :: Primitive -> ()
$crnf :: Primitive -> ()
NFData, Eq Primitive
Eq Primitive
-> (Int -> Primitive -> Int)
-> (Primitive -> Int)
-> Hashable Primitive
Int -> Primitive -> Int
Primitive -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Primitive -> Int
$chash :: Primitive -> Int
hashWithSalt :: Int -> Primitive -> Int
$chashWithSalt :: Int -> Primitive -> Int
$cp1Hashable :: Eq Primitive
Hashable, Primitive -> Primitive -> Bool
(Primitive -> Primitive -> Bool)
-> (Primitive -> Primitive -> Bool) -> Eq Primitive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Primitive -> Primitive -> Bool
$c/= :: Primitive -> Primitive -> Bool
== :: Primitive -> Primitive -> Bool
$c== :: Primitive -> Primitive -> Bool
Eq)
data PrimitiveGuard a
= DontTranslate
| HasBlackBox [PrimitiveWarning] a
deriving
( Int -> PrimitiveGuard a -> ShowS
[PrimitiveGuard a] -> ShowS
PrimitiveGuard a -> String
(Int -> PrimitiveGuard a -> ShowS)
-> (PrimitiveGuard a -> String)
-> ([PrimitiveGuard a] -> ShowS)
-> Show (PrimitiveGuard a)
forall a. Show a => Int -> PrimitiveGuard a -> ShowS
forall a. Show a => [PrimitiveGuard a] -> ShowS
forall a. Show a => PrimitiveGuard a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrimitiveGuard a] -> ShowS
$cshowList :: forall a. Show a => [PrimitiveGuard a] -> ShowS
show :: PrimitiveGuard a -> String
$cshow :: forall a. Show a => PrimitiveGuard a -> String
showsPrec :: Int -> PrimitiveGuard a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> PrimitiveGuard a -> ShowS
Show, ReadPrec [PrimitiveGuard a]
ReadPrec (PrimitiveGuard a)
Int -> ReadS (PrimitiveGuard a)
ReadS [PrimitiveGuard a]
(Int -> ReadS (PrimitiveGuard a))
-> ReadS [PrimitiveGuard a]
-> ReadPrec (PrimitiveGuard a)
-> ReadPrec [PrimitiveGuard a]
-> Read (PrimitiveGuard a)
forall a. Read a => ReadPrec [PrimitiveGuard a]
forall a. Read a => ReadPrec (PrimitiveGuard a)
forall a. Read a => Int -> ReadS (PrimitiveGuard a)
forall a. Read a => ReadS [PrimitiveGuard a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrimitiveGuard a]
$creadListPrec :: forall a. Read a => ReadPrec [PrimitiveGuard a]
readPrec :: ReadPrec (PrimitiveGuard a)
$creadPrec :: forall a. Read a => ReadPrec (PrimitiveGuard a)
readList :: ReadS [PrimitiveGuard a]
$creadList :: forall a. Read a => ReadS [PrimitiveGuard a]
readsPrec :: Int -> ReadS (PrimitiveGuard a)
$creadsPrec :: forall a. Read a => Int -> ReadS (PrimitiveGuard a)
Read, Typeable (PrimitiveGuard a)
DataType
Constr
Typeable (PrimitiveGuard a)
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PrimitiveGuard a
-> c (PrimitiveGuard a))
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PrimitiveGuard a))
-> (PrimitiveGuard a -> Constr)
-> (PrimitiveGuard a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PrimitiveGuard a)))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PrimitiveGuard a)))
-> ((forall b. Data b => b -> b)
-> PrimitiveGuard a -> PrimitiveGuard a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> PrimitiveGuard a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveGuard a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a))
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a))
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a))
-> Data (PrimitiveGuard a)
PrimitiveGuard a -> DataType
PrimitiveGuard a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (PrimitiveGuard a))
(forall b. Data b => b -> b)
-> PrimitiveGuard a -> PrimitiveGuard a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveGuard a -> c (PrimitiveGuard a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PrimitiveGuard a)
forall a. Data a => Typeable (PrimitiveGuard a)
forall a. Data a => PrimitiveGuard a -> DataType
forall a. Data a => PrimitiveGuard a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b)
-> PrimitiveGuard a -> PrimitiveGuard a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> PrimitiveGuard a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> PrimitiveGuard a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PrimitiveGuard a)
forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveGuard a -> c (PrimitiveGuard a)
forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PrimitiveGuard a))
forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PrimitiveGuard a))
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveGuard a -> u
forall u. (forall d. Data d => d -> u) -> PrimitiveGuard a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PrimitiveGuard a)
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveGuard a -> c (PrimitiveGuard a)
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (PrimitiveGuard a))
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PrimitiveGuard a))
$cHasBlackBox :: Constr
$cDontTranslate :: Constr
$tPrimitiveGuard :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
$cgmapMo :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
gmapMp :: (forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
$cgmapMp :: forall a (m :: Type -> Type).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
gmapM :: (forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
$cgmapM :: forall a (m :: Type -> Type).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> PrimitiveGuard a -> m (PrimitiveGuard a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimitiveGuard a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> PrimitiveGuard a -> u
gmapQ :: (forall d. Data d => d -> u) -> PrimitiveGuard a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> PrimitiveGuard a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveGuard a -> r
gmapT :: (forall b. Data b => b -> b)
-> PrimitiveGuard a -> PrimitiveGuard a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> PrimitiveGuard a -> PrimitiveGuard a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PrimitiveGuard a))
$cdataCast2 :: forall a (t :: Type -> Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (PrimitiveGuard a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (PrimitiveGuard a))
$cdataCast1 :: forall a (t :: Type -> Type) (c :: Type -> Type).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (PrimitiveGuard a))
dataTypeOf :: PrimitiveGuard a -> DataType
$cdataTypeOf :: forall a. Data a => PrimitiveGuard a -> DataType
toConstr :: PrimitiveGuard a -> Constr
$ctoConstr :: forall a. Data a => PrimitiveGuard a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PrimitiveGuard a)
$cgunfold :: forall a (c :: Type -> Type).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (PrimitiveGuard a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveGuard a -> c (PrimitiveGuard a)
$cgfoldl :: forall a (c :: Type -> Type).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveGuard a -> c (PrimitiveGuard a)
$cp1Data :: forall a. Data a => Typeable (PrimitiveGuard a)
Data, (forall x. PrimitiveGuard a -> Rep (PrimitiveGuard a) x)
-> (forall x. Rep (PrimitiveGuard a) x -> PrimitiveGuard a)
-> Generic (PrimitiveGuard a)
forall x. Rep (PrimitiveGuard a) x -> PrimitiveGuard a
forall x. PrimitiveGuard a -> Rep (PrimitiveGuard a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (PrimitiveGuard a) x -> PrimitiveGuard a
forall a x. PrimitiveGuard a -> Rep (PrimitiveGuard a) x
$cto :: forall a x. Rep (PrimitiveGuard a) x -> PrimitiveGuard a
$cfrom :: forall a x. PrimitiveGuard a -> Rep (PrimitiveGuard a) x
Generic, PrimitiveGuard a -> ()
(PrimitiveGuard a -> ()) -> NFData (PrimitiveGuard a)
forall a. NFData a => PrimitiveGuard a -> ()
forall a. (a -> ()) -> NFData a
rnf :: PrimitiveGuard a -> ()
$crnf :: forall a. NFData a => PrimitiveGuard a -> ()
NFData, Eq (PrimitiveGuard a)
Eq (PrimitiveGuard a)
-> (Int -> PrimitiveGuard a -> Int)
-> (PrimitiveGuard a -> Int)
-> Hashable (PrimitiveGuard a)
Int -> PrimitiveGuard a -> Int
PrimitiveGuard a -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall a. Hashable a => Eq (PrimitiveGuard a)
forall a. Hashable a => Int -> PrimitiveGuard a -> Int
forall a. Hashable a => PrimitiveGuard a -> Int
hash :: PrimitiveGuard a -> Int
$chash :: forall a. Hashable a => PrimitiveGuard a -> Int
hashWithSalt :: Int -> PrimitiveGuard a -> Int
$chashWithSalt :: forall a. Hashable a => Int -> PrimitiveGuard a -> Int
$cp1Hashable :: forall a. Hashable a => Eq (PrimitiveGuard a)
Hashable, a -> PrimitiveGuard b -> PrimitiveGuard a
(a -> b) -> PrimitiveGuard a -> PrimitiveGuard b
(forall a b. (a -> b) -> PrimitiveGuard a -> PrimitiveGuard b)
-> (forall a b. a -> PrimitiveGuard b -> PrimitiveGuard a)
-> Functor PrimitiveGuard
forall a b. a -> PrimitiveGuard b -> PrimitiveGuard a
forall a b. (a -> b) -> PrimitiveGuard a -> PrimitiveGuard b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> PrimitiveGuard b -> PrimitiveGuard a
$c<$ :: forall a b. a -> PrimitiveGuard b -> PrimitiveGuard a
fmap :: (a -> b) -> PrimitiveGuard a -> PrimitiveGuard b
$cfmap :: forall a b. (a -> b) -> PrimitiveGuard a -> PrimitiveGuard b
Functor, PrimitiveGuard a -> Bool
(a -> m) -> PrimitiveGuard a -> m
(a -> b -> b) -> b -> PrimitiveGuard a -> b
(forall m. Monoid m => PrimitiveGuard m -> m)
-> (forall m a. Monoid m => (a -> m) -> PrimitiveGuard a -> m)
-> (forall m a. Monoid m => (a -> m) -> PrimitiveGuard a -> m)
-> (forall a b. (a -> b -> b) -> b -> PrimitiveGuard a -> b)
-> (forall a b. (a -> b -> b) -> b -> PrimitiveGuard a -> b)
-> (forall b a. (b -> a -> b) -> b -> PrimitiveGuard a -> b)
-> (forall b a. (b -> a -> b) -> b -> PrimitiveGuard a -> b)
-> (forall a. (a -> a -> a) -> PrimitiveGuard a -> a)
-> (forall a. (a -> a -> a) -> PrimitiveGuard a -> a)
-> (forall a. PrimitiveGuard a -> [a])
-> (forall a. PrimitiveGuard a -> Bool)
-> (forall a. PrimitiveGuard a -> Int)
-> (forall a. Eq a => a -> PrimitiveGuard a -> Bool)
-> (forall a. Ord a => PrimitiveGuard a -> a)
-> (forall a. Ord a => PrimitiveGuard a -> a)
-> (forall a. Num a => PrimitiveGuard a -> a)
-> (forall a. Num a => PrimitiveGuard a -> a)
-> Foldable PrimitiveGuard
forall a. Eq a => a -> PrimitiveGuard a -> Bool
forall a. Num a => PrimitiveGuard a -> a
forall a. Ord a => PrimitiveGuard a -> a
forall m. Monoid m => PrimitiveGuard m -> m
forall a. PrimitiveGuard a -> Bool
forall a. PrimitiveGuard a -> Int
forall a. PrimitiveGuard a -> [a]
forall a. (a -> a -> a) -> PrimitiveGuard a -> a
forall m a. Monoid m => (a -> m) -> PrimitiveGuard a -> m
forall b a. (b -> a -> b) -> b -> PrimitiveGuard a -> b
forall a b. (a -> b -> b) -> b -> PrimitiveGuard a -> b
forall (t :: Type -> Type).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: PrimitiveGuard a -> a
$cproduct :: forall a. Num a => PrimitiveGuard a -> a
sum :: PrimitiveGuard a -> a
$csum :: forall a. Num a => PrimitiveGuard a -> a
minimum :: PrimitiveGuard a -> a
$cminimum :: forall a. Ord a => PrimitiveGuard a -> a
maximum :: PrimitiveGuard a -> a
$cmaximum :: forall a. Ord a => PrimitiveGuard a -> a
elem :: a -> PrimitiveGuard a -> Bool
$celem :: forall a. Eq a => a -> PrimitiveGuard a -> Bool
length :: PrimitiveGuard a -> Int
$clength :: forall a. PrimitiveGuard a -> Int
null :: PrimitiveGuard a -> Bool
$cnull :: forall a. PrimitiveGuard a -> Bool
toList :: PrimitiveGuard a -> [a]
$ctoList :: forall a. PrimitiveGuard a -> [a]
foldl1 :: (a -> a -> a) -> PrimitiveGuard a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> PrimitiveGuard a -> a
foldr1 :: (a -> a -> a) -> PrimitiveGuard a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> PrimitiveGuard a -> a
foldl' :: (b -> a -> b) -> b -> PrimitiveGuard a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> PrimitiveGuard a -> b
foldl :: (b -> a -> b) -> b -> PrimitiveGuard a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> PrimitiveGuard a -> b
foldr' :: (a -> b -> b) -> b -> PrimitiveGuard a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> PrimitiveGuard a -> b
foldr :: (a -> b -> b) -> b -> PrimitiveGuard a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> PrimitiveGuard a -> b
foldMap' :: (a -> m) -> PrimitiveGuard a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> PrimitiveGuard a -> m
foldMap :: (a -> m) -> PrimitiveGuard a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> PrimitiveGuard a -> m
fold :: PrimitiveGuard m -> m
$cfold :: forall m. Monoid m => PrimitiveGuard m -> m
Foldable
, Functor PrimitiveGuard
Foldable PrimitiveGuard
Functor PrimitiveGuard
-> Foldable PrimitiveGuard
-> (forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> PrimitiveGuard a -> f (PrimitiveGuard b))
-> (forall (f :: Type -> Type) a.
Applicative f =>
PrimitiveGuard (f a) -> f (PrimitiveGuard a))
-> (forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> PrimitiveGuard a -> m (PrimitiveGuard b))
-> (forall (m :: Type -> Type) a.
Monad m =>
PrimitiveGuard (m a) -> m (PrimitiveGuard a))
-> Traversable PrimitiveGuard
(a -> f b) -> PrimitiveGuard a -> f (PrimitiveGuard b)
forall (t :: Type -> Type).
Functor t
-> Foldable t
-> (forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: Type -> Type) a.
Applicative f =>
t (f a) -> f (t a))
-> (forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: Type -> Type) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: Type -> Type) a.
Monad m =>
PrimitiveGuard (m a) -> m (PrimitiveGuard a)
forall (f :: Type -> Type) a.
Applicative f =>
PrimitiveGuard (f a) -> f (PrimitiveGuard a)
forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> PrimitiveGuard a -> m (PrimitiveGuard b)
forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> PrimitiveGuard a -> f (PrimitiveGuard b)
sequence :: PrimitiveGuard (m a) -> m (PrimitiveGuard a)
$csequence :: forall (m :: Type -> Type) a.
Monad m =>
PrimitiveGuard (m a) -> m (PrimitiveGuard a)
mapM :: (a -> m b) -> PrimitiveGuard a -> m (PrimitiveGuard b)
$cmapM :: forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> PrimitiveGuard a -> m (PrimitiveGuard b)
sequenceA :: PrimitiveGuard (f a) -> f (PrimitiveGuard a)
$csequenceA :: forall (f :: Type -> Type) a.
Applicative f =>
PrimitiveGuard (f a) -> f (PrimitiveGuard a)
traverse :: (a -> f b) -> PrimitiveGuard a -> f (PrimitiveGuard b)
$ctraverse :: forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> PrimitiveGuard a -> f (PrimitiveGuard b)
$cp2Traversable :: Foldable PrimitiveGuard
$cp1Traversable :: Functor PrimitiveGuard
Traversable, Get (PrimitiveGuard a)
[PrimitiveGuard a] -> Put
PrimitiveGuard a -> Put
(PrimitiveGuard a -> Put)
-> Get (PrimitiveGuard a)
-> ([PrimitiveGuard a] -> Put)
-> Binary (PrimitiveGuard a)
forall a. Binary a => Get (PrimitiveGuard a)
forall a. Binary a => [PrimitiveGuard a] -> Put
forall a. Binary a => PrimitiveGuard a -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [PrimitiveGuard a] -> Put
$cputList :: forall a. Binary a => [PrimitiveGuard a] -> Put
get :: Get (PrimitiveGuard a)
$cget :: forall a. Binary a => Get (PrimitiveGuard a)
put :: PrimitiveGuard a -> Put
$cput :: forall a. Binary a => PrimitiveGuard a -> Put
Binary, PrimitiveGuard a -> PrimitiveGuard a -> Bool
(PrimitiveGuard a -> PrimitiveGuard a -> Bool)
-> (PrimitiveGuard a -> PrimitiveGuard a -> Bool)
-> Eq (PrimitiveGuard a)
forall a. Eq a => PrimitiveGuard a -> PrimitiveGuard a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimitiveGuard a -> PrimitiveGuard a -> Bool
$c/= :: forall a. Eq a => PrimitiveGuard a -> PrimitiveGuard a -> Bool
== :: PrimitiveGuard a -> PrimitiveGuard a -> Bool
$c== :: forall a. Eq a => PrimitiveGuard a -> PrimitiveGuard a -> Bool
Eq )
data PrimitiveWarning
= WarnNonSynthesizable String
| WarnAlways String
deriving (Int -> PrimitiveWarning -> ShowS
[PrimitiveWarning] -> ShowS
PrimitiveWarning -> String
(Int -> PrimitiveWarning -> ShowS)
-> (PrimitiveWarning -> String)
-> ([PrimitiveWarning] -> ShowS)
-> Show PrimitiveWarning
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrimitiveWarning] -> ShowS
$cshowList :: [PrimitiveWarning] -> ShowS
show :: PrimitiveWarning -> String
$cshow :: PrimitiveWarning -> String
showsPrec :: Int -> PrimitiveWarning -> ShowS
$cshowsPrec :: Int -> PrimitiveWarning -> ShowS
Show, ReadPrec [PrimitiveWarning]
ReadPrec PrimitiveWarning
Int -> ReadS PrimitiveWarning
ReadS [PrimitiveWarning]
(Int -> ReadS PrimitiveWarning)
-> ReadS [PrimitiveWarning]
-> ReadPrec PrimitiveWarning
-> ReadPrec [PrimitiveWarning]
-> Read PrimitiveWarning
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrimitiveWarning]
$creadListPrec :: ReadPrec [PrimitiveWarning]
readPrec :: ReadPrec PrimitiveWarning
$creadPrec :: ReadPrec PrimitiveWarning
readList :: ReadS [PrimitiveWarning]
$creadList :: ReadS [PrimitiveWarning]
readsPrec :: Int -> ReadS PrimitiveWarning
$creadsPrec :: Int -> ReadS PrimitiveWarning
Read, Typeable PrimitiveWarning
DataType
Constr
Typeable PrimitiveWarning
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveWarning -> c PrimitiveWarning)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveWarning)
-> (PrimitiveWarning -> Constr)
-> (PrimitiveWarning -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimitiveWarning))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveWarning))
-> ((forall b. Data b => b -> b)
-> PrimitiveWarning -> PrimitiveWarning)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r)
-> (forall u.
(forall d. Data d => d -> u) -> PrimitiveWarning -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveWarning -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning)
-> Data PrimitiveWarning
PrimitiveWarning -> DataType
PrimitiveWarning -> Constr
(forall b. Data b => b -> b)
-> PrimitiveWarning -> PrimitiveWarning
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveWarning -> c PrimitiveWarning
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveWarning
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveWarning -> u
forall u. (forall d. Data d => d -> u) -> PrimitiveWarning -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveWarning
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveWarning -> c PrimitiveWarning
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimitiveWarning)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveWarning)
$cWarnAlways :: Constr
$cWarnNonSynthesizable :: Constr
$tPrimitiveWarning :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
gmapMp :: (forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
gmapM :: (forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveWarning -> m PrimitiveWarning
gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimitiveWarning -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveWarning -> u
gmapQ :: (forall d. Data d => d -> u) -> PrimitiveWarning -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PrimitiveWarning -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveWarning -> r
gmapT :: (forall b. Data b => b -> b)
-> PrimitiveWarning -> PrimitiveWarning
$cgmapT :: (forall b. Data b => b -> b)
-> PrimitiveWarning -> PrimitiveWarning
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveWarning)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveWarning)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PrimitiveWarning)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimitiveWarning)
dataTypeOf :: PrimitiveWarning -> DataType
$cdataTypeOf :: PrimitiveWarning -> DataType
toConstr :: PrimitiveWarning -> Constr
$ctoConstr :: PrimitiveWarning -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveWarning
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveWarning
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveWarning -> c PrimitiveWarning
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrimitiveWarning -> c PrimitiveWarning
$cp1Data :: Typeable PrimitiveWarning
Data, (forall x. PrimitiveWarning -> Rep PrimitiveWarning x)
-> (forall x. Rep PrimitiveWarning x -> PrimitiveWarning)
-> Generic PrimitiveWarning
forall x. Rep PrimitiveWarning x -> PrimitiveWarning
forall x. PrimitiveWarning -> Rep PrimitiveWarning x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PrimitiveWarning x -> PrimitiveWarning
$cfrom :: forall x. PrimitiveWarning -> Rep PrimitiveWarning x
Generic, PrimitiveWarning -> ()
(PrimitiveWarning -> ()) -> NFData PrimitiveWarning
forall a. (a -> ()) -> NFData a
rnf :: PrimitiveWarning -> ()
$crnf :: PrimitiveWarning -> ()
NFData, Eq PrimitiveWarning
Eq PrimitiveWarning
-> (Int -> PrimitiveWarning -> Int)
-> (PrimitiveWarning -> Int)
-> Hashable PrimitiveWarning
Int -> PrimitiveWarning -> Int
PrimitiveWarning -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PrimitiveWarning -> Int
$chash :: PrimitiveWarning -> Int
hashWithSalt :: Int -> PrimitiveWarning -> Int
$chashWithSalt :: Int -> PrimitiveWarning -> Int
$cp1Hashable :: Eq PrimitiveWarning
Hashable, Get PrimitiveWarning
[PrimitiveWarning] -> Put
PrimitiveWarning -> Put
(PrimitiveWarning -> Put)
-> Get PrimitiveWarning
-> ([PrimitiveWarning] -> Put)
-> Binary PrimitiveWarning
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [PrimitiveWarning] -> Put
$cputList :: [PrimitiveWarning] -> Put
get :: Get PrimitiveWarning
$cget :: Get PrimitiveWarning
put :: PrimitiveWarning -> Put
$cput :: PrimitiveWarning -> Put
Binary, PrimitiveWarning -> PrimitiveWarning -> Bool
(PrimitiveWarning -> PrimitiveWarning -> Bool)
-> (PrimitiveWarning -> PrimitiveWarning -> Bool)
-> Eq PrimitiveWarning
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimitiveWarning -> PrimitiveWarning -> Bool
$c/= :: PrimitiveWarning -> PrimitiveWarning -> Bool
== :: PrimitiveWarning -> PrimitiveWarning -> Bool
$c== :: PrimitiveWarning -> PrimitiveWarning -> Bool
Eq)
extractPrim
:: PrimitiveGuard a
-> Maybe a
=
\case
HasBlackBox [PrimitiveWarning]
_ a
p -> a -> Maybe a
forall a. a -> Maybe a
Just a
p
PrimitiveGuard a
DontTranslate -> Maybe a
forall a. Maybe a
Nothing
extractWarnings
:: PrimitiveGuard a
-> [PrimitiveWarning]
=
\case
HasBlackBox [PrimitiveWarning]
w a
_ -> [PrimitiveWarning]
w
PrimitiveGuard a
DontTranslate -> []