microlens and an ugly parse of ,(something,something)
btw we triggered a ghc bug here with iscallTok in parser. Apparently it kills `call` for whichever reason. New ghc solved it.
This commit is contained in:
		
							parent
							
								
									0d52bcf663
								
							
						
					
					
						commit
						0092723895
					
				|  | @ -15,7 +15,7 @@ import Env (PrlgEnv(..), findAtom, findStruct, prlgError) | ||||||
| import Heap (Dereferenced(..), derefHeap, heapStruct, newHeapVars) | import Heap (Dereferenced(..), derefHeap, heapStruct, newHeapVars) | ||||||
| import qualified IR | import qualified IR | ||||||
| import Interpreter (backtrack) | import Interpreter (backtrack) | ||||||
| import Lens.Family2.State | import Lens.Micro.Mtl | ||||||
| import Load (processInput) | import Load (processInput) | ||||||
| import qualified Operators as O | import qualified Operators as O | ||||||
| import System.Console.Haskeline (getInputChar, outputStr, outputStrLn) | import System.Console.Haskeline (getInputChar, outputStr, outputStrLn) | ||||||
|  | @ -50,7 +50,7 @@ printLocals = do | ||||||
| 
 | 
 | ||||||
| promptRetry :: InterpFn | promptRetry :: InterpFn | ||||||
| promptRetry = do | promptRetry = do | ||||||
|   last <- cho `uses` null |   last <- null <$> use cho | ||||||
|   if last |   if last | ||||||
|     then continue |     then continue | ||||||
|     else promptRetry' |     else promptRetry' | ||||||
|  | @ -407,7 +407,7 @@ addPrelude = do | ||||||
|             , U (Struct s) -- expand_something(Arg1, Arg2). |             , U (Struct s) -- expand_something(Arg1, Arg2). | ||||||
|             , U (LocalRef 0) |             , U (LocalRef 0) | ||||||
|             , U (LocalRef 1) |             , U (LocalRef 1) | ||||||
|             , Cut -- TODO  check that the cut works here; this was the whole reason why we migrated off vienna |             , Cut | ||||||
|             , Done |             , Done | ||||||
|             ] |             ] | ||||||
|           , [U (LocalRef 0), U (LocalRef 0), Done] |           , [U (LocalRef 0), U (LocalRef 0), Done] | ||||||
|  |  | ||||||
|  | @ -3,8 +3,8 @@ | ||||||
| module CodeLens where | module CodeLens where | ||||||
| 
 | 
 | ||||||
| import Code | import Code | ||||||
| import Lens.Family2.TH | import Lens.Micro.TH | ||||||
| 
 | 
 | ||||||
| $(makeLenses ''Cho) | makeLenses ''Cho | ||||||
| 
 | 
 | ||||||
| $(makeLenses ''Interp) | makeLenses ''Interp | ||||||
|  |  | ||||||
|  | @ -3,11 +3,11 @@ module Env where | ||||||
| import Code (InterpFn, PrlgEnv) | import Code (InterpFn, PrlgEnv) | ||||||
| import CodeLens | import CodeLens | ||||||
| import qualified IR | import qualified IR | ||||||
| import Lens.Family2.State | import Lens.Micro.Mtl | ||||||
| 
 | 
 | ||||||
| withStrTable :: (IR.StrTable -> (IR.StrTable, a)) -> Env.PrlgEnv a | withStrTable :: (IR.StrTable -> (IR.StrTable, a)) -> Env.PrlgEnv a | ||||||
| withStrTable f = do | withStrTable f = do | ||||||
|   (st', x) <- strtable `uses` f |   (st', x) <- f <$> use strtable | ||||||
|   strtable .= st' |   strtable .= st' | ||||||
|   return x |   return x | ||||||
| 
 | 
 | ||||||
|  |  | ||||||
|  | @ -11,7 +11,7 @@ import qualified Data.Map as M | ||||||
| import Env (PrlgEnv) | import Env (PrlgEnv) | ||||||
| import qualified IR | import qualified IR | ||||||
| import qualified Interpreter as I | import qualified Interpreter as I | ||||||
| import Lens.Family2.State | import Lens.Micro.Mtl | ||||||
| import Load | import Load | ||||||
|   ( compile |   ( compile | ||||||
|   , intern |   , intern | ||||||
|  | @ -67,7 +67,7 @@ interpreterLoop queryMode = do | ||||||
|                then queryExpansion |                then queryExpansion | ||||||
|                else loadExpansion) |                else loadExpansion) | ||||||
|             ast |             ast | ||||||
|         finished <- lift $ cmdq `uses` null |         finished <- lift $ null <$> use cmdq | ||||||
|         when finished . lift . lift . outputStrLn $ |         when finished . lift . lift . outputStrLn $ | ||||||
|           case (resOK, queryMode) of |           case (resOK, queryMode) of | ||||||
|             (True, True) -> "yes." |             (True, True) -> "yes." | ||||||
|  |  | ||||||
|  | @ -5,7 +5,7 @@ import CodeLens | ||||||
| import Data.Foldable (traverse_) | import Data.Foldable (traverse_) | ||||||
| import qualified Data.Map as M | import qualified Data.Map as M | ||||||
| import IR (Id(..)) | import IR (Id(..)) | ||||||
| import Lens.Family2.State | import Lens.Micro.Mtl | ||||||
| 
 | 
 | ||||||
