{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Grisette.Internal.Internal.Impl.Core.Data.Class.ToCon () where
import Control.Monad.Except (ExceptT (ExceptT))
import Control.Monad.Identity
( Identity (Identity, runIdentity),
IdentityT (IdentityT),
)
import Control.Monad.Trans.Maybe (MaybeT)
import qualified Control.Monad.Writer.Lazy as WriterLazy
import qualified Control.Monad.Writer.Strict as WriterStrict
import qualified Data.ByteString as B
import Data.Functor.Compose (Compose (Compose))
import Data.Functor.Const (Const)
import Data.Functor.Product (Product)
import Data.Functor.Sum (Sum)
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Monoid (Alt, Ap)
import qualified Data.Monoid as Monoid
import Data.Ord (Down)
import Data.Ratio (Ratio, denominator, numerator, (%))
import qualified Data.Text as T
import Data.Word (Word16, Word32, Word64, Word8)
import GHC.Generics
( K1 (K1),
M1 (M1),
Par1 (Par1),
Rec1 (Rec1),
U1,
V1,
(:.:) (Comp1),
type (:*:),
type (:+:),
)
import GHC.TypeNats (KnownNat, type (<=))
import Generics.Deriving (Default (Default), Default1 (Default1))
import Generics.Deriving.Instances ()
import Grisette.Internal.Core.Control.Exception
( AssertionError,
VerificationConditions,
)
import Grisette.Internal.Core.Data.Class.BitCast (bitCastOrCanonical)
import Grisette.Internal.Core.Data.Class.Solvable
( Solvable (conView),
pattern Con,
)
import Grisette.Internal.Internal.Decl.Core.Data.Class.ToCon
( ToCon (toCon),
ToCon1 (liftToCon),
ToCon2,
toCon1,
)
import Grisette.Internal.SymPrim.AlgReal (AlgReal (AlgExactRational))
import Grisette.Internal.SymPrim.BV
( IntN (IntN),
WordN (WordN),
)
import Grisette.Internal.SymPrim.FP
( FP,
FP32,
FP64,
FPRoundingMode,
NotRepresentableFPError,
ValidFP,
)
import Grisette.Internal.SymPrim.GeneralFun (type (-->))
import Grisette.Internal.SymPrim.IntBitwidth (intBitwidthQ)
import Grisette.Internal.SymPrim.Prim.Term (LinkedRep)
import Grisette.Internal.SymPrim.SymAlgReal (SymAlgReal)
import Grisette.Internal.SymPrim.SymBV
( SymIntN,
SymWordN,
)
import Grisette.Internal.SymPrim.SymBool (SymBool)
import Grisette.Internal.SymPrim.SymFP
( SymFP,
SymFP32,
SymFP64,
SymFPRoundingMode,
)
import Grisette.Internal.SymPrim.SymGeneralFun (type (-~>) (SymGeneralFun))
import Grisette.Internal.SymPrim.SymInteger (SymInteger)
import Grisette.Internal.SymPrim.SymTabularFun (type (=~>) (SymTabularFun))
import Grisette.Internal.SymPrim.TabularFun (type (=->))
import Grisette.Internal.TH.Derivation.Derive (derive)
#define CONCRETE_TOCON(type) \
instance ToCon type type where \
toCon = Just
#define CONCRETE_TOCON_BV(type) \
instance (KnownNat n, 1 <= n) => ToCon (type n) (type n) where \
toCon = Just
#if 1
CONCRETE_TOCON(Bool)
CONCRETE_TOCON(Integer)
CONCRETE_TOCON(Char)
CONCRETE_TOCON(Int)
CONCRETE_TOCON(Int8)
CONCRETE_TOCON(Int16)
CONCRETE_TOCON(Int32)
CONCRETE_TOCON(Int64)
CONCRETE_TOCON(Word)
CONCRETE_TOCON(Word8)
CONCRETE_TOCON(Word16)
CONCRETE_TOCON(Word32)
CONCRETE_TOCON(Word64)
CONCRETE_TOCON(Float)
CONCRETE_TOCON(Double)
CONCRETE_TOCON(B.ByteString)
CONCRETE_TOCON(T.Text)
CONCRETE_TOCON_BV(WordN)
CONCRETE_TOCON_BV(IntN)
CONCRETE_TOCON(FPRoundingMode)
CONCRETE_TOCON(Monoid.All)
CONCRETE_TOCON(Monoid.Any)
CONCRETE_TOCON(Ordering)
#endif
instance (ValidFP eb sb) => ToCon (FP eb sb) (FP eb sb) where
toCon :: FP eb sb -> Maybe (FP eb sb)
toCon = FP eb sb -> Maybe (FP eb sb)
forall a. a -> Maybe a
Just
instance ToCon (a =-> b) (a =-> b) where
toCon :: (a =-> b) -> Maybe (a =-> b)
toCon = (a =-> b) -> Maybe (a =-> b)
forall a. a -> Maybe a
Just
instance ToCon (a --> b) (a --> b) where
toCon :: (a --> b) -> Maybe (a --> b)
toCon = (a --> b) -> Maybe (a --> b)
forall a. a -> Maybe a
Just
#define TO_CON_SYMID_SIMPLE(symtype) \
instance ToCon symtype symtype where \
toCon = Just
#define TO_CON_SYMID_BV(symtype) \
instance ToCon (symtype n) (symtype n) where \
toCon = Just
#define TO_CON_SYMID_FUN(op) \
instance ToCon (a op b) (a op b) where \
toCon = Just
#if 1
TO_CON_SYMID_SIMPLE(SymBool)
TO_CON_SYMID_SIMPLE(SymInteger)
TO_CON_SYMID_SIMPLE(SymAlgReal)
TO_CON_SYMID_BV(SymIntN)
TO_CON_SYMID_BV(SymWordN)
TO_CON_SYMID_FUN(=~>)
TO_CON_SYMID_FUN(-~>)
TO_CON_SYMID_SIMPLE(SymFPRoundingMode)
#endif
instance (ValidFP eb sb) => ToCon (SymFP eb sb) (SymFP eb sb) where
toCon :: SymFP eb sb -> Maybe (SymFP eb sb)
toCon = SymFP eb sb -> Maybe (SymFP eb sb)
forall a. a -> Maybe a
Just
#define TO_CON_FROMSYM_SIMPLE(contype, symtype) \
instance ToCon symtype contype where \
toCon = conView
#define TO_CON_FROMSYM_BV(contype, symtype) \
instance (KnownNat n, 1 <= n) => ToCon (symtype n) (contype n) where \
toCon = conView
#define TO_CON_FROMSYM_FUN(conop, symop, consop) \
instance (LinkedRep ca sa, LinkedRep cb sb) => ToCon (symop sa sb) (conop ca cb) where \
toCon a@(consop _) = conView a
#if 1
TO_CON_FROMSYM_SIMPLE(Integer, SymInteger)
TO_CON_FROMSYM_SIMPLE(AlgReal, SymAlgReal)
TO_CON_FROMSYM_BV(IntN, SymIntN)
TO_CON_FROMSYM_BV(WordN, SymWordN)
TO_CON_FROMSYM_FUN((=->), (=~>), SymTabularFun)
TO_CON_FROMSYM_FUN((-->), (-~>), SymGeneralFun)
TO_CON_FROMSYM_SIMPLE(FPRoundingMode, SymFPRoundingMode)
#endif
instance (ValidFP eb sb) => ToCon (SymFP eb sb) (FP eb sb) where
toCon :: SymFP eb sb -> Maybe (FP eb sb)
toCon = SymFP eb sb -> Maybe (FP eb sb)
forall c t. Solvable c t => t -> Maybe c
conView
#define TOCON_MACHINE_INTEGER(sbvw, bvw, n, int) \
instance ToCon (sbvw n) int where \
toCon (Con (bvw v :: bvw n)) = Just $ fromIntegral v; \
toCon _ = Nothing
#if 1
TOCON_MACHINE_INTEGER(SymIntN, IntN, 8, Int8)
TOCON_MACHINE_INTEGER(SymIntN, IntN, 16, Int16)
TOCON_MACHINE_INTEGER(SymIntN, IntN, 32, Int32)
TOCON_MACHINE_INTEGER(SymIntN, IntN, 64, Int64)
TOCON_MACHINE_INTEGER(SymWordN, WordN, 8, Word8)
TOCON_MACHINE_INTEGER(SymWordN, WordN, 16, Word16)
TOCON_MACHINE_INTEGER(SymWordN, WordN, 32, Word32)
TOCON_MACHINE_INTEGER(SymWordN, WordN, 64, Word64)
TOCON_MACHINE_INTEGER(SymIntN, IntN, $intBitwidthQ, Int)
TOCON_MACHINE_INTEGER(SymWordN, WordN, $intBitwidthQ, Word)
#endif
instance ToCon SymFP32 Float where
toCon :: SymFP32 -> Maybe Float
toCon (Con (FP32
fp :: FP32)) = Float -> Maybe Float
forall a. a -> Maybe a
Just (Float -> Maybe Float) -> Float -> Maybe Float
forall a b. (a -> b) -> a -> b
$ FP32 -> Float
forall from to. BitCastOrCanonical from to => from -> to
bitCastOrCanonical FP32
fp
toCon SymFP32
_ = Maybe Float
forall a. Maybe a
Nothing
instance ToCon SymFP64 Double where
toCon :: SymFP64 -> Maybe Double
toCon (Con (FP64
fp :: FP64)) = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double) -> Double -> Maybe Double
forall a b. (a -> b) -> a -> b
$ FP64 -> Double
forall from to. BitCastOrCanonical from to => from -> to
bitCastOrCanonical FP64
fp
toCon SymFP64
_ = Maybe Double
forall a. Maybe a
Nothing
instance (ToCon a b, Integral b) => ToCon (Ratio a) (Ratio b) where
toCon :: Ratio a -> Maybe (Ratio b)
toCon Ratio a
r = do
n <- a -> Maybe b
forall a b. ToCon a b => a -> Maybe b
toCon (Ratio a -> a
forall a. Ratio a -> a
numerator Ratio a
r)
d <- toCon (denominator r)
return $ n % d
instance ToCon SymAlgReal Rational where
toCon :: SymAlgReal -> Maybe Rational
toCon (Con (AlgReal
x :: AlgReal)) =
case AlgReal
x of
AlgExactRational Rational
r -> Rational -> Maybe Rational
forall a. a -> Maybe a
Just Rational
r
AlgReal
_ -> Maybe Rational
forall a. Maybe a
Nothing
toCon SymAlgReal
_ = Maybe Rational
forall a. Maybe a
Nothing