spiros-0.4.0: Spiros Boosalis's Custom Prelude

Safe HaskellNone
LanguageHaskell2010

Prelude.Spiros

Contents

Synopsis

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 Names.

Prelude.Spiros.TemplateHaskell provides a few helpers for using doctest and working with TemplateHaskell.

data Replace a Source #

Intended Specializations:

Constructors

Replace 

Fields

Instances
Functor Replace Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

fmap :: (a -> b) -> Replace a -> Replace b #

(<$) :: a -> Replace b -> Replace a #

Foldable Replace Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

fold :: Monoid m => Replace m -> m #

foldMap :: Monoid m => (a -> m) -> Replace a -> m #

foldr :: (a -> b -> b) -> b -> Replace a -> b #

foldr' :: (a -> b -> b) -> b -> Replace a -> b #

foldl :: (b -> a -> b) -> b -> Replace a -> b #

foldl' :: (b -> a -> b) -> b -> Replace a -> b #

foldr1 :: (a -> a -> a) -> Replace a -> a #

foldl1 :: (a -> a -> a) -> Replace a -> a #

toList :: Replace a -> [a] #

null :: Replace a -> Bool #

length :: Replace a -> Int #

elem :: Eq a => a -> Replace a -> Bool #

maximum :: Ord a => Replace a -> a #

minimum :: Ord a => Replace a -> a #

sum :: Num a => Replace a -> a #

product :: Num a => Replace a -> a #

Traversable Replace Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

traverse :: Applicative f => (a -> f b) -> Replace a -> f (Replace b) #

sequenceA :: Applicative f => Replace (f a) -> f (Replace a) #

mapM :: Monad m => (a -> m b) -> Replace a -> m (Replace b) #

sequence :: Monad m => Replace (m a) -> m (Replace a) #