| data Dereferenced | data Dereferenced | ||||||
|   = FreeRef Int |   = FreeRef Int | ||||||
|  | @ -27,7 +27,7 @@ deref' h@(Heap _ hmap) x = | ||||||
| derefHeap = deref' --TODO remove | derefHeap = deref' --TODO remove | ||||||
| 
 | 
 | ||||||
| deref :: Int -> PrlgEnv Dereferenced | deref :: Int -> PrlgEnv Dereferenced | ||||||
| deref = uses (cur . heap) . flip deref' | deref x = flip deref' x <$> use (cur . heap) | ||||||
| 
 | 
 | ||||||
| writeHeap :: Int -> Datum -> PrlgEnv () | writeHeap :: Int -> Datum -> PrlgEnv () | ||||||
| writeHeap a v = cur . heap %= (\(Heap nxt m) -> Heap nxt $ M.insert a v m) | writeHeap a v = cur . heap %= (\(Heap nxt m) -> Heap nxt $ M.insert a v m) | ||||||
|  |  | ||||||
|  | @ -19,8 +19,8 @@ import qualified Data.Map as M | ||||||
| import Env (PrlgEnv) | import Env (PrlgEnv) | ||||||
| import Heap | import Heap | ||||||
| import IR (Id(..), StrTable(..)) | import IR (Id(..), StrTable(..)) | ||||||
| import Lens.Family2 | import Lens.Micro | ||||||
| import Lens.Family2.State | import Lens.Micro.Mtl | ||||||
| 
 | 
 | ||||||
| prove :: Code -> PrlgEnv (Either String Bool) | prove :: Code -> PrlgEnv (Either String Bool) | ||||||
| prove g = do | prove g = do | ||||||
|  | @ -140,7 +140,7 @@ cutGoal = doCut >> advance | ||||||
| 
 | 
 | ||||||
| openGoal :: IR.Id -> InterpFn | openGoal :: IR.Id -> InterpFn | ||||||
| openGoal fn = do | openGoal fn = do | ||||||
|   def <- defs `uses` (M.!? fn) |   def <- (M.!? fn) <$> use defs | ||||||
|   case def of |   case def of | ||||||
|     Just hs@(_:_) -> do |     Just hs@(_:_) -> do | ||||||
|       advance |       advance | ||||||
|  | @ -293,7 +293,7 @@ unify _ _ = backtrack | ||||||
| {- unification reference-handling tools -} | {- unification reference-handling tools -} | ||||||
| findLocalRef :: Lens' Cho (M.Map Int Int) -> Int -> PrlgEnv Int | findLocalRef :: Lens' Cho (M.Map Int Int) -> Int -> PrlgEnv Int | ||||||
| findLocalRef store lr = do | findLocalRef store lr = do | ||||||
|   a' <- (cur . store) `uses` (M.!? lr) |   a' <- (M.!? lr) <$> use (cur . store) | ||||||
|   case a' of |   case a' of | ||||||
|     Nothing -> do |     Nothing -> do | ||||||
|       a <- newHeapVar |       a <- newHeapVar | ||||||
|  |  | ||||||
|  | @ -8,7 +8,7 @@ import Control.Monad.Trans.Except (ExceptT, except) | ||||||
| import qualified Data.Map as M | import qualified Data.Map as M | ||||||
| import Env (findAtom, findStruct, withStrTable) | import Env (findAtom, findStruct, withStrTable) | ||||||
| import qualified IR | import qualified IR | ||||||
| import Lens.Family2.State | import Lens.Micro.Mtl | ||||||
| import qualified Parser as P | import qualified Parser as P | ||||||
| import qualified Text.Megaparsec as MP | import qualified Text.Megaparsec as MP | ||||||
| 
 | 
 | ||||||
