{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Refined.Internal
(
Refined(Refined)
, refine
, refineThrow
, refineFail
, refineError
, refineTH
, unrefine
, Predicate (validate)
, Not
, And
, type (&&)
, Or
, type (||)
, IdPred
, LessThan
, GreaterThan
, From
, To
, FromTo
, EqualTo
, NotEqualTo
, Positive
, NonPositive
, Negative
, NonNegative
, ZeroToOne
, NonZero
, SizeLessThan
, SizeGreaterThan
, SizeEqualTo
, NonEmpty
, Ascending
, Descending
, Weaken (weaken)
, andLeft
, andRight
, leftOr
, rightOr
, RefineException
( RefineNotException
, RefineAndException
, RefineOrException
, RefineOtherException
)
, displayRefineException
, RefineT, runRefineT, mapRefineT
, RefineM, refineM, runRefineM
, throwRefine, catchRefine
, throwRefineOtherException
, (|>)
, (.>)
) where
import Prelude
(Num, fromIntegral, undefined)
import Control.Applicative (Applicative (pure))
import Control.Exception (Exception (displayException))
import Control.Monad (Monad, unless, when)
import Data.Bool (Bool(True,False),(&&), otherwise)
import Data.Coerce (coerce)
import Data.Either
(Either (Left, Right), either, isRight)
import Data.Eq (Eq, (==), (/=))
import Data.Foldable (Foldable(length, foldl'))
import Data.Function (const, flip, ($), (.))
import Data.Functor (Functor, fmap)
import Data.Functor.Identity (Identity (runIdentity))
import Data.List ((++))
import Data.Monoid (mconcat)
import Data.Ord (Ord, (<), (<=), (>), (>=))
import Data.Proxy (Proxy (Proxy))
import Data.Semigroup (Semigroup((<>)))
import Data.Typeable (TypeRep, Typeable, typeOf)
import Data.Void (Void)
import Text.Read (Read (readsPrec), lex, readParen)
import Text.Show (Show (show))
import Control.Monad.Catch (MonadThrow)
import qualified Control.Monad.Catch as MonadThrow
import Control.Monad.Error.Class (MonadError)
import qualified Control.Monad.Error.Class as MonadError
import Control.Monad.Fail (MonadFail, fail)
import Control.Monad.Fix (MonadFix, fix)
import Control.Monad.Trans.Class (MonadTrans (lift))
import Control.Monad.Trans.Except (ExceptT)
import qualified Control.Monad.Trans.Except as ExceptT
import GHC.Generics (Generic, Generic1)
import GHC.TypeLits (type (<=), KnownNat, Nat, natVal)
import Refined.These (These(This,That,These))
import qualified Data.Text.Prettyprint.Doc as PP
import qualified Language.Haskell.TH.Syntax as TH
infixl 0 |>
infixl 9 .>
(|>) :: a -> (a -> b) -> b
(|>) = flip ($)
{-# INLINE (|>) #-}
(.>) :: (a -> b) -> (b -> c) -> a -> c
f .> g = \x -> g (f x)
{-# INLINE (.>) #-}
data Ordered a = Empty | Decreasing a | Increasing a
inc :: Ordered a -> Bool
inc (Decreasing _) = False
inc _ = True
{-# INLINE inc #-}
dec :: Ordered a -> Bool
dec (Increasing _) = False
dec _ = True
{-# INLINE dec #-}
increasing :: (Foldable t, Ord a) => t a -> Bool
increasing = inc . foldl' go Empty where
go Empty y = Increasing y
go (Decreasing x) _ = Decreasing x
go (Increasing x) y
| x <= y = Increasing y
| otherwise = Decreasing y
{-# INLINABLE increasing #-}
decreasing :: (Foldable t, Ord a) => t a -> Bool
decreasing = dec . foldl' go Empty where
go Empty y = Decreasing y
go (Increasing x) _ = Increasing x
go (Decreasing x) y
| x >= y = Decreasing y
| otherwise = Increasing y
{-# INLINABLE decreasing #-}
newtype Refined p x = Refined x
deriving (Eq, Foldable , Ord, Show, Typeable)
type role Refined nominal nominal
instance (Read x, Predicate p x) => Read (Refined p x) where
readsPrec d = readParen (d > 10) $ \r1 -> do
("Refined", r2) <- lex r1
(raw, r3) <- readsPrec 11 r2
case refine raw of
Right val -> [(val, r3)]
Left _ -> []
instance (TH.Lift x) => TH.Lift (Refined p x) where
lift (Refined a) = [|Refined a|]
refine :: (Predicate p x) => x -> Either RefineException (Refined p x)
refine x = do
let predicateByResult :: RefineM (Refined p x) -> p
predicateByResult = const undefined
runRefineM $ fix $ \result -> do
validate (predicateByResult result) x
pure (Refined x)
{-# INLINABLE refine #-}
refineThrow :: (Predicate p x, MonadThrow m) => x -> m (Refined p x)
refineThrow = refine .> either MonadThrow.throwM pure
{-# INLINABLE refineThrow #-}
refineFail :: (Predicate p x, MonadFail m) => x -> m (Refined p x)
refineFail = refine .> either (displayException .> fail) pure
{-# INLINABLE refineFail #-}
refineError :: (Predicate p x, MonadError RefineException m)
=> x -> m (Refined p x)
refineError = refine .> either MonadError.throwError pure
{-# INLINABLE refineError #-}
refineTH :: (Predicate p x, TH.Lift x) => x -> TH.Q (TH.TExp (Refined p x))
refineTH = let refineByResult :: (Predicate p x)
=> TH.Q (TH.TExp (Refined p x))
-> x
-> Either RefineException (Refined p x)
refineByResult = const refine
in fix $ \loop -> refineByResult (loop undefined)
.> either (show .> fail) TH.lift
.> fmap TH.TExp
{-# INLINE unrefine #-}
unrefine :: Refined p x -> x
unrefine = coerce
class (Typeable p) => Predicate p x where
{-# MINIMAL validate #-}
validate :: (Monad m) => p -> x -> RefineT m ()
data IdPred
deriving (Generic)
instance Predicate IdPred x where
validate _ _ = pure ()
data Not p
deriving (Generic, Generic1)
instance (Predicate p x, Typeable p) => Predicate (Not p) x where
validate p x = do
result <- runRefineT (validate @p undefined x)
when (isRight result) $ do
throwRefine (RefineNotException (typeOf p))
data And l r
deriving (Generic, Generic1)
infixr 3 &&
type (&&) = And
instance ( Predicate l x, Predicate r x, Typeable l, Typeable r
) => Predicate (And l r) x where
validate p x = do
a <- lift $ runRefineT $ validate @l undefined x
b <- lift $ runRefineT $ validate @r undefined x
let throw err = throwRefine (RefineAndException (typeOf p) err)
case (a, b) of
(Left e, Left e1) -> throw (These e e1)
(Left e, _) -> throw (This e)
(Right _, Left e) -> throw (That e)
(Right _, Right _) -> pure ()
data Or l r
deriving (Generic, Generic1)
infixr 2 ||
type (||) = Or
instance ( Predicate l x, Predicate r x, Typeable l, Typeable r
) => Predicate (Or l r) x where
validate p x = do
left <- lift $ runRefineT $ validate @l undefined x
right <- lift $ runRefineT $ validate @r undefined x
case (left, right) of
(Left l, Left r) -> throwRefine (RefineOrException (typeOf p) l r)
_ -> pure ()
data SizeLessThan (n :: Nat)
deriving (Generic)
instance (Foldable t, KnownNat n) => Predicate (SizeLessThan n) (t a) where
validate p x = do
let x' = natVal p
sz = length x
unless (sz < fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Size of Foldable is not less than " <> PP.pretty x' <> "\n"
<> "\tSize is: " <> PP.pretty sz
data SizeGreaterThan (n :: Nat)
deriving (Generic)
instance (Foldable t, KnownNat n) => Predicate (SizeGreaterThan n) (t a) where
validate p x = do
let x' = natVal p
sz = length x
unless (sz > fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Size of Foldable is not greater than " <> PP.pretty x' <> "\n"
<> "\tSize is: " <> PP.pretty sz
data SizeEqualTo (n :: Nat)
deriving (Generic)
instance (Foldable t, KnownNat n) => Predicate (SizeEqualTo n) (t a) where
validate p x = do
let x' = natVal p
sz = length x
unless (sz == fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Size of Foldable is not equal to " <> PP.pretty x' <> "\n"
<> "\tSize is: " <> PP.pretty sz
data Ascending
deriving (Generic)
instance (Foldable t, Ord a) => Predicate Ascending (t a) where
validate p x = do
unless (increasing x) $ do
throwRefineOtherException (typeOf p)
$ "Foldable is not in ascending order "
data Descending
deriving (Generic)
instance (Foldable t, Ord a) => Predicate Descending (t a) where
validate p x = do
unless (decreasing x) $ do
throwRefineOtherException (typeOf p)
$ "Foldable is not in descending order "
data LessThan (n :: Nat)
deriving (Generic)
instance (Ord x, Num x, KnownNat n) => Predicate (LessThan n) x where
validate p x = do
let x' = natVal p
unless (x < fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Value is not less than " <> PP.pretty x'
data GreaterThan (n :: Nat)
deriving (Generic)
instance (Ord x, Num x, KnownNat n) => Predicate (GreaterThan n) x where
validate p x = do
let x' = natVal p
unless (x > fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Value is not greater than " <> PP.pretty x'
data From (n :: Nat)
deriving (Generic)
instance (Ord x, Num x, KnownNat n) => Predicate (From n) x where
validate p x = do
let x' = natVal p
unless (x >= fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Value is less than " <> PP.pretty x'
data To (n :: Nat)
deriving (Generic)
instance (Ord x, Num x, KnownNat n) => Predicate (To n) x where
validate p x = do
let x' = natVal p
unless (x <= fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Value is greater than " <> PP.pretty x'
data FromTo (mn :: Nat) (mx :: Nat)
deriving (Generic)
instance ( Ord x, Num x, KnownNat mn, KnownNat mx, mn <= mx
) => Predicate (FromTo mn mx) x where
validate p x = do
let mn' = natVal (Proxy @mn)
let mx' = natVal (Proxy @mx)
unless ((x >= fromIntegral mn') && (x <= fromIntegral mx')) $ do
let msg = [ "Value is out of range (minimum: "
, PP.pretty mn'
, ", maximum: "
, PP.pretty mx'
, ")"
] |> mconcat
throwRefineOtherException (typeOf p) msg
data EqualTo (n :: Nat)
deriving (Generic)
instance (Eq x, Num x, KnownNat n) => Predicate (EqualTo n) x where
validate p x = do
let x' = natVal p
unless (x == fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Value does not equal " <> PP.pretty x'
data NotEqualTo (n :: Nat)
deriving (Generic)
instance (Eq x, Num x, KnownNat n) => Predicate (NotEqualTo n) x where
validate p x = do
let x' = natVal p
unless (x /= fromIntegral x') $ do
throwRefineOtherException (typeOf p)
$ "Value does equal " <> PP.pretty x'
type Positive = GreaterThan 0
type NonPositive = To 0
type Negative = LessThan 0
type NonNegative = From 0
type ZeroToOne = FromTo 0 1
type NonZero = NotEqualTo 0
type NonEmpty = SizeGreaterThan 0
class Weaken from to where
weaken :: Refined from x -> Refined to x
weaken = coerce
instance (n <= m) => Weaken (LessThan n) (LessThan m)
instance (n <= m) => Weaken (LessThan n) (To m)
instance (n <= m) => Weaken (To n) (To m)
instance (m <= n) => Weaken (GreaterThan n) (GreaterThan m)
instance (m <= n) => Weaken (GreaterThan n) (From m)
instance (m <= n) => Weaken (From n) (From m)
instance (p <= n, m <= q) => Weaken (FromTo n m) (FromTo p q)
instance (p <= n) => Weaken (FromTo n m) (From p)
instance (m <= q) => Weaken (FromTo n m) (To q)
andLeft :: Refined (And l r) x -> Refined l x
andLeft = coerce
andRight :: Refined (And l r) x -> Refined r x
andRight = coerce
leftOr :: Refined l x -> Refined (Or l r) x
leftOr = coerce
rightOr :: Refined r x -> Refined (Or l r) x
rightOr = coerce
data RefineException
=
RefineNotException
{ _RefineException_typeRep :: !TypeRep
}
|
RefineAndException
{ _RefineException_typeRep :: !TypeRep
, _RefineException_andChild :: !(These RefineException RefineException)
}
|
RefineOrException
{ _RefineException_typeRep :: !TypeRep
, _RefineException_orLChild :: !RefineException
, _RefineException_orRChild :: !RefineException
}
|
RefineOtherException
{ _RefineException_typeRep :: !TypeRep
, _RefineException_message :: !(PP.Doc Void)
}
deriving (Generic)
instance Show RefineException where
show = PP.pretty .> show
displayRefineException :: RefineException -> PP.Doc ann
displayRefineException (RefineOtherException tr msg)
= PP.pretty ("The predicate (" ++ show tr ++ ") does not hold: \n \t" ++ show msg)
displayRefineException (RefineNotException tr)
= PP.pretty ("The negation of the predicate (" ++ show tr ++ ") does not hold.")
displayRefineException (RefineOrException tr orLChild orRChild)
= PP.pretty ("Both subpredicates failed in: (" ++ show tr ++ "). \n")
<> "\t" <> (displayRefineException orLChild) <> "\n"
<> "\t" <> (displayRefineException orRChild) <> "\n"
displayRefineException (RefineAndException tr andChild)
= PP.pretty ("The predicate (" ++ show tr ++ ") does not hold: \n \t")
<> case andChild of
This a -> "The left subpredicate does not hold:\n\t" <> displayRefineException a <> "\n"
That b -> "The right subpredicate does not hold:\n\t" <> displayRefineException b <> "\n"
These a b -> "\t Neither subpredicate holds: \n"
<> "\t" <> displayRefineException a <> "\n"
<> "\t" <> displayRefineException b <> "\n"
instance PP.Pretty RefineException where
pretty = displayRefineException
instance Exception RefineException where
displayException = show
newtype RefineT m a
= RefineT (ExceptT RefineException m a)
deriving ( Functor, Applicative, Monad, MonadFix
, MonadError RefineException, MonadTrans
, Generic, Generic1
)
runRefineT
:: RefineT m a
-> m (Either RefineException a)
runRefineT = coerce .> ExceptT.runExceptT
mapRefineT
:: (m (Either RefineException a) -> n (Either RefineException b))
-> RefineT m a
-> RefineT n b
mapRefineT f = coerce .> ExceptT.mapExceptT f .> coerce
type RefineM a = RefineT Identity a
refineM
:: Either RefineException a
-> RefineM a
refineM = ExceptT.except .> coerce
runRefineM
:: RefineM a
-> Either RefineException a
runRefineM = runRefineT .> runIdentity
throwRefine
:: (Monad m)
=> RefineException
-> RefineT m a
throwRefine = MonadError.throwError
catchRefine
:: (Monad m)
=> RefineT m a
-> (RefineException -> RefineT m a)
-> RefineT m a
catchRefine = MonadError.catchError
throwRefineOtherException
:: (Monad m)
=> TypeRep
-> PP.Doc Void
-> RefineT m a
throwRefineOtherException rep
= RefineOtherException rep .> throwRefine