[LIGO-37] [LIGO-38] Looks like it fixes it

This commit is contained in:
Kirill Andreev 2020-08-24 12:29:51 +04:00
parent 3037be689b
commit f554551f75
No known key found for this signature in database
GPG Key ID: CF7DA79DE4785A47
7 changed files with 90 additions and 39 deletions

View File

@ -68,13 +68,13 @@ example :: FilePath
-- example = "../../../src/test/contracts/let_in_multi_bind.mligo" -- example = "../../../src/test/contracts/let_in_multi_bind.mligo"
example = "../../../src/test/contracts/fibo2.mligo" example = "../../../src/test/contracts/fibo2.mligo"
raw :: IO () -- raw :: IO ()
raw = toParseTree (Path example) -- raw = toParseTree (Path example)
>>= print . pp -- >>= print . pp
raw' :: FilePath -> IO () -- raw' :: FilePath -> IO ()
raw' example = toParseTree (Path example) -- raw' example = toParseTree (Path example)
>>= print . pp -- >>= print . pp
sample :: IO () sample :: IO ()
sample sample
@ -89,7 +89,7 @@ sample' example
>>= print . pp . fst >>= print . pp . fst
recognise :: RawTree -> ParserM (LIGO Info) recognise :: RawTree -> ParserM (LIGO Info)
recognise = descent (\_ -> error . show . pp) $ map usingScope recognise = descent (error "Reasonligo.recognise") $ map usingScope
[ -- Contract [ -- Contract
Descent do Descent do
boilerplate $ \case boilerplate $ \case

View File

@ -43,10 +43,10 @@ import ParseTree
-- >>= runParserM . recognise -- >>= runParserM . recognise
-- >>= return . fst -- >>= return . fst
source' :: FilePath -> IO () -- source' :: FilePath -> IO ()
source' f -- source' f
= toParseTree (Path f) -- = toParseTree (Path f)
>>= print . pp -- >>= print . pp
-- sample :: IO () -- sample :: IO ()
-- sample -- sample
@ -60,7 +60,7 @@ source' f
-- >>= print . pp -- >>= print . pp
recognise :: RawTree -> ParserM (LIGO Info) recognise :: RawTree -> ParserM (LIGO Info)
recognise = descent (\_ -> error . show . pp) $ map usingScope recognise = descent (error "Reasonligo.recognise") $ map usingScope
[ -- Contract [ -- Contract
Descent do Descent do
boilerplate \case boilerplate \case

View File

@ -44,7 +44,7 @@ import Product
-- >>= print . pp . fst -- >>= print . pp . fst
recognise :: RawTree -> ParserM (LIGO Info) recognise :: RawTree -> ParserM (LIGO Info)
recognise = descent (\_ -> error . show . pp) $ map usingScope recognise = descent (error "Reasonligo.recognise") $ map usingScope
[ -- Contract [ -- Contract
Descent do Descent do
boilerplate $ \case boilerplate $ \case

View File

@ -17,7 +17,9 @@ import Control.Arrow (second)
import Control.Monad.State import Control.Monad.State
import Control.Monad.Catch import Control.Monad.Catch
import Control.Monad.Catch.Pure import Control.Monad.Catch.Pure
import Control.Monad.Writer (WriterT, execWriterT, tell)
import Data.Monoid (First(getFirst))
import qualified Data.List as List import qualified Data.List as List
import Data.Map (Map) import Data.Map (Map)
import qualified Data.Map as Map import qualified Data.Map as Map
@ -46,7 +48,7 @@ data Category = Variable | Type
-- | The type/value declaration. -- | The type/value declaration.
data ScopedDecl = ScopedDecl data ScopedDecl = ScopedDecl
{ _sdName :: LIGO () { _sdName :: Text
, _sdOrigin :: Range , _sdOrigin :: Range
, _sdBody :: Maybe Range , _sdBody :: Maybe Range
, _sdType :: Maybe (Either (LIGO ()) Kind) , _sdType :: Maybe (Either (LIGO ()) Kind)
@ -98,12 +100,6 @@ ofCategory _ _ = False
type Info' = Product [[ScopedDecl], Maybe Category, [Text], Range, ShowRange] type Info' = Product [[ScopedDecl], Maybe Category, [Text], Range, ShowRange]
-- instance Modifies (Product '[[ScopedDecl], Maybe Category, [Text], Range, a]) where
-- ascribe (ds :> _ :> _ :> r :> _) d =
-- color 3 (fsep (map (pp . _sdName) ds))
-- $$ pp r
-- $$ d
addLocalScopes addLocalScopes
:: forall xs :: forall xs
. (Collectable xs, Eq (Product xs)) . (Collectable xs, Eq (Product xs))
@ -290,16 +286,18 @@ lookupEnv :: Text -> [ScopedDecl] -> Maybe ScopedDecl
lookupEnv name = listToMaybe . filter ((name ==) . ppToText . _sdName) lookupEnv name = listToMaybe . filter ((name ==) . ppToText . _sdName)
-- | Add a type declaration to the current scope. -- | Add a type declaration to the current scope.
defType :: HasRange a => LIGO a -> Kind -> LIGO a -> [Text] -> CollectM () defType :: Collectable xs => LIGO (Product xs) -> Kind -> LIGO (Product xs) -> [Text] -> CollectM ()
defType name kind body doc = do defType name' kind body doc = do
define Type define Type
$ ScopedDecl $ ScopedDecl
(void name) name
(getRange $ extract name) r
(Just $ getRange $ extract body) (Just $ getRange $ extract body)
(Just (Right kind)) (Just (Right kind))
[] []
doc doc
where
(r, name) = getTypeName name'
-- -- observe :: Pretty i => Pretty res => Text -> i -> res -> res -- -- observe :: Pretty i => Pretty res => Text -> i -> res -> res
-- -- observe msg i res -- -- observe msg i res
@ -309,23 +307,79 @@ defType name kind body doc = do
-- | Add a value declaration to the current scope. -- | Add a value declaration to the current scope.
def def
:: HasRange a :: Collectable xs
=> LIGO a => LIGO (Product xs)
-> Maybe (LIGO a) -> Maybe (LIGO (Product xs))
-> Maybe (LIGO a) -> Maybe (LIGO (Product xs))
-> [Text] -> [Text]
-> CollectM () -> CollectM ()
def name ty body doc = do def name' ty body doc = do
define Variable define Variable
$ ScopedDecl $ ScopedDecl
(void name) name
(getRange $ extract name) r
((getRange . extract) <$> body) ((getRange . extract) <$> body)
((Left . void) <$> ty) ((Left . void) <$> ty)
[] []
doc doc
where
(r, name) = getName name'
type Collectable xs = (Contains Range xs, Contains [Text] xs) select
:: ( Lattice (Product info)
, Contains ShowRange info
, Contains Range info
, Modifies (Product info)
, Eq (Product info)
)
=> Text
-> [Visit RawLigoList (Product info) (WriterT [LIGO (Product info)] Catch)]
-> LIGO (Product info)
-> (Range, Text)
select what handlers t
= maybe
(error . show $ "Tree does not contain a" <+> pp what <.> ":" <+> pp t <+> pp (getRange $ extract t))
(\t -> (getElem $ extract t, ppToText t))
$ either (const Nothing) listToMaybe
$ runCatch
$ execWriterT
$ visit handlers
t
getName
:: ( Lattice (Product info)
, Contains ShowRange info
, Contains Range info
, Modifies (Product info)
, Eq (Product info)
)
=> LIGO (Product info)
-> (Range, Text)
getName = select "name"
[ Visit \(r, Name t) -> do
tell [make (r, Name t)]
]
getTypeName
:: ( Lattice (Product info)
, Contains ShowRange info
, Contains Range info
, Modifies (Product info)
, Eq (Product info)
)
=> LIGO (Product info)
-> (Range, Text)
getTypeName = select "type name"
[ Visit \(r, TypeName t) -> do
tell [make (r, TypeName t)]
]
type Collectable xs =
( Contains Range xs
, Contains [Text] xs
, Contains ShowRange xs
, Eq (Product xs)
)
instance Collectable xs => Scoped (Product xs) CollectM (LIGO (Product xs)) Contract where instance Collectable xs => Scoped (Product xs) CollectM (LIGO (Product xs)) Contract where
before r _ = enter r before r _ = enter r

View File

@ -383,11 +383,11 @@ instance Pretty1 Pattern where
instance Pretty1 Name where instance Pretty1 Name where
pp1 = \case pp1 = \case
Name raw -> color 2 $ pp raw Name raw -> pp raw
instance Pretty1 TypeName where instance Pretty1 TypeName where
pp1 = \case pp1 = \case
TypeName raw -> color 3 $ pp raw TypeName raw -> pp raw
instance Pretty1 FieldName where instance Pretty1 FieldName where
pp1 = \case pp1 = \case

View File

@ -66,8 +66,8 @@ srcToBytestring = \case
type RawTree = Tree '[ParseTree] RawInfo type RawTree = Tree '[ParseTree] RawInfo
type RawInfo = Product [Range, Text] type RawInfo = Product [Range, Text]
instance {-# OVERLAPS #-} Modifies RawInfo where -- instance {-# OVERLAPS #-} Modifies RawInfo where
ascribe (r :> n :> _) d = color 3 (pp n) <+> pp r `indent` pp d -- ascribe (r :> n :> _) d = color 3 (pp n) <+> pp r `indent` pp d
data TreeKind data TreeKind
= Error = Error

View File

@ -55,9 +55,6 @@ instance Eq (Product '[]) where
instance (Eq x, Eq (Product xs)) => Eq (Product (x : xs)) where instance (Eq x, Eq (Product xs)) => Eq (Product (x : xs)) where
x :> xs == y :> ys = and [x == y, xs == ys] x :> xs == y :> ys = and [x == y, xs == ys]
-- instance Modifies (Product xs) where
-- ascribe _ = id
class PrettyProd xs where class PrettyProd xs where
ppProd :: Product xs -> Doc ppProd :: Product xs -> Doc