|  | @ -53,7 +53,7 @@ expansion noexpand expander output x = do | ||||||
|   es <- findStruct expander 2 |   es <- findStruct expander 2 | ||||||
|   o <- findAtom output |   o <- findAtom output | ||||||
|   comma <- findAtom "," |   comma <- findAtom "," | ||||||
|   expand <- defs `uses` M.member es |   expand <- M.member es <$> use defs | ||||||
|   pure $ |   pure $ | ||||||
|     if expand |     if expand | ||||||
|       then IR.CallI |       then IR.CallI | ||||||
|  |  | ||||||
|  | @ -49,7 +49,7 @@ singleToks = ",;|()[]{}!" | ||||||
| 
 | 
 | ||||||
| identParts = "_" | identParts = "_" | ||||||
| 
 | 
 | ||||||
| notOpToks = "\'%" ++ identParts | notOpToks = "\'" ++ identParts | ||||||
| 
 | 
 | ||||||
| isOperatorlike x = | isOperatorlike x = | ||||||
|   (isSymbol x || isPunctuation x) && not (x `elem` singleToks ++ notOpToks) |   (isSymbol x || isPunctuation x) && not (x `elem` singleToks ++ notOpToks) | ||||||
|  | @ -162,20 +162,32 @@ free = (<* ws) -- we eat blanks _after_ the token. | ||||||
| 
 | 
 | ||||||
| isNormalTokStr = (`notElem` [".", "[", "]", "(", "|", ")", "{", "}"]) | isNormalTokStr = (`notElem` [".", "[", "]", "(", "|", ")", "{", "}"]) | ||||||
| 
 | 
 | ||||||
|  | isNormalTok :: Lexeme -> Bool | ||||||
| isNormalTok (Tok x) = isNormalTokStr x | isNormalTok (Tok x) = isNormalTokStr x | ||||||
| isNormalTok (QTok x _) = isNormalTokStr x | isNormalTok (QTok _ _) = True | ||||||
| isNormalTok _ = False | isNormalTok _ = False | ||||||
| 
 | 
 | ||||||
|  | isCallTok :: Lexeme -> Bool | ||||||
|  | isCallTok (Tok x) = | ||||||
|  |   all (\c -> not (isSymbol c) && not (isPunctuation c) || c `elem` identParts) x | ||||||
|  | isCallTok _ = True | ||||||
|  | 
 | ||||||
| unTok (Tok t) = t | unTok (Tok t) = t | ||||||
| unTok (QTok t _) = t | unTok (QTok t _) = t | ||||||
| 
 | 
 | ||||||
| literal :: Parser PAST | literal :: Parser PAST | ||||||
| literal = Literal . unTok <$> free (satisfy isNormalTok <* notFollowedBy lParen) | literal = | ||||||
|  |   Literal . unTok <$> | ||||||
|  |   free | ||||||
|  |     (choice | ||||||
|  |        [ satisfy isCallTok <* notFollowedBy (choice [lParen, lBrace]) | ||||||
|  |        , satisfy (\x -> not (isCallTok x) && isNormalTok x) | ||||||
|  |        ]) | ||||||
| 
 | 
 | ||||||
| makeParams (Seq inner) = splitOn [Literal ","] inner | makeParams (Seq inner) = splitOn [Literal ","] inner | ||||||
| 
 | 
 | ||||||
| call eb contents fmod = do | call eb contents fmod = do | ||||||
|   fn <- fmod . unTok <$> satisfy isNormalTok -- not free |   fn <- fmod . unTok <$> satisfy isCallTok -- not free | ||||||
|   (Call fn [] <$ try eb) <|> (Call fn . makeParams <$> free contents) |   (Call fn [] <$ try eb) <|> (Call fn . makeParams <$> free contents) | ||||||
| 
 | 
 | ||||||
| parens = Seq <$> (free lParen *> some seqItem <* free rParen) | parens = Seq <$> (free lParen *> some seqItem <* free rParen) | ||||||
|  |  | ||||||
|  | @ -29,7 +29,7 @@ executable prlg | ||||||
| 
 | 
 | ||||||
|     -- LANGUAGE extensions used by modules in this package. |     -- LANGUAGE extensions used by modules in this package. | ||||||
|     -- other-extensions: |     -- other-extensions: | ||||||
|     build-depends:    base >=4.14, containers, megaparsec, haskeline, split, transformers, lens-family, lens-family-th |     build-depends:    base >=4.14, containers, megaparsec, haskeline, split, transformers, microlens, microlens-th, microlens-mtl | ||||||
|     hs-source-dirs:   app |     hs-source-dirs:   app | ||||||
|     default-language: Haskell2010 |     default-language: Haskell2010 | ||||||
|     ghc-options:      -Wunused-imports |     ghc-options:      -Wunused-imports | ||||||
|  |  | ||||||
		Loading…
	
		Reference in a new issue