{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TupleSections #-}
module Language.Fixpoint.Types.Solutions (
Solution, GSolution
, Sol (gMap, sEnv, sEbd, sxEnv)
, updateGMap, updateGMapWithKey
, sScp
, CMap
, Hyp, Cube (..), QBind, GBind
, EQual (..)
, EbindSol (..)
, eQual
, trueEqual
, qbToGb, gbToQbs, gbEquals, equalsGb, emptyGMap, qbExprs
, Cand
, fromList
, update
, updateEbind
, lookupQBind
, lookup, glookup
, qb
, qbPreds
, qbFilter
, gbFilterM
, result, resultGradual
, Index (..)
, KIndex (..)
, BindPred (..)
, BIndex (..)
) where
import Prelude hiding (lookup)
import GHC.Generics
import Control.DeepSeq
import Data.Hashable
import qualified Data.Maybe as Mb
import qualified Data.HashMap.Strict as M
import qualified Data.List as L
import Data.Generics (Data)
#if !MIN_VERSION_base(4,14,0)
import Data.Semigroup (Semigroup (..))
#endif
import Data.Typeable (Typeable)
import Control.Monad (filterM)
import Language.Fixpoint.Misc
import Language.Fixpoint.Types.PrettyPrint
import Language.Fixpoint.Types.Spans
import Language.Fixpoint.Types.Names
import Language.Fixpoint.Types.Sorts
import Language.Fixpoint.Types.Theories
import Language.Fixpoint.Types.Refinements
import Language.Fixpoint.Types.Environments
import Language.Fixpoint.Types.Constraints
import Language.Fixpoint.Types.Substitutions
import Language.Fixpoint.SortCheck (elaborate)
import Text.PrettyPrint.HughesPJ.Compat
update :: Sol a QBind -> [KVar] -> [(KVar, EQual)] -> (Bool, Sol a QBind)
update s ks kqs = (or bs, s')
where
kqss = groupKs ks kqs
(bs, s') = folds update1 s kqss
folds :: (a -> b -> (c, a)) -> a -> [b] -> ([c], a)
folds f b = L.foldl' step ([], b)
where
step (cs, acc) x = (c:cs, x')
where
(c, x') = f acc x
groupKs :: [KVar] -> [(KVar, EQual)] -> [(KVar, QBind)]
groupKs ks kqs = [ (k, QB eqs) | (k, eqs) <- M.toList $ groupBase m0 kqs ]
where
m0 = M.fromList $ (,[]) <$> ks
update1 :: Sol a QBind -> (KVar, QBind) -> (Bool, Sol a QBind)
update1 s (k, qs) = (change, updateK k qs s)
where
oldQs = lookupQBind s k
change = qbSize oldQs /= qbSize qs
type Solution = Sol () QBind
type GSolution = Sol (((Symbol, Sort), Expr), GBind) QBind
newtype QBind = QB [EQual] deriving (Show, Data, Typeable, Generic, Eq)
newtype GBind = GB [[EQual]] deriving (Show, Data, Typeable, Generic)
emptyGMap :: GSolution -> GSolution
emptyGMap sol = mapGMap sol (\(x,_) -> (x, GB []))
updateGMapWithKey :: [(KVar, QBind)] -> GSolution -> GSolution
updateGMapWithKey kqs sol = sol {gMap = foldl (\m (k, (QB eq)) -> M.adjust (\(x, GB eqs) -> (x, GB (if eq `elem` eqs then eqs else eq:eqs))) k m) (gMap sol) kqs }
qb :: [EQual] -> QBind
qb = QB
qbEQuals :: QBind -> [EQual]
qbEQuals (QB xs) = xs
qbExprs :: QBind -> [Expr]
qbExprs (QB xs) = eqPred <$> xs
qbToGb :: QBind -> GBind
qbToGb (QB xs) = GB $ map (:[]) xs
gbToQbs :: GBind -> [QBind]
gbToQbs (GB []) = [QB [trueEqual]]
gbToQbs (GB ess) = QB <$> ess
gbEquals :: GBind -> [[EQual]]
gbEquals (GB eqs) = eqs
equalsGb :: [[EQual]] -> GBind
equalsGb = GB
gbFilterM :: Monad m => ([EQual] -> m Bool) -> GBind -> m GBind
gbFilterM f (GB eqs) = GB <$> filterM f eqs
qbSize :: QBind -> Int
qbSize = length . qbEQuals
qbFilter :: (EQual -> Bool) -> QBind -> QBind
qbFilter f (QB eqs) = QB (filter f eqs)
instance NFData QBind
instance NFData GBind
instance PPrint QBind where
pprintTidy k = pprintTidy k . qbEQuals
data EbindSol
= EbDef [SimpC ()] Symbol
| EbSol Expr
| EbIncr
deriving (Show, Generic, NFData)
instance PPrint EbindSol where
pprintTidy k (EbDef i x) = "EbDef:" <+> pprintTidy k i <+> pprintTidy k x
pprintTidy k (EbSol e) = "EbSol:" <+> pprintTidy k e
pprintTidy _ (EbIncr) = "EbIncr"
updateEbind :: Sol a b -> BindId -> Pred -> Sol a b
updateEbind s i !e = case M.lookup i (sEbd s) of
Nothing -> errorstar $ "updateEBind: Unknown ebind " ++ show i
Just (EbSol e0) -> errorstar $ "updateEBind: Re-assigning ebind " ++ show i ++ " with solution: " ++ show e0
Just _ -> s { sEbd = M.insert i (EbSol e) (sEbd s) }
data Sol b a = Sol
{ sEnv :: !SymEnv
, sMap :: !(M.HashMap KVar a)
, gMap :: !(M.HashMap KVar b)
, sHyp :: !(M.HashMap KVar Hyp)
, sScp :: !(M.HashMap KVar IBindEnv)
, sEbd :: !(M.HashMap BindId EbindSol)
, sxEnv :: !(SEnv (BindId, Sort))
} deriving (Generic)
deriving instance (NFData b, NFData a) => NFData (Sol b a)
updateGMap :: Sol b a -> M.HashMap KVar b -> Sol b a
updateGMap sol gmap = sol {gMap = gmap}
mapGMap :: Sol b a -> (b -> b) -> Sol b a
mapGMap sol f = sol {gMap = M.map f (gMap sol)}
instance Semigroup (Sol a b) where
s1 <> s2 = Sol { sEnv = (sEnv s1) <> (sEnv s2)
, sMap = (sMap s1) <> (sMap s2)
, gMap = (gMap s1) <> (gMap s2)
, sHyp = (sHyp s1) <> (sHyp s2)
, sScp = (sScp s1) <> (sScp s2)
, sEbd = (sEbd s1) <> (sEbd s2)
, sxEnv = (sxEnv s1) <> (sxEnv s2)
}
instance Monoid (Sol a b) where
mempty = Sol { sEnv = mempty
, sMap = mempty
, gMap = mempty
, sHyp = mempty
, sScp = mempty
, sEbd = mempty
, sxEnv = mempty
}
mappend = (<>)
instance Functor (Sol a) where
fmap f (Sol e s m1 m2 m3 m4 m5) = Sol e (f <$> s) m1 m2 m3 m4 m5
instance (PPrint a, PPrint b) => PPrint (Sol a b) where
pprintTidy k s = vcat [ "sMap :=" <+> pprintTidy k (sMap s)
, "sEbd :=" <+> pprintTidy k (sEbd s)
]
type Hyp = ListNE Cube
data Cube = Cube
{ cuBinds :: IBindEnv
, cuSubst :: Subst
, cuId :: SubcId
, cuTag :: Tag
} deriving (Generic, NFData)
instance PPrint Cube where
pprintTidy _ c = "Cube" <+> pprint (cuId c)
instance Show Cube where
show = showpp
result :: Sol a QBind -> M.HashMap KVar Expr
result s = sMap $ (pAnd . fmap eqPred . qbEQuals) <$> s
resultGradual :: GSolution -> M.HashMap KVar (Expr, [Expr])
resultGradual s = fmap go' (gMap s)
where
go' ((_,e), GB eqss)
= (e, [PAnd $ fmap eqPred eqs | eqs <- eqss])
fromList :: SymEnv
-> [(KVar, a)]
-> [(KVar, b)]
-> [(KVar, Hyp)]
-> M.HashMap KVar IBindEnv
-> [(BindId, EbindSol)]
-> SEnv (BindId, Sort)
-> Sol a b
fromList env kGs kXs kYs z ebs xbs
= Sol env kXm kGm kYm z ebm xbs
where
kXm = M.fromList kXs
kYm = M.fromList kYs
kGm = M.fromList kGs
ebm = M.fromList ebs
qbPreds :: String -> Sol a QBind -> Subst -> QBind -> [(Pred, EQual)]
qbPreds msg s su (QB eqs) = [ (elabPred eq, eq) | eq <- eqs ]
where
elabPred eq = elaborate (atLoc eq $ "qbPreds:" ++ msg) env
. subst su
. eqPred
$ eq
env = sEnv s
lookupQBind :: Sol a QBind -> KVar -> QBind
lookupQBind s k = Mb.fromMaybe (QB []) (lookupElab s k)
where
_msg = "lookupQB: k = " ++ show k
glookup :: GSolution -> KVar -> Either Hyp (Either QBind (((Symbol, Sort), Expr), GBind))
glookup s k
| Just gbs <- M.lookup k (gMap s)
= Right (Right gbs)
| Just cs <- M.lookup k (sHyp s)
= Left cs
| Just eqs <- lookupElab s k
= Right (Left eqs)
| otherwise
= errorstar $ "solLookup: Unknown kvar " ++ show k
lookup :: Sol a QBind -> KVar -> Either Hyp QBind
lookup s k
| Just cs <- M.lookup k (sHyp s)
= Left cs
| Just eqs <- lookupElab s k
= Right eqs
| otherwise
= errorstar $ "solLookup: Unknown kvar " ++ show k
lookupElab :: Sol b QBind -> KVar -> Maybe QBind
lookupElab s k = M.lookup k (sMap s)
updateK :: KVar -> a -> Sol b a -> Sol b a
updateK k qs s = s { sMap = M.insert k qs (sMap s)
}
type Cand a = [(Expr, a)]
data EQual = EQL
{ eqQual :: !Qualifier
, eqPred :: !Expr
, _eqArgs :: ![Expr]
} deriving (Eq, Show, Data, Typeable, Generic)
instance Loc EQual where
srcSpan = srcSpan . eqQual
trueEqual :: EQual
trueEqual = EQL trueQual mempty []
instance PPrint EQual where
pprintTidy k = pprintTidy k . eqPred
instance NFData EQual
eQual :: Qualifier -> [Symbol] -> EQual
eQual q xs = EQL q p es
where
p = subst su $ qBody q
su = mkSubst $ safeZip "eQual" qxs es
es = eVar <$> xs
qxs = qpSym <$> qParams q
data KIndex = KIndex { kiBIndex :: !BindId
, kiPos :: !Int
, kiKVar :: !KVar
}
deriving (Eq, Ord, Show, Generic)
instance Hashable KIndex
instance PPrint KIndex where
pprintTidy _ = tshow
data BIndex = Root
| Bind !BindId
| Cstr !SubcId
deriving (Eq, Ord, Show, Generic)
instance Hashable BIndex
instance PPrint BIndex where
pprintTidy _ = tshow
data BindPred = BP
{ bpConc :: !Pred
, bpKVar :: ![KIndex]
} deriving (Show)
instance PPrint BindPred where
pprintTidy _ = tshow
data Index = FastIdx
{ bindExpr :: !(BindId |-> BindPred)
, kvUse :: !(KIndex |-> KVSub)
, kvDef :: !(KVar |-> Hyp)
, envBinds :: !(CMap IBindEnv)
, envTx :: !(CMap [SubcId])
, envSorts :: !(SEnv Sort)
}
type CMap a = M.HashMap SubcId a