module Ondim.Internal.Basic where
import Control.Monad.ST (RealWorld, ST)
import Data.HashMap.Strict qualified as Map
import Data.STRef (STRef)
import Data.Text qualified as T
import GHC.Exception (SrcLoc)
import GHC.Exts qualified as GHC
import GHC.IO (ioToST)
import Ondim.Internal.Class (OndimNode)
import System.FilePath (takeExtensions)
import Type.Reflection (SomeTypeRep)
newtype Ondim s a = Ondim
{ forall s a.
Ondim s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
unOndimT ::
ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
}
deriving newtype ((forall a b. (a -> b) -> Ondim s a -> Ondim s b)
-> (forall a b. a -> Ondim s b -> Ondim s a) -> Functor (Ondim s)
forall a b. a -> Ondim s b -> Ondim s a
forall a b. (a -> b) -> Ondim s a -> Ondim s b
forall s a b. a -> Ondim s b -> Ondim s a
forall s a b. (a -> b) -> Ondim s a -> Ondim s b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall s a b. (a -> b) -> Ondim s a -> Ondim s b
fmap :: forall a b. (a -> b) -> Ondim s a -> Ondim s b
$c<$ :: forall s a b. a -> Ondim s b -> Ondim s a
<$ :: forall a b. a -> Ondim s b -> Ondim s a
Functor, Functor (Ondim s)
Functor (Ondim s) =>
(forall a. a -> Ondim s a)
-> (forall a b. Ondim s (a -> b) -> Ondim s a -> Ondim s b)
-> (forall a b c.
(a -> b -> c) -> Ondim s a -> Ondim s b -> Ondim s c)
-> (forall a b. Ondim s a -> Ondim s b -> Ondim s b)
-> (forall a b. Ondim s a -> Ondim s b -> Ondim s a)
-> Applicative (Ondim s)
forall s. Functor (Ondim s)
forall a. a -> Ondim s a
forall s a. a -> Ondim s a
forall a b. Ondim s a -> Ondim s b -> Ondim s a
forall a b. Ondim s a -> Ondim s b -> Ondim s b
forall a b. Ondim s (a -> b) -> Ondim s a -> Ondim s b
forall s a b. Ondim s a -> Ondim s b -> Ondim s a
forall s a b. Ondim s a -> Ondim s b -> Ondim s b
forall s a b. Ondim s (a -> b) -> Ondim s a -> Ondim s b
forall a b c. (a -> b -> c) -> Ondim s a -> Ondim s b -> Ondim s c
forall s a b c.
(a -> b -> c) -> Ondim s a -> Ondim s b -> Ondim s c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall s a. a -> Ondim s a
pure :: forall a. a -> Ondim s a
$c<*> :: forall s a b. Ondim s (a -> b) -> Ondim s a -> Ondim s b
<*> :: forall a b. Ondim s (a -> b) -> Ondim s a -> Ondim s b
$cliftA2 :: forall s a b c.
(a -> b -> c) -> Ondim s a -> Ondim s b -> Ondim s c
liftA2 :: forall a b c. (a -> b -> c) -> Ondim s a -> Ondim s b -> Ondim s c
$c*> :: forall s a b. Ondim s a -> Ondim s b -> Ondim s b
*> :: forall a b. Ondim s a -> Ondim s b -> Ondim s b
$c<* :: forall s a b. Ondim s a -> Ondim s b -> Ondim s a
<* :: forall a b. Ondim s a -> Ondim s b -> Ondim s a
Applicative, Applicative (Ondim s)
Applicative (Ondim s) =>
(forall a b. Ondim s a -> (a -> Ondim s b) -> Ondim s b)
-> (forall a b. Ondim s a -> Ondim s b -> Ondim s b)
-> (forall a. a -> Ondim s a)
-> Monad (Ondim s)
forall s. Applicative (Ondim s)
forall a. a -> Ondim s a
forall s a. a -> Ondim s a
forall a b. Ondim s a -> Ondim s b -> Ondim s b
forall a b. Ondim s a -> (a -> Ondim s b) -> Ondim s b
forall s a b. Ondim s a -> Ondim s b -> Ondim s b
forall s a b. Ondim s a -> (a -> Ondim s b) -> Ondim s b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall s a b. Ondim s a -> (a -> Ondim s b) -> Ondim s b
>>= :: forall a b. Ondim s a -> (a -> Ondim s b) -> Ondim s b
$c>> :: forall s a b. Ondim s a -> Ondim s b -> Ondim s b
>> :: forall a b. Ondim s a -> Ondim s b -> Ondim s b
$creturn :: forall s a. a -> Ondim s a
return :: forall a. a -> Ondim s a
Monad)
liftST :: ST s a -> Ondim s a
liftST :: forall s a. ST s a -> Ondim s a
liftST = ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> Ondim s a
forall s a.
ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> Ondim s a
Ondim (ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> Ondim s a)
-> (ST s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a)
-> ST s a
-> Ondim s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT OndimException (ST s) a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
forall (m :: * -> *) a.
Monad m =>
m a -> ReaderT (TraceData, STRef s (OndimState s)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ExceptT OndimException (ST s) a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a)
-> (ST s a -> ExceptT OndimException (ST s) a)
-> ST s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ST s a -> ExceptT OndimException (ST s) a
forall (m :: * -> *) a.
Monad m =>
m a -> ExceptT OndimException m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
instance MonadIO (Ondim RealWorld) where
liftIO :: forall a. IO a -> Ondim RealWorld a
liftIO IO a
m = ST RealWorld a -> Ondim RealWorld a
forall s a. ST s a -> Ondim s a
liftST (ST RealWorld a -> Ondim RealWorld a)
-> ST RealWorld a -> Ondim RealWorld a
forall a b. (a -> b) -> a -> b
$ IO a -> ST RealWorld a
forall a. IO a -> ST RealWorld a
ioToST IO a
m
type Expansion s t = t -> Ondim s [t]
newtype Namespace m = Namespace {forall m. Namespace m -> HashMap Text (NamespaceItem m)
hashmap :: HashMap Text (NamespaceItem m)}
deriving ((forall x. Namespace m -> Rep (Namespace m) x)
-> (forall x. Rep (Namespace m) x -> Namespace m)
-> Generic (Namespace m)
forall x. Rep (Namespace m) x -> Namespace m
forall x. Namespace m -> Rep (Namespace m) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall m x. Rep (Namespace m) x -> Namespace m
forall m x. Namespace m -> Rep (Namespace m) x
$cfrom :: forall m x. Namespace m -> Rep (Namespace m) x
from :: forall x. Namespace m -> Rep (Namespace m) x
$cto :: forall m x. Rep (Namespace m) x -> Namespace m
to :: forall x. Rep (Namespace m) x -> Namespace m
Generic)
type PolyExpansion s = forall a. (OndimNode a) => Expansion s a
data NamespaceItem s where
TypedExpansion :: (Typeable a) => DefinitionSite -> Expansion s a -> NamespaceItem s
PolyExpansion :: DefinitionSite -> PolyExpansion s -> NamespaceItem s
TemplateData :: (OndimNode a) => DefinitionSite -> a -> NamespaceItem s
NamespaceData :: Namespace s -> NamespaceItem s
instance Semigroup (Namespace s) where
(Namespace HashMap Text (NamespaceItem s)
x) <> :: Namespace s -> Namespace s -> Namespace s
<> (Namespace HashMap Text (NamespaceItem s)
y) = HashMap Text (NamespaceItem s) -> Namespace s
forall m. HashMap Text (NamespaceItem m) -> Namespace m
Namespace (HashMap Text (NamespaceItem s) -> Namespace s)
-> HashMap Text (NamespaceItem s) -> Namespace s
forall a b. (a -> b) -> a -> b
$ (NamespaceItem s -> NamespaceItem s -> NamespaceItem s)
-> HashMap Text (NamespaceItem s)
-> HashMap Text (NamespaceItem s)
-> HashMap Text (NamespaceItem s)
forall k v.
Eq k =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
Map.unionWith NamespaceItem s -> NamespaceItem s -> NamespaceItem s
forall {s}. NamespaceItem s -> NamespaceItem s -> NamespaceItem s
f HashMap Text (NamespaceItem s)
x HashMap Text (NamespaceItem s)
y
where
f :: NamespaceItem s -> NamespaceItem s -> NamespaceItem s
f (NamespaceData Namespace s
n) (NamespaceData Namespace s
m) = Namespace s -> NamespaceItem s
forall s. Namespace s -> NamespaceItem s
NamespaceData (Namespace s -> NamespaceItem s) -> Namespace s -> NamespaceItem s
forall a b. (a -> b) -> a -> b
$ Namespace s
n Namespace s -> Namespace s -> Namespace s
forall a. Semigroup a => a -> a -> a
<> Namespace s
m
f NamespaceItem s
z NamespaceItem s
_ = NamespaceItem s
z
instance Monoid (Namespace s) where
mempty :: Namespace s
mempty = HashMap Text (NamespaceItem s) -> Namespace s
forall m. HashMap Text (NamespaceItem m) -> Namespace m
Namespace HashMap Text (NamespaceItem s)
forall a. Monoid a => a
mempty
newtype OndimState (s :: Type) = OndimState
{
forall s. OndimState s -> Namespace s
expansions :: Namespace s
}
deriving ((forall x. OndimState s -> Rep (OndimState s) x)
-> (forall x. Rep (OndimState s) x -> OndimState s)
-> Generic (OndimState s)
forall x. Rep (OndimState s) x -> OndimState s
forall x. OndimState s -> Rep (OndimState s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall s x. Rep (OndimState s) x -> OndimState s
forall s x. OndimState s -> Rep (OndimState s) x
$cfrom :: forall s x. OndimState s -> Rep (OndimState s) x
from :: forall x. OndimState s -> Rep (OndimState s) x
$cto :: forall s x. Rep (OndimState s) x -> OndimState s
to :: forall x. Rep (OndimState s) x -> OndimState s
Generic)
deriving newtype (NonEmpty (OndimState s) -> OndimState s
OndimState s -> OndimState s -> OndimState s
(OndimState s -> OndimState s -> OndimState s)
-> (NonEmpty (OndimState s) -> OndimState s)
-> (forall b. Integral b => b -> OndimState s -> OndimState s)
-> Semigroup (OndimState s)
forall b. Integral b => b -> OndimState s -> OndimState s
forall s. NonEmpty (OndimState s) -> OndimState s
forall s. OndimState s -> OndimState s -> OndimState s
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall s b. Integral b => b -> OndimState s -> OndimState s
$c<> :: forall s. OndimState s -> OndimState s -> OndimState s
<> :: OndimState s -> OndimState s -> OndimState s
$csconcat :: forall s. NonEmpty (OndimState s) -> OndimState s
sconcat :: NonEmpty (OndimState s) -> OndimState s
$cstimes :: forall s b. Integral b => b -> OndimState s -> OndimState s
stimes :: forall b. Integral b => b -> OndimState s -> OndimState s
Semigroup, Semigroup (OndimState s)
OndimState s
Semigroup (OndimState s) =>
OndimState s
-> (OndimState s -> OndimState s -> OndimState s)
-> ([OndimState s] -> OndimState s)
-> Monoid (OndimState s)
[OndimState s] -> OndimState s
OndimState s -> OndimState s -> OndimState s
forall s. Semigroup (OndimState s)
forall s. OndimState s
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall s. [OndimState s] -> OndimState s
forall s. OndimState s -> OndimState s -> OndimState s
$cmempty :: forall s. OndimState s
mempty :: OndimState s
$cmappend :: forall s. OndimState s -> OndimState s -> OndimState s
mappend :: OndimState s -> OndimState s -> OndimState s
$cmconcat :: forall s. [OndimState s] -> OndimState s
mconcat :: [OndimState s] -> OndimState s
Monoid)
data TraceData = TraceData
{ TraceData -> Int
depth :: !Int,
TraceData -> [(Text, DefinitionSite)]
expansionTrace :: ![(Text, DefinitionSite)],
TraceData -> DefinitionSite
currentSite :: !DefinitionSite,
TraceData -> Bool
inhibitErrors :: !Bool
}
deriving (TraceData -> TraceData -> Bool
(TraceData -> TraceData -> Bool)
-> (TraceData -> TraceData -> Bool) -> Eq TraceData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceData -> TraceData -> Bool
== :: TraceData -> TraceData -> Bool
$c/= :: TraceData -> TraceData -> Bool
/= :: TraceData -> TraceData -> Bool
Eq, Int -> TraceData -> ShowS
[TraceData] -> ShowS
TraceData -> String
(Int -> TraceData -> ShowS)
-> (TraceData -> String)
-> ([TraceData] -> ShowS)
-> Show TraceData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceData -> ShowS
showsPrec :: Int -> TraceData -> ShowS
$cshow :: TraceData -> String
show :: TraceData -> String
$cshowList :: [TraceData] -> ShowS
showList :: [TraceData] -> ShowS
Show)
initialTraceData :: TraceData
initialTraceData :: TraceData
initialTraceData = Int
-> [(Text, DefinitionSite)] -> DefinitionSite -> Bool -> TraceData
TraceData Int
0 [] DefinitionSite
NoDefinition Bool
False
data DefinitionSite
= CodeDefinition !SrcLoc
| FileDefinition {DefinitionSite -> String
definitionPath :: !FilePath, DefinitionSite -> Text
definitionExt :: !Text}
| NoDefinition
deriving (DefinitionSite -> DefinitionSite -> Bool
(DefinitionSite -> DefinitionSite -> Bool)
-> (DefinitionSite -> DefinitionSite -> Bool) -> Eq DefinitionSite
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DefinitionSite -> DefinitionSite -> Bool
== :: DefinitionSite -> DefinitionSite -> Bool
$c/= :: DefinitionSite -> DefinitionSite -> Bool
/= :: DefinitionSite -> DefinitionSite -> Bool
Eq, Int -> DefinitionSite -> ShowS
[DefinitionSite] -> ShowS
DefinitionSite -> String
(Int -> DefinitionSite -> ShowS)
-> (DefinitionSite -> String)
-> ([DefinitionSite] -> ShowS)
-> Show DefinitionSite
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DefinitionSite -> ShowS
showsPrec :: Int -> DefinitionSite -> ShowS
$cshow :: DefinitionSite -> String
show :: DefinitionSite -> String
$cshowList :: [DefinitionSite] -> ShowS
showList :: [DefinitionSite] -> ShowS
Show, (forall x. DefinitionSite -> Rep DefinitionSite x)
-> (forall x. Rep DefinitionSite x -> DefinitionSite)
-> Generic DefinitionSite
forall x. Rep DefinitionSite x -> DefinitionSite
forall x. DefinitionSite -> Rep DefinitionSite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DefinitionSite -> Rep DefinitionSite x
from :: forall x. DefinitionSite -> Rep DefinitionSite x
$cto :: forall x. Rep DefinitionSite x -> DefinitionSite
to :: forall x. Rep DefinitionSite x -> DefinitionSite
Generic)
fileSite :: FilePath -> DefinitionSite
fileSite :: String -> DefinitionSite
fileSite String
fp = String -> Text -> DefinitionSite
FileDefinition String
fp Text
exts
where
exts :: Text
exts = Int -> Text -> Text
T.drop Int
1 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
forall a. ToText a => a -> Text
toText (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
takeExtensions String
fp
callStackSite :: DefinitionSite
callStackSite :: DefinitionSite
callStackSite = case CallStack -> [Item CallStack]
forall l. IsList l => l -> [Item l]
GHC.toList CallStack
HasCallStack => CallStack
callStack of
Item CallStack
x : [Item CallStack]
_ -> SrcLoc -> DefinitionSite
CodeDefinition ((String, SrcLoc) -> SrcLoc
forall a b. (a, b) -> b
snd (String, SrcLoc)
Item CallStack
x)
[] -> DefinitionSite
NoDefinition
getCurrentSite :: Ondim s DefinitionSite
getCurrentSite :: forall s. Ondim s DefinitionSite
getCurrentSite = ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
DefinitionSite
-> Ondim s DefinitionSite
forall s a.
ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> Ondim s a
Ondim (ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
DefinitionSite
-> Ondim s DefinitionSite)
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
DefinitionSite
-> Ondim s DefinitionSite
forall a b. (a -> b) -> a -> b
$ ((TraceData, STRef s (OndimState s)) -> DefinitionSite)
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
DefinitionSite
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (TraceData -> DefinitionSite
currentSite (TraceData -> DefinitionSite)
-> ((TraceData, STRef s (OndimState s)) -> TraceData)
-> (TraceData, STRef s (OndimState s))
-> DefinitionSite
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TraceData, STRef s (OndimState s)) -> TraceData
forall a b. (a, b) -> a
fst)
withSite :: DefinitionSite -> Ondim s a -> Ondim s a
withSite :: forall s a. DefinitionSite -> Ondim s a -> Ondim s a
withSite DefinitionSite
site = ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> Ondim s a
forall s a.
ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> Ondim s a
Ondim (ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> Ondim s a)
-> (Ondim s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a)
-> Ondim s a
-> Ondim s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TraceData, STRef s (OndimState s))
-> (TraceData, STRef s (OndimState s)))
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
forall a.
((TraceData, STRef s (OndimState s))
-> (TraceData, STRef s (OndimState s)))
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local ((TraceData -> TraceData)
-> (TraceData, STRef s (OndimState s))
-> (TraceData, STRef s (OndimState s))
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first \TraceData
s -> TraceData
s {currentSite = site}) (ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a)
-> (Ondim s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a)
-> Ondim s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ondim s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
forall s a.
Ondim s a
-> ReaderT
(TraceData, STRef s (OndimState s))
(ExceptT OndimException (ST s))
a
unOndimT
data ExceptionType
= MaxExpansionDepthExceeded
|
TemplateError
!CallStack
!Text
|
Failure
!SomeTypeRep
!Text
!OndimFailure
deriving (Int -> ExceptionType -> ShowS
[ExceptionType] -> ShowS
ExceptionType -> String
(Int -> ExceptionType -> ShowS)
-> (ExceptionType -> String)
-> ([ExceptionType] -> ShowS)
-> Show ExceptionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExceptionType -> ShowS
showsPrec :: Int -> ExceptionType -> ShowS
$cshow :: ExceptionType -> String
show :: ExceptionType -> String
$cshowList :: [ExceptionType] -> ShowS
showList :: [ExceptionType] -> ShowS
Show, Show ExceptionType
Typeable ExceptionType
(Typeable ExceptionType, Show ExceptionType) =>
(ExceptionType -> SomeException)
-> (SomeException -> Maybe ExceptionType)
-> (ExceptionType -> String)
-> (ExceptionType -> Bool)
-> Exception ExceptionType
SomeException -> Maybe ExceptionType
ExceptionType -> Bool
ExceptionType -> String
ExceptionType -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> (e -> Bool)
-> Exception e
$ctoException :: ExceptionType -> SomeException
toException :: ExceptionType -> SomeException
$cfromException :: SomeException -> Maybe ExceptionType
fromException :: SomeException -> Maybe ExceptionType
$cdisplayException :: ExceptionType -> String
displayException :: ExceptionType -> String
$cbacktraceDesired :: ExceptionType -> Bool
backtraceDesired :: ExceptionType -> Bool
Exception)
data OndimFailure
=
NotBound
|
ExpansionWrongType
!SomeTypeRep
|
TemplateWrongType
!SomeTypeRep
|
FailureOther !Text
deriving (Int -> OndimFailure -> ShowS
[OndimFailure] -> ShowS
OndimFailure -> String
(Int -> OndimFailure -> ShowS)
-> (OndimFailure -> String)
-> ([OndimFailure] -> ShowS)
-> Show OndimFailure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OndimFailure -> ShowS
showsPrec :: Int -> OndimFailure -> ShowS
$cshow :: OndimFailure -> String
show :: OndimFailure -> String
$cshowList :: [OndimFailure] -> ShowS
showList :: [OndimFailure] -> ShowS
Show, Show OndimFailure
Typeable OndimFailure
(Typeable OndimFailure, Show OndimFailure) =>
(OndimFailure -> SomeException)
-> (SomeException -> Maybe OndimFailure)
-> (OndimFailure -> String)
-> (OndimFailure -> Bool)
-> Exception OndimFailure
SomeException -> Maybe OndimFailure
OndimFailure -> Bool
OndimFailure -> String
OndimFailure -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> (e -> Bool)
-> Exception e
$ctoException :: OndimFailure -> SomeException
toException :: OndimFailure -> SomeException
$cfromException :: SomeException -> Maybe OndimFailure
fromException :: SomeException -> Maybe OndimFailure
$cdisplayException :: OndimFailure -> String
displayException :: OndimFailure -> String
$cbacktraceDesired :: OndimFailure -> Bool
backtraceDesired :: OndimFailure -> Bool
Exception)
data OndimException = OndimException !ExceptionType !TraceData
deriving (Int -> OndimException -> ShowS
[OndimException] -> ShowS
OndimException -> String
(Int -> OndimException -> ShowS)
-> (OndimException -> String)
-> ([OndimException] -> ShowS)
-> Show OndimException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OndimException -> ShowS
showsPrec :: Int -> OndimException -> ShowS
$cshow :: OndimException -> String
show :: OndimException -> String
$cshowList :: [OndimException] -> ShowS
showList :: [OndimException] -> ShowS
Show, Show OndimException
Typeable OndimException
(Typeable OndimException, Show OndimException) =>
(OndimException -> SomeException)
-> (SomeException -> Maybe OndimException)
-> (OndimException -> String)
-> (OndimException -> Bool)
-> Exception OndimException
SomeException -> Maybe OndimException
OndimException -> Bool
OndimException -> String
OndimException -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> (e -> Bool)
-> Exception e
$ctoException :: OndimException -> SomeException
toException :: OndimException -> SomeException
$cfromException :: SomeException -> Maybe OndimException
fromException :: SomeException -> Maybe OndimException
$cdisplayException :: OndimException -> String
displayException :: OndimException -> String
$cbacktraceDesired :: OndimException -> Bool
backtraceDesired :: OndimException -> Bool
Exception)