|
3 | 3 | {-# LANGUAGE TupleSections #-} |
4 | 4 | {-# LANGUAGE RecordWildCards #-} |
5 | 5 | {-# LANGUAGE OverloadedStrings #-} |
| 6 | +{-# LANGUAGE DeriveTraversable #-} |
| 7 | + |
6 | 8 | {-# OPTIONS_GHC -Wno-x-partial #-} |
7 | 9 |
|
8 | 10 | module Language.Haskell.Liquid.Bare.Check |
9 | 11 | ( checkTargetSpec |
10 | 12 | , checkBareSpec |
11 | 13 | , checkTargetSrc |
| 14 | + , checkStratTys |
12 | 15 | , tyCompat |
13 | 16 | ) where |
14 | 17 |
|
15 | | - |
16 | 18 | import Language.Haskell.Liquid.Constraint.ToFixpoint |
17 | 19 |
|
18 | 20 | import Liquid.GHC.API as Ghc hiding ( Located |
@@ -55,27 +57,101 @@ import qualified Language.Haskell.Liquid.Bare.Resolve as Bare |
55 | 57 | import Language.Haskell.Liquid.UX.Config |
56 | 58 | import Language.Fixpoint.Types.Config (ElabFlags (ElabFlags), solverFlags) |
57 | 59 |
|
58 | | - |
59 | 60 | ---------------------------------------------------------------------------------------------- |
60 | 61 | -- | Checking TargetSrc ------------------------------------------------------------------------ |
61 | 62 | ---------------------------------------------------------------------------------------------- |
62 | | -checkTargetSrc :: Config -> TargetSrc -> Either Diagnostics () |
63 | | -checkTargetSrc cfg spec |
| 63 | +checkTargetSrc :: Config -> BareSpec -> TargetSrc -> Either Diagnostics () |
| 64 | +checkTargetSrc cfg bare spec |
64 | 65 | | nopositivity cfg |
65 | 66 | || nopositives == emptyDiagnostics |
66 | 67 | = Right () |
67 | 68 | | otherwise |
68 | 69 | = Left nopositives |
69 | | - where nopositives = checkPositives (gsTcs spec) |
| 70 | + where nopositives = checkPositives bare $ gsTcs spec |
70 | 71 |
|
| 72 | +isStratifiedTyCon :: BareSpec -> TyCon -> Bool |
| 73 | +isStratifiedTyCon bs tc = Ghc.tyConName tc `elem` sn |
| 74 | + where sn = mapMaybe (getLHGHCName . F.val) $ S.toList $ stratified bs |
71 | 75 |
|
72 | | -checkPositives :: [TyCon] -> Diagnostics |
73 | | -checkPositives tys = mkDiagnostics [] $ mkNonPosError (getNonPositivesTyCon tys) |
| 76 | +checkPositives :: BareSpec -> [TyCon] -> Diagnostics |
| 77 | +checkPositives bare tys = mkDiagnostics [] |
| 78 | + $ mkNonPosError |
| 79 | + $ filter (not . isStratifiedTyCon bare . fst) |
| 80 | + $ getNonPositivesTyCon tys |
74 | 81 |
|
75 | 82 | mkNonPosError :: [(TyCon, [DataCon])] -> [Error] |
76 | 83 | mkNonPosError tcs = [ ErrPosTyCon (getSrcSpan tc) (pprint tc) (pprint dc <+> ":" <+> pprint (dataConRepType dc)) |
77 | 84 | | (tc, dc:_) <- tcs] |
78 | 85 |
|
| 86 | +-------------------------------------------------- |
| 87 | +-- | Checking that stratified ctors are present -- |
| 88 | +-------------------------------------------------- |
| 89 | + |
| 90 | +--- | Like 'Either' but the 'Semigroup' instance combines the failure |
| 91 | +--- | values. |
| 92 | +data Validation e a |
| 93 | + = Failure e |
| 94 | + | Success a |
| 95 | + deriving (Show, Eq, Functor, Foldable, Traversable) |
| 96 | + |
| 97 | +instance (Semigroup e, Semigroup a) => Semigroup (Validation e a) where |
| 98 | + Failure e1 <> Failure e2 = Failure (e1 <> e2) |
| 99 | + Failure e <> _ = Failure e |
| 100 | + _ <> Failure e = Failure e |
| 101 | + Success x <> Success y = Success (x <> y) |
| 102 | + |
| 103 | +instance (Semigroup e, Monoid a) => Monoid (Validation e a) where |
| 104 | + mempty = Success mempty |
| 105 | + mappend = (<>) |
| 106 | + |
| 107 | +valToEither :: Validation e a -> Either e a |
| 108 | +valToEither (Failure e) = Left e |
| 109 | +valToEither (Success x) = Right x |
| 110 | + |
| 111 | +-- | Check that all stratified types have their constructors |
| 112 | +-- defined with refinement type signatures in the BareSpec. |
| 113 | +-- |
| 114 | +-- Yields the names of the data constructors of the stratified types. |
| 115 | +checkStratTys :: BareSpec -> TargetSrc -> Either Diagnostics [Name] |
| 116 | +checkStratTys bare spec = |
| 117 | + valToEither |
| 118 | + $ foldMap (checkStratTy bare) |
| 119 | + $ mapMaybe (traverse (findTyCon (gsTcs spec))) |
| 120 | + $ S.toList $ stratified bare |
| 121 | + |
| 122 | +-- | Find the TyCon corresponding to the given LHName in the given list of TyCons |
| 123 | +findTyCon :: [TyCon] -> LHName -> Maybe TyCon |
| 124 | +findTyCon tcs nm = do |
| 125 | + c <- getLHGHCName nm |
| 126 | + L.find ((== c) . Ghc.tyConName) tcs |
| 127 | + |
| 128 | +-- | Check that the given TyCon is an ADT and that all its constructors |
| 129 | +-- have refinements in the BareSpec. |
| 130 | +checkStratTy :: BareSpec -> Located TyCon -> Validation Diagnostics [Name] |
| 131 | +checkStratTy spec ltycon = |
| 132 | + case tyConDataCons_maybe (val ltycon) of |
| 133 | + Just ctors -> foldMap (checkStratCtor ltycon spec) ctors |
| 134 | + Nothing -> Failure $ mkDiagnostics mempty [ err ] |
| 135 | + where |
| 136 | + pos = GM.sourcePos2SrcSpan (loc ltycon) (locE ltycon) |
| 137 | + err = ErrStratNotAdt pos (pprint (Ghc.tyConName $ val ltycon)) |
| 138 | + |
| 139 | +-- | Check that the given DataCon has a refinement type signature in the BareSpec. |
| 140 | +-- |
| 141 | +-- Yields the names of the data constructors that are stratified. |
| 142 | +checkStratCtor :: Located TyCon -> BareSpec -> DataCon -> Validation Diagnostics [Name] |
| 143 | +checkStratCtor ltycon spec datacon |
| 144 | + | hasRefinementTypeSignature datacon (map (val . fst) $ sigs spec) |
| 145 | + = Success [ dataConName datacon ] |
| 146 | + | otherwise = Failure $ mkDiagnostics mempty [ err ] |
| 147 | + where |
| 148 | + pos = GM.sourcePos2SrcSpan (loc ltycon) (locE ltycon) |
| 149 | + err = ErrStratNotRefCtor pos (pprint $ dataConName datacon) (pprint $ Ghc.tyConName $ val ltycon) |
| 150 | + hasRefinementTypeSignature :: DataCon -> [LHName] -> Bool |
| 151 | + hasRefinementTypeSignature dc lns = |
| 152 | + dataConName dc `elem` mapMaybe getLHGHCName lns |
| 153 | + |
| 154 | + |
79 | 155 | ---------------------------------------------------------------------------------------------- |
80 | 156 | -- | Checking BareSpec ------------------------------------------------------------------------ |
81 | 157 | ---------------------------------------------------------------------------------------------- |
@@ -223,11 +299,7 @@ checkConstructorRefinement = mconcat . map checkOne |
223 | 299 | validRef (F.Reft (_, F.PTrue)) |
224 | 300 | = True |
225 | 301 | -- Prop foo from ProofCombinators |
226 | | - validRef (F.Reft (v, F.PAtom F.Eq (F.EApp (F.EVar n) (F.EVar v')) _)) |
227 | | - | n == "Language.Haskell.Liquid.ProofCombinators.prop" |
228 | | - , v == v' |
229 | | - = True |
230 | | - validRef _ = False |
| 302 | + validRef n = isJust $ getPropIndex n |
231 | 303 |
|
232 | 304 | isCtorName x = case idDetails x of |
233 | 305 | DataConWorkId _ -> True |
|
0 commit comments