Eq a => Eq (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

(==) :: Replace a -> Replace a -> Bool #

(/=) :: Replace a -> Replace a -> Bool #

Ord a => Ord (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

compare :: Replace a -> Replace a -> Ordering #

(<) :: Replace a -> Replace a -> Bool #

(<=) :: Replace a -> Replace a -> Bool #

(>) :: Replace a -> Replace a -> Bool #

(>=) :: Replace a -> Replace a -> Bool #

max :: Replace a -> Replace a -> Replace a #

min :: Replace a -> Replace a -> Replace a #

Read a => Read (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Show a => Show (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

showsPrec :: Int -> Replace a -> ShowS #

show :: Replace a -> String #

showList :: [Replace a] -> ShowS #

Generic (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Associated Types

type Rep (Replace a) :: Type -> Type #

Methods

from :: Replace a -> Rep (Replace a) x #

to :: Rep (Replace a) x -> Replace a #

Lift a => Lift (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

lift :: Replace a -> Q Exp #

NFData a => NFData (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

rnf :: Replace a -> () #

Hashable a => Hashable (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

Methods

hashWithSalt :: Int -> Replace a -> Int #

hash :: Replace a -> Int #

type Rep (Replace a) Source # 
Instance details

Defined in Prelude.Spiros.Enriched

type Rep (Replace a) = D1 (MetaData "Replace" "Prelude.Spiros.Enriched" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" False) (C1 (MetaCons "Replace" PrefixI True) (S1 (MetaSel (Just "old") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "new") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)))

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. old) in 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 new (i.e. 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 #

mappendGeneric :: (Generic a, GMonoid' (Rep a)) => a -> a -> a infixr 6 Source #

data GUI Source #

A globally unique haskell identifier, for either a value or type, fully-qualified with its module and package.

TODO new field: Version.

Instances
Eq GUI Source # 
Instance details

Defined in Prelude.Spiros.GUI

Methods

(==) :: GUI -> GUI -> Bool #

(/=) :: GUI -> GUI -> Bool #

Data GUI Source # 
Instance details

Defined in Prelude.Spiros.GUI

Methods

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 #

toConstr :: GUI -> Constr #

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 # 
Instance details

Defined in Prelude.Spiros.GUI

Methods

compare :: GUI -> GUI -> Ordering #

(<) :: GUI -> GUI -> Bool #

(<=) :: GUI -> GUI -> Bool #

(>) :: GUI -> GUI -> Bool #

(>=) :: GUI -> GUI -> Bool #

max :: GUI -> GUI -> GUI #

min :: GUI -> GUI -> GUI #

Show GUI Source # 
Instance details

Defined in Prelude.Spiros.GUI

Methods

showsPrec :: Int -> GUI -> ShowS #

show :: GUI -> String #

showList :: [GUI] -> ShowS #

Generic GUI Source # 
Instance details

Defined in Prelude.Spiros.GUI

Associated Types

type Rep GUI :: Type -> Type #

Methods

from :: GUI -> Rep GUI x #

to :: Rep GUI x -> GUI #

NFData GUI Source # 
Instance details

Defined in Prelude.Spiros.GUI

Methods

rnf :: GUI -> () #

Hashable GUI Source # 
Instance details

Defined in Prelude.Spiros.GUI

Methods

hashWithSalt :: Int -> GUI -> Int #

hash :: GUI -> Int #

type Rep GUI Source # 
Instance details

Defined in Prelude.Spiros.GUI

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 bound
  • NameQ ModName: A qualified name; dynamically bound
  • NameU !Int: A unique local name
  • NameL !Int: Local name bound outside of the TH AST
  • NameG 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 #

The globally unique identifier for a type: (pkg, modid, tycon)

>>> :set -XPolyKinds
>>> import Data.Proxy
>>> displayGUI $ fromTypeProxy (Proxy :: Proxy [])
"ghc-prim:GHC.Types.(type [])"

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 #

More convenient, but less informative, than validator.

Parameters:

name = validator_ 'name check cast :: Validator _ _

e.g. validating naturals:

validateNatural :: Integer -> Possibly Natural
validateNatural = validator 'validateNatural (>= 0) fromIntegral

Wraps throwN_.

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:

validateNatural Int     :: Validator Int     Natural
validateNatural Integer :: Validator Integer Natural
validateNatural @Natural :: Validator Natural Natural
...

Specializations of m:

validateNatural Int Maybe      :: Integer ->                Maybe Natural
validateNatural Int (Either _) :: Integer -> Either SomeException Natural
validateNatural Int []         :: Integer ->                     [Natural]
validateNatural Int 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.

maybeMonadThrowWithmaybe (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 Either SomeException (a concrete, pure MonadThrow instance), to an abstract MonadThrow m.

either throwM return

newtype CallStack' Source #

Constructors

CallStack' 
Instances
Eq CallStack' Source # 
Instance details

Defined in Prelude.Spiros.Exception

Ord CallStack' Source # 
Instance details

Defined in Prelude.Spiros.Exception

Show CallStack' Source # 
Instance details

Defined in Prelude.Spiros.Exception

Generic CallStack' Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep CallStack' :: Type -> Type #

NFData CallStack' Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

rnf :: CallStack' -> () #

Hashable CallStack' Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep CallStack' Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep CallStack' = D1 (MetaData "CallStack'" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" True) (C1 (MetaCons "CallStack'" PrefixI True) (S1 (MetaSel (Just "toCallFrames") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq CallFrame))))

data CallFrame Source #

Instances
Eq CallFrame Source # 
Instance details

Defined in Prelude.Spiros.Exception

Ord CallFrame Source # 
Instance details

Defined in Prelude.Spiros.Exception

Show CallFrame Source # 
Instance details

Defined in Prelude.Spiros.Exception

Generic CallFrame Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep CallFrame :: Type -> Type #

NFData CallFrame Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

rnf :: CallFrame -> () #

Hashable CallFrame Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep CallFrame Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep CallFrame = D1 (MetaData "CallFrame" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" 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)))

data Source 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.

Instances
Eq Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

(==) :: Source -> Source -> Bool #

(/=) :: Source -> Source -> Bool #

Ord Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

Read Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

Show Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

Generic Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

NFData Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

rnf :: Source -> () #

Hashable Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

hashWithSalt :: Int -> Source -> Int #

hash :: Source -> Int #

type Rep Source Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep Source = D1 (MetaData "Source" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" 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))))

data FileSpan Source #

The location of something spanning a contiguous region in a file.

The [start .. end] range is inclusive.

e.g. a highlighted region.

Constructors

FileSpan 
Instances
Eq FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

Ord FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

Read FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

Show FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

Generic FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep FileSpan :: Type -> Type #

Methods

from :: FileSpan -> Rep FileSpan x #

to :: Rep FileSpan x -> FileSpan #

NFData FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

rnf :: FileSpan -> () #

Hashable FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

hashWithSalt :: Int -> FileSpan -> Int #

hash :: FileSpan -> Int #

type Rep FileSpan Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep FileSpan = D1 (MetaData "FileSpan" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" 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?

Constructors

FilePosition 

Fields

Instances
Eq FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

Ord FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

Read FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

Show FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

Generic FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep FilePosition :: Type -> Type #

NFData FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

rnf :: FilePosition -> () #

Hashable FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep FilePosition Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep FilePosition = D1 (MetaData "FilePosition" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" False) (C1 (MetaCons "FilePosition" PrefixI True) (S1 (MetaSel (Just "_fileLine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_fileColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

throwEither :: (MonadThrow m, Exception e) => Either e a -> m a Source #

throwEither = either
 throwE
 return

throwEitherWith :: (MonadThrow m, Show e) => Either e 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
Eq SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Ord SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Read SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Show SimpleException Source #

custom for Exception (non-Readable).

= displaySimpleException
Instance details

Defined in Prelude.Spiros.Exception

IsString SimpleException Source #

SimpleException

Instance details

Defined in Prelude.Spiros.Exception

Generic SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep SimpleException :: Type -> Type #

Exception SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Default SimpleException Source #
SimpleException ""
Instance details

Defined in Prelude.Spiros.Exception

NFData SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

rnf :: SimpleException -> () #

Hashable SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep SimpleException Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep SimpleException = D1 (MetaData "SimpleException" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" False) (C1 (MetaCons "SimpleException" PrefixI True) (S1 (MetaSel (Just "_SimpleException_message") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))

data QuotedException Source #

Instances
Eq QuotedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Ord QuotedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Show QuotedException Source #

custom for Exception (non-Readable).

= displayQuotedException
Instance details

Defined in Prelude.Spiros.Exception

IsString QuotedException Source #

= QuotedException 'throwM.

NOTE the prefixing apostrophe is a TemplateHaskellQuotes name quote (not a typo)

Instance details

Defined in Prelude.Spiros.Exception

Generic QuotedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep QuotedException :: Type -> Type #

Exception QuotedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Default QuotedException Source #

"" :: QuotedException (see the IsString instance).

Instance details

Defined in Prelude.Spiros.Exception

NFData QuotedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Methods

rnf :: QuotedException -> () #

Hashable QuotedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep QuotedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep QuotedException = D1 (MetaData "QuotedException" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" False) (C1 (MetaCons "QuotedException" PrefixI True) (S1 (MetaSel (Just "_QuotedException_caller") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GUI) :*: S1 (MetaSel (Just "_QuotedException_message") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))

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,

throwMs a SimpleException.

throwS :: MonadThrow m => String -> m a Source #

S for String,

throwMs a SimpleException.

e.g.

> throwS "this is an example"
*** Exception: 

[spiros-0.0.1-inplace:Prelude.Spiros.Exception.throwS] was called with:

this is an example

e.g.

> throwS ""
*** Exception: 

[spiros-0.0.1-inplace:Prelude.Spiros.Exception.throwS] was called.

throwN :: MonadThrow m => Name -> String -> m a Source #

N for Name,

throwMs 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 #

throwN_ name = throwN name ""

e.g. validating naturals:

natural :: Integer -> Possibly Natural
natural i
 | i >= 0    = return $ fromIntegral i
 | otherwise = throwN_ 'natural

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 #

M for MonadThrow, like throwM.

MonadThrow analogue of base's guard.

= guardE uninformative

guardS :: MonadThrow m => String -> Bool -> m () Source #

S for String, calls throwM.

guardN :: MonadThrow m => Name -> Bool -> m () Source #

N for Name, calls throwM.

guardF :: MonadFail m => String -> Bool -> m () Source #

F for MonadFail, calls fail.

guardP :: MonadPlus m => Bool -> m () Source #

P for MonadPlus, calls mzero.

throwL :: (MonadThrow m, HasCallStack) => String -> m a Source #

L for Location or CallStack (caLLstack, lol).

throwMs 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).

data LocatedException Source #

Instances
Show LocatedException Source #

custom for Exception (non-Readable).

= displayLocatedException
Instance details

Defined in Prelude.Spiros.Exception

IsString LocatedException Source #

Requires HasCallStack around wherever the string literal is (i.e. at the "call-site" of fromString).

Instance details

Defined in Prelude.Spiros.Exception

Generic LocatedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Associated Types

type Rep LocatedException :: Type -> Type #

Exception LocatedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

Default LocatedException Source #

"" :: LocatedException (see the IsString instance).

Instance details

Defined in Prelude.Spiros.Exception

type Rep LocatedException Source # 
Instance details

Defined in Prelude.Spiros.Exception

type Rep LocatedException = D1 (MetaData "LocatedException" "Prelude.Spiros.Exception" "spiros-0.4.0-4h2fnqdGzKwEsvTfCIxvsa" False) (C1 (MetaCons "LocatedException" PrefixI True) (S1 (MetaSel (Just "_LocatedException_stack") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CallStack) :*: S1 (MetaSel (Just "_LocatedException_message") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))

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 doctested. Those with single @>@ may have brittle output, and codeblocks might describe relations by "returning" variables, and thus aren't.