{-# LANGUAGE ExistentialQuantification, StandaloneDeriving, ScopedTypeVariables #-}

-- |
-- Module      : OAlg.Control.Solver
-- Description : solver with possible failure
-- Copyright   : (c) Erich Gut
-- License     : BSD3
-- Maintainer  : zerich.gut@gmail.com
--
-- A monad to express solving algebraic problems which may fail.
--
-- __Note__ To express algebraic unsolvable
--  - e.g determine the multiplicative inverse of 0 - one should only
--  use the @'failure'@ mechanism from this module (see examples in @'solvable'@).
module OAlg.Control.Solver
  ( -- * Result Type For Solving Algebraic Problems
    Solver(), failure, handle, solve, solvable
  )
  where

import Control.Exception hiding (handle)

--------------------------------------------------------------------------------
-- Solver

-- | monad to solve algebraic problems which may fail because it is not solvable or ...
data Solver x
  = Solution x
  | forall e . Exception e => Failure e

deriving instance Show x => Show (Solver x)

instance Functor Solver where
  fmap :: forall a b. (a -> b) -> Solver a -> Solver b
fmap a -> b
f (Solution a
x) = forall x. x -> Solver x
Solution (a -> b
f a
x)
  fmap a -> b
_ (Failure e
e)  = forall x e. Exception e => e -> Solver x
Failure e
e

instance Applicative Solver where
  pure :: forall x. x -> Solver x
pure = forall x. x -> Solver x
Solution
  (Solution a -> b
f) <*> :: forall a b. Solver (a -> b) -> Solver a -> Solver b
<*> (Solution a
x) = forall x. x -> Solver x
Solution (a -> b
f a
x)
  (Failure e
e)  <*> Solver a
_            = forall x e. Exception e => e -> Solver x
Failure e
e
  Solver (a -> b)
_            <*> (Failure e
e)  = forall x e. Exception e => e -> Solver x
Failure e
e     

instance Monad Solver where
  return :: forall x. x -> Solver x
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
  (Solution a
x) >>= :: forall a b. Solver a -> (a -> Solver b) -> Solver b
>>= a -> Solver b
f = a -> Solver b
f a
x
  (Failure e
e)  >>= a -> Solver b
_ = forall x e. Exception e => e -> Solver x
Failure e
e

-- | extracting the solution from the solver. If during solving an exception @e@ occurs, then @e@ will
-- be thrown via the regular @throw@ mechanism of @'Control.Exception'@.
--
-- __Note__ @solve@ extracts the solution lazy!
solve :: Solver x -> x
solve :: forall x. Solver x -> x
solve (Solution x
x) = x
x 
solve (Failure e
e)  = forall a e. Exception e => e -> a
throw e
e

-- | checks for solvability of a algebraic problem represented be a solver @s@ (see also @'solve'@). 
solvable :: Solver r -> Bool
solvable :: forall r. Solver r -> Bool
solvable (Solution r
_) = Bool
True
solvable (Failure e
_)  = Bool
False

-- | throwing exception in to @'Solver'@ to express unsolvable.
failure :: Exception e => e -> Solver x
failure :: forall e x. Exception e => e -> Solver x
failure = forall x e. Exception e => e -> Solver x
Failure

-- | handling exception.
--
-- __Note__ Only exceptions expressed via the @'failure'@ mechanism can be handled by 'handle'!
handle :: Exception e => Solver x -> (e -> Solver x) -> Solver x
handle :: forall e x. Exception e => Solver x -> (e -> Solver x) -> Solver x
handle x :: Solver x
x@(Solution x
_) e -> Solver x
_ = Solver x
x
handle f :: Solver x
f@(Failure e
e)  e -> Solver x
h = case forall e. Exception e => SomeException -> Maybe e
fromException forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
toException forall a b. (a -> b) -> a -> b
$ e
e of
                              Just e
e' -> e -> Solver x
h e
e'
                              Maybe e
_       -> Solver x
f