Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- module Prelude.Spiros.Print
- module Prelude.Spiros.Parse
- data Replace a = Replace {}
- checkReplace :: (IsString t, Eq t) => Replace t -> Maybe (Replace t)
- replace_StrictText :: Replace Text -> Text -> Text
- replace :: Replace Text -> Text -> Text
- replace_LazyText :: Replace Text -> Text -> Text
- sappendGeneric :: (Generic a, GSemigroup' (Rep a)) => a -> a -> a
- memptyGeneric :: (Generic a, GMonoid' (Rep a)) => a
- mappendGeneric :: (Generic a, GMonoid' (Rep a)) => a -> a -> a
- data GUI = GUI {
- _guiPackage :: !PkgName
- _guiModule :: !ModName
- _guiIdentifier :: !OccName
- _guiNamespace :: !NameSpace
- unsafeGUI :: Name -> GUI
- fromGlobalName :: Name -> Maybe GUI
- fromValueName :: Name -> Maybe GUI
- fromTypeProxy :: forall a proxy. Typeable a => proxy a -> GUI
- displayGUI :: GUI -> String
- type Validator a b = forall m. MonadThrow m => a -> m b
- type Possibly b = forall m. MonadThrow m => m b
- validator :: (MonadThrow m, Show a) => HaskellName -> (a -> Bool) -> (String -> String) -> (a -> b) -> a -> m b
- validator_ :: MonadThrow m => HaskellName -> (a -> Bool) -> (a -> b) -> a -> m b
- validateNatural :: forall i m. (Integral i, Show i) => MonadThrow m => i -> m Natural
- someMonadThrowException :: Show a => a -> SomeException
- maybeMonadThrow :: MonadThrow m => Maybe a -> m a
- maybeMonadThrowWith :: MonadThrow m => SomeException -> Maybe a -> m a
- listMonadThrow :: MonadThrow m => [a] -> m a
- listMonadThrowWith :: MonadThrow m => SomeException -> [a] -> m a
- eitherMonadThrow :: MonadThrow m => Either SomeException a -> m a
- newtype CallStack' = CallStack' {}
- data CallFrame = CallFrame {}
- data Source = Source {
- _sourcePackage :: !Text
- _sourceModule :: !Text
- _sourceFilename :: !Text
- _sourceFileSpan :: !FileSpan
- data FileSpan = FileSpan {}
- data FilePosition = FilePosition {
- _fileLine :: !Int
- _fileColumn :: !Int
- throwEither :: (MonadThrow m, Exception e) => Either e a -> m a
- throwEitherWith :: (MonadThrow m, Show e) => Either e a -> m a
- throwMaybe :: MonadThrow m => Maybe a -> m a
- throwMaybeWith :: (MonadThrow m, Exception e) => e -> Maybe a -> m a
- throwList :: MonadThrow m => List a -> m a
- throwListWith :: (MonadThrow m, Exception e) => e -> List a -> m a
- data SimpleException = SimpleException {}
- displaySimpleException :: SimpleException -> String
- data QuotedException = QuotedException {}
- displayQuotedException :: QuotedException -> String
- formatCustomExceptionWithCaller :: String -> String
- formatCustomExceptionWithMessage :: String -> String -> String
- formatCustomExceptionWithCallStack :: String -> String -> String -> String
- displayQualifiedVariable :: Name -> String
- throwE :: (MonadThrow m, Exception e) => e -> m a
- throwS :: MonadThrow m => String -> m a
- throwN :: MonadThrow m => Name -> String -> m a
- throwN_ :: MonadThrow m => Name -> m a
- guardE :: (MonadThrow m, Exception e) => e -> Bool -> m ()
- guardM :: MonadThrow m => Bool -> m ()
- guardS :: MonadThrow m => String -> Bool -> m ()
- guardN :: MonadThrow m => Name -> Bool -> m ()
- guardF :: MonadFail m => String -> Bool -> m ()
- guardP :: MonadPlus m => Bool -> m ()
- uninformative :: SomeException
- someSimpleException_ :: SomeException
- someQuotedException_ :: SomeException
- someSimpleException :: String -> SomeException
- someQuotedException :: Name -> String -> SomeException
- throwL :: (MonadThrow m, HasCallStack) => String -> m a
- guardL :: (MonadThrow m, HasCallStack) => Bool -> m ()
- someLocatedException_ :: HasCallStack => SomeException
- someLocatedException :: HasCallStack => String -> SomeException
- data LocatedException = LocatedException {}
- toLocatedException :: HasCallStack => String -> LocatedException
- displayLocatedException :: LocatedException -> String
- module Prelude.Spiros.System
- module Prelude.Spiros.Utilities
- module Prelude.Spiros.Reexports
- module Prelude.Spiros.Types
Re-exports
These are re-exported by Prelude.Spiros
.
Prelude.Spiros.Reexports re-exports: the core types/values from several packages; minus all partial functions, except for some functions whose names are prefixed with "unsafe"
, i.e. "explicitly partial functions", e.g. unsafeNatural
(however, no unsafeHead
is exported, as its need often implies that the []
being used is the wrong type).
Prelude.Spiros.Utilities defines a few dozen simple utilities, like an extended prelude.
Prelude.Spiros.System provides system information: about the current operating system, architecture, and compiler.
Prelude.Spiros.Exception defines a few new exception types, which may (or may not) tag the message with a TemplateHaskell
Name
or with a CallStack
, as auxiliary/contextual information.
Prelude.Spiros.Validator re-exports helpers for defining simple validators (e.g. a -> Maybe b
).
Prelude.Spiros.GUI provides helpers for working with TemplateHaskell
Name
s.
Prelude.Spiros.TemplateHaskell provides a few helpers for using doctest
and working with TemplateHaskell
.
module Prelude.Spiros.Print
module Prelude.Spiros.Parse
Instances
checkReplace :: (IsString t, Eq t) => Replace t -> Maybe (Replace t) Source #
Ensure that old
is nonempty.
replace_StrictText :: Replace Text -> Text -> Text Source #
(Original Documention...)
O(m+n) Replace every non-overlapping occurrence of needle
(a.k.a.
)
in old
haystack
with replacement
(a.k.a.
).new
This function behaves as though it was defined as follows:
replace_StrictText Replace{old,new} haystack =intercalate
new (splitOn
needle haystack)
As this suggests, each occurrence is replaced exactly once. So if
needle
occurs in replacement
, that occurrence will not itself
be replaced recursively:
>>>
replace_StrictText Replace{ old = "oo", new = "foo" } "oo"
"foo"
In cases where several instances of needle
overlap, only the
first one will be replaced:
>>>
replace_StrictText Replace{ old = "ofo", new = "bar" } "ofofo"
"barfo"
(Additional Documention...)
this function has two differences from the function it wraps:
- the "enriched" argument record
Replace
, done for clarity of argument order. - the behavior when
(i.e.new
needle
), is empty (i.e.""
), which simply outputs the input unchanged, rather than erroring.
i.e.
>>>
replace_StrictText Replace{ old = "", new = "anything" } "unchanged"
"unchanged"
You can use (the trivial) checkReplace
.
replace :: Replace Text -> Text -> Text Source #
Alias for replace_StrictText
.
(See replace_StrictText
for documentation).
replace_LazyText :: Replace Text -> Text -> Text Source #
Lazy analogue to replace_StrictText
.
(See replace_StrictText
for documentation).
sappendGeneric :: (Generic a, GSemigroup' (Rep a)) => a -> a -> a infixr 6 Source #
A globally unique haskell identifier, for either a value or type, fully-qualified with its module and package.
TODO new field: Version
.
GUI | |
|
Instances
Eq GUI Source # | |
Data GUI Source # | |
Defined in Prelude.Spiros.GUI gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GUI -> c GUI # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GUI # dataTypeOf :: GUI -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GUI) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GUI) # gmapT :: (forall b. Data b => b -> b) -> GUI -> GUI # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GUI -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GUI -> r # gmapQ :: (forall d. Data d => d -> u) -> GUI -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GUI -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GUI -> m GUI # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GUI -> m GUI # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GUI -> m GUI # | |
Ord GUI Source # | |
Show GUI Source # | |
Generic GUI Source # | |
NFData GUI Source # | |
Defined in Prelude.Spiros.GUI | |
Hashable GUI Source # | |
Defined in Prelude.Spiros.GUI | |
type Rep GUI Source # | |
Defined in Prelude.Spiros.GUI type Rep GUI = D1 (MetaData "GUI" "Prelude.Spiros.GUI" "spiros-0.4.0-7yNYhuNqI1YgajQL6GSlo" False) (C1 (MetaCons "GUI" PrefixI True) ((S1 (MetaSel (Just "_guiPackage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PkgName) :*: S1 (MetaSel (Just "_guiModule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ModName)) :*: (S1 (MetaSel (Just "_guiIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OccName) :*: S1 (MetaSel (Just "_guiNamespace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NameSpace)))) |
unsafeGUI :: Name -> GUI Source #
Return a globally unique identifier from a Template Haskell Name
, even if it's local (i.e. not global).
Implementation: TemplateHaskellQuotes
return only "local names" (NameL
) and "global names" (NameG
, which fromGlobalName
validates).
See Name
:
NameS
: An unqualified name; dynamically boundNameQ
ModName: A qualified name; dynamically boundNameU
!Int: A unique local nameNameL
!Int: Local name bound outside of the TH ASTNameG
NameSpace PkgName ModName: Global name bound outside of the TH AST: An original name (occurrences only, not binders) Need the namespace too to be sure which thing we are naming
fromGlobalName :: Name -> Maybe GUI Source #
if the given identifier is [1] global and [2] a value, then return it as a GUI.
e.g.
> fromGlobalName 'fromGlobalName Just (PkgName "spiros-0.0.1-inplace",ModName Prelude.Spiros.Exception,OccName "fromGlobalName")
Implementation Note: Name
use is compatible with template-haskell >=2.11
.
fromValueName :: Name -> Maybe GUI Source #
like fromGlobalName
, but restricted to identifiers
(i.e. not types/classes, not constructors/patterns).
e.g.
fromTypeProxy :: forall a proxy. Typeable a => proxy a -> GUI Source #
displayGUI :: GUI -> String Source #
>>>
displayGUI (GUI (PkgName "package-name") (ModName "Module.SubModule") (OccName "identifierName") VarName)
"package-name:Module.SubModule.identifierName">>>
displayGUI (GUI (PkgName "package-name") (ModName "Module.SubModule") (OccName "ConstructorName") DataName)
"package-name:Module.SubModule.ConstructorName">>>
displayGUI (GUI (PkgName "package-name") (ModName "Module.SubModule") (OccName "TypeName") TcClsName)
"package-name:Module.SubModule.(type TypeName)"
type Validator a b = forall m. MonadThrow m => a -> m b Source #
Represents a validator as something that injects a type into another type, with the possibility of failure.
Equivalent to:
Validator a b ≡ (a ->Possibly
b) Validator a b ≡ (∀m. (MonadThrow
m) => Kleisli m a b)
Specializations:
Validator a b ~ (a -> Maybe b) Validator a b ~ (a -> [] b) Validator a b ~ (a -> Either SomeException b) Validator a b ~ (a -> IO b) ...
Usage:
-- x :: a return x :: Validator a a
type Possibly b = forall m. MonadThrow m => m b Source #
Represents a value that has possibly failed ("or" will possibly fail).
Specializations:
Possibly b ~ Maybe b Possibly b ~ [b] Possibly b ~ Either _ b Possibly b ~ IO b ...
validator :: (MonadThrow m, Show a) => HaskellName -> (a -> Bool) -> (String -> String) -> (a -> b) -> a -> m b Source #
Parameters:
name = validator name check display cast :: Validator
_ _
e.g. validating naturals:
validateNatural :: Validator
Integer Natural
validateNatural = validator 'natural
(\i -> i >= 0)
(\i -> i ++ " must be non-negative")
(\i -> fromIntegral i)
is the same as the explicit:
validateNatural :: (MonadThrow
m) => Integer -> m Natural validateNatural i | i >= 0 = return $ fromIntegral i | otherwise =throwN
'validateNatural $ "must be non-negative"
and as the point-free styled:
validateNatural :: Integer -> Possibly
Natural
validateNatural = validator 'natural
(>= 0)
(++ " must be non-negative")
(fromIntegral)
Wraps throwN
.
validator_ :: MonadThrow m => HaskellName -> (a -> Bool) -> (a -> b) -> a -> m b Source #
validateNatural :: forall i m. (Integral i, Show i) => MonadThrow m => i -> m Natural Source #
>>>
validateNatural 2
2>>>
validateNatural (-2) :: Maybe Natural
Nothing
> validateNatural (-2) *** Exception: ... -2 must be non-negative ...
Specializations of i
:
validateNaturalInt ::
Integer ::Validator
Int Natural validateNaturalValidator
Integer Natural validateNatural @Natural ::Validator
Natural Natural ...
Specializations of m
:
validateNaturalInt
Maybe :: Integer -> Maybe Natural validateNaturalInt
(Either _) :: Integer -> Either SomeException Natural validateNaturalInt
[] :: Integer -> [Natural] validateNaturalInt
IO :: Integer -> IO Natural
Definition:
validateNatural :: forall i m. ...
validateNatural = validator
'validateNatural
(>= 0)
(++ " must be non-negative")
(fromIntegral)
someMonadThrowException :: Show a => a -> SomeException Source #
A default Exception
, useful when manipulating MonadThrow
instances.
An ErrorCall
(whose message is uninformative).
maybeMonadThrow :: MonadThrow m => Maybe a -> m a Source #
Generalize Maybe
(a concrete, pure MonadThrow
instance),
to an abstract MonadThrow
m
.
≡maybe
(throwM
_)return
maybeMonadThrowWith :: MonadThrow m => SomeException -> Maybe a -> m a Source #
Generalize Maybe
(a concrete, pure MonadThrow
instance),
to an abstract MonadThrow
m
.
maybeMonadThrowWith
≡maybe
(throwM
e)return
listMonadThrow :: MonadThrow m => [a] -> m a Source #
Generalize '[]' (a concrete, pure MonadThrow
instance),
to an abstract MonadThrow
m
.
listMonadThrow
≡ \case [] ->throwM
_ (x:_) ->return
x
Only return the first success (i.e. the head of the "list of successes").
listMonadThrowWith :: MonadThrow m => SomeException -> [a] -> m a Source #
Generalize '[]' (a concrete, pure MonadThrow
instance),
to an abstract MonadThrow
m
.
eitherMonadThrow :: MonadThrow m => Either SomeException a -> m a Source #
Generalize
(a concrete, pure Either
SomeException
MonadThrow
instance),
to an abstract MonadThrow
m
.
≡either
throwM
return
newtype CallStack' Source #
Instances
Instances
Eq CallFrame Source # | |
Ord CallFrame Source # | |
Defined in Prelude.Spiros.Exception | |
Show CallFrame Source # | |
Generic CallFrame Source # | |
NFData CallFrame Source # | |
Defined in Prelude.Spiros.Exception | |
Hashable CallFrame Source # | |
Defined in Prelude.Spiros.Exception | |
type Rep CallFrame Source # | |
Defined in Prelude.Spiros.Exception type Rep CallFrame = D1 (MetaData "CallFrame" "Prelude.Spiros.Exception" "spiros-0.4.0-7yNYhuNqI1YgajQL6GSlo" False) (C1 (MetaCons "CallFrame" PrefixI True) (S1 (MetaSel (Just "_CallFrame_caller") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GUI) :*: S1 (MetaSel (Just "_CallFrame_callSite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Source))) |
A single location in the source code.
Equivalent to SrcLoc
:
srcLocPackage :: String srcLocModule :: String srcLocFile :: String srcLocStartLine :: Int srcLocStartCol :: Int srcLocEndLine :: Int srcLocEndCol :: Int
but with more instances.
Source | |
|
Instances
Eq Source Source # | |
Ord Source Source # | |
Read Source Source # | |
Show Source Source # | |
Generic Source Source # | |
NFData Source Source # | |
Defined in Prelude.Spiros.Exception | |
Hashable Source Source # | |
Defined in Prelude.Spiros.Exception | |
type Rep Source Source # | |
Defined in Prelude.Spiros.Exception type Rep Source = D1 (MetaData "Source" "Prelude.Spiros.Exception" "spiros-0.4.0-7yNYhuNqI1YgajQL6GSlo" False) (C1 (MetaCons "Source" PrefixI True) ((S1 (MetaSel (Just "_sourcePackage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_sourceModule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "_sourceFilename") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_sourceFileSpan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FileSpan)))) |
The location of something spanning a contiguous region in a file.
The [start .. end]
range is inclusive.
e.g. a highlighted region.
Instances
Eq FileSpan Source # | |
Ord FileSpan Source # | |
Defined in Prelude.Spiros.Exception | |
Read FileSpan Source # | |
Show FileSpan Source # | |
Generic FileSpan Source # | |
NFData FileSpan Source # | |
Defined in Prelude.Spiros.Exception | |
Hashable FileSpan Source # | |
Defined in Prelude.Spiros.Exception | |
type Rep FileSpan Source # | |
Defined in Prelude.Spiros.Exception type Rep FileSpan = D1 (MetaData "FileSpan" "Prelude.Spiros.Exception" "spiros-0.4.0-7yNYhuNqI1YgajQL6GSlo" False) (C1 (MetaCons "FileSpan" PrefixI True) (S1 (MetaSel (Just "_spanStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePosition) :*: S1 (MetaSel (Just "_spanEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePosition))) |
data FilePosition Source #
The location of a single cell (e.g. a character) in a file.
We conceive text files as grids, so this is equivalent to a 2 dimensional point, with different naming. The line number $sel:_fileLine:FilePosition
is like the y-coordinate (descending vertically); the column number $sel:_fileColumn:FilePosition
being the x-coordinate.
TODO One-indexed ("the first line") versus Zero-indexed?
FilePosition | |
|
Instances
throwEither :: (MonadThrow m, Exception e) => Either e a -> m a Source #
throwEitherWith :: (MonadThrow m, Show e) => Either e a -> m a Source #
throwMaybe :: MonadThrow m => Maybe a -> m a Source #
throwMaybeWith :: (MonadThrow m, Exception e) => e -> Maybe a -> m a Source #
throwList :: MonadThrow m => List a -> m a Source #
throwListWith :: (MonadThrow m, Exception e) => e -> List a -> m a Source #
data SimpleException Source #
Instances
displaySimpleException :: SimpleException -> String Source #
formatCustomExceptionWithCaller
if the message is empty,
formatCustomExceptionWithMessage
otherwise.
data QuotedException Source #
Instances
displayQualifiedVariable :: Name -> String Source #
>>>
:set -XTemplateHaskellQuotes
>>>
displayQualifiedVariable 'length
"base:Data.Foldable.length">>>
import qualified Prelude
>>>
displayQualifiedVariable 'Prelude.length
"base:Data.Foldable.length"
let x = undefined in displayQualifiedVariable 'x == "?"
throwE :: (MonadThrow m, Exception e) => e -> m a Source #
E
for Exception
,
throwS :: MonadThrow m => String -> m a Source #
throwN :: MonadThrow m => Name -> String -> m a Source #
N
for Name
,
throwM
s a QuotedException
with the given caller and message.
e.g.
> throwN
'throwN "this is an example"
*** Exception:
[spiros-0.0.1-inplace:Prelude.Spiros.Exception.throwN] was called with:
this is an example
Useful for easily defining smart constructors, whose error message has a fully-qualified name for debugging.
If you rename the module, the error message changes automatically;
and if you rename the identifier, you will get a compile time error from Template Haskell if you don't simultaneously update the useage of throwN
(unless another name is captured).
e.g. validating naturals:
natural :: Integer -> Possibly
Natural
natural i
| i >= 0 = return $ fromIntegral i
| otherwise = throwN 'natural $ "must be non-negative"
throwN_ :: MonadThrow m => Name -> m a Source #
guardE :: (MonadThrow m, Exception e) => e -> Bool -> m () Source #
E
for Exception
, calls throwM
.
NOTE if [1] you don't like the naming convention of the convenience functions below, or [2] if you need custom exceptions that aren't just a message with some location information, then directly use some exception (like when using the exceptions
pacakge).
e.g.:
>>>
import Control.Exception (ArithException(..))
>>>
divideM x y = guardE DivideByZero (y /= (0::Double)) >> return (x / y)
>>>
:t divideM
divideM :: MonadThrow m => Double -> Double -> m Double>>>
divideM 1 4
0.25>>>
divideM 1 0
*** Exception: divide by zero>>>
divideM 1 4 :: Maybe Double
Just 0.25>>>
divideM 1 0 :: Maybe Double
Nothing
guardM :: MonadThrow m => Bool -> m () Source #
someSimpleException_ :: SomeException Source #
the def
ault SimpleException
.
someQuotedException_ :: SomeException Source #
the def
ault QuotedException
.
someQuotedException :: Name -> String -> SomeException Source #
throwL :: (MonadThrow m, HasCallStack) => String -> m a Source #
L
for Location
or CallStack
(caLLstack
, lol).
throwM
s a LocatedException
with the given call-stack and message.
e.g.
> caller = throwL
"this is an example"
> caller
*** Exception:
[safe-exceptions-0.1.6.0-HpnSY2upHz4DtQ1B03RoNw:Control.Exception.Safe.throwM] was called with:
this is an example
... and called from:
CallStack (from HasCallStack):
toLocatedException, called at sourcesPreludeSpiros/Exception.hs:385:20 in spiros-0.0.1-inplace:Prelude.Spiros.Exception
throwL, called at interactive:28:1 in interactive:Ghci1
guardL :: (MonadThrow m, HasCallStack) => Bool -> m () Source #
L
for Location
or CallStack
(caLLstack
).
someLocatedException_ :: HasCallStack => SomeException Source #
the def
ault LocatedException
.
data LocatedException Source #
Instances
module Prelude.Spiros.System
module Prelude.Spiros.Utilities
module Prelude.Spiros.Reexports
module Prelude.Spiros.Types
Usage
assertions:
assert
:: Bool -> a -> a
If the first argument evaluates to True, then the result is the second argument. Otherwise an AssertionFailed exception is raised, containing a String with the source file and line number of the call to assert.
Assertions can normally be turned on or off with a compiler flag (for GHC, assertions are normally on unless optimisation is turned on with -O or the -fignore-asserts option is given). When assertions are turned off, the first argument to assert is ignored, and the second argument is returned as the result.
Non-exports
These must be explicitly imported, they aren't re-exported by Prelude.Spiros
.
Prelude.Spiros.Classes re-exports only typeclases/methods (and a few helpers), from several packages (like Prelude.Spiros.Reexports
), for deriving or defining instances (e.g. in a .Types
module). Unlike Prelude.Spiros.Reexports
, partial functions that are methods (like toEnum
and fromEnum
) are necessarily exported, since they must be visible when manually writing instances.
Notes
Most examples (all those prefixed with a triple @>>>@
) are doctest
ed. Those with single @>@
may have brittle output, and codeblocks might describe relations by "returning" variables, and thus aren't.