1
1
mirror of https://github.com/github/semantic.git synced 2024-12-26 00:12:29 +03:00

Merge pull request #36 from github/if-any-monad-is-not-freer-then-I-too-am-bound

Copy Freer in to Assignment, 🔥 dependency on freer-cofreer
This commit is contained in:
Patrick Thomson 2019-06-03 14:41:52 -04:00 committed by GitHub
commit ac8bd4409c
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 54 additions and 27 deletions

3
.gitmodules vendored
View File

@ -4,9 +4,6 @@
[submodule "vendor/haskell-tree-sitter"] [submodule "vendor/haskell-tree-sitter"]
path = vendor/haskell-tree-sitter path = vendor/haskell-tree-sitter
url = https://github.com/tree-sitter/haskell-tree-sitter.git url = https://github.com/tree-sitter/haskell-tree-sitter.git
[submodule "vendor/freer-cofreer"]
path = vendor/freer-cofreer
url = https://github.com/robrix/freer-cofreer.git
[submodule "vendor/proto3-suite"] [submodule "vendor/proto3-suite"]
path = vendor/proto3-suite path = vendor/proto3-suite
url = https://github.com/joshvera/proto3-suite.git url = https://github.com/joshvera/proto3-suite.git

View File

@ -290,7 +290,6 @@ library
, cryptohash ^>= 0.11.9 , cryptohash ^>= 0.11.9
, deepseq ^>= 1.4.4.0 , deepseq ^>= 1.4.4.0
, directory-tree ^>= 0.12.1 , directory-tree ^>= 0.12.1
, freer-cofreer
, generic-monoid ^>= 0.1.0.0 , generic-monoid ^>= 0.1.0.0
, ghc-prim ^>= 0.5.3 , ghc-prim ^>= 0.5.3
, gitrev ^>= 1.3.1 , gitrev ^>= 1.3.1

View File

@ -98,7 +98,6 @@ import Prologue
import Prelude hiding (fail) import Prelude hiding (fail)
import qualified Assigning.Assignment.Table as Table import qualified Assigning.Assignment.Table as Table
import Control.Monad.Except (MonadError (..)) import Control.Monad.Except (MonadError (..))
import Control.Monad.Free.Freer
import Data.AST import Data.AST
import Data.Error import Data.Error
import Data.Range import Data.Range
@ -200,7 +199,7 @@ choice :: (Enum grammar, Eq1 ast, Ix grammar, HasCallStack) => [Assignment ast g
choice [] = empty choice [] = empty
choice alternatives choice alternatives
| null choices = asum alternatives | null choices = asum alternatives
| otherwise = tracing (Choose (Table.fromListWith (<|>) choices) (wrap . tracing . Alt . toList <$> nonEmpty atEnd) (mergeHandlers handlers)) `Then` pure | otherwise = tracing (Choose (Table.fromListWith (<|>) choices) ((`Then` id) . tracing . Alt . toList <$> nonEmpty atEnd) (mergeHandlers handlers)) `Then` pure
where (choices, atEnd, handlers) = foldMap toChoices alternatives where (choices, atEnd, handlers) = foldMap toChoices alternatives
toChoices :: (Enum grammar, Ix grammar) => Assignment ast grammar a -> ([(grammar, Assignment ast grammar a)], [Assignment ast grammar a], [Error (Either String grammar) -> Assignment ast grammar a]) toChoices :: (Enum grammar, Ix grammar) => Assignment ast grammar a -> ([(grammar, Assignment ast grammar a)], [Assignment ast grammar a], [Error (Either String grammar) -> Assignment ast grammar a])
toChoices rule = case rule of toChoices rule = case rule of
@ -356,7 +355,7 @@ instance MonadFail (Assignment ast grammar) where
fail :: HasCallStack => String -> Assignment ast grammar a fail :: HasCallStack => String -> Assignment ast grammar a
fail s = tracing (Fail s) `Then` pure fail s = tracing (Fail s) `Then` pure
instance (Enum grammar, Eq1 ast, Ix grammar, Show grammar, Show1 ast) => Parsing (Assignment ast grammar) where instance (Enum grammar, Eq1 ast, Ix grammar, Show grammar) => Parsing (Assignment ast grammar) where
try = id try = id
(<?>) :: HasCallStack => Assignment ast grammar a -> String -> Assignment ast grammar a (<?>) :: HasCallStack => Assignment ast grammar a -> String -> Assignment ast grammar a
@ -369,7 +368,7 @@ instance (Enum grammar, Eq1 ast, Ix grammar, Show grammar, Show1 ast) => Parsing
eof = tracing End `Then` pure eof = tracing End `Then` pure
notFollowedBy :: (HasCallStack, Show a) => Assignment ast grammar a -> Assignment ast grammar () notFollowedBy :: (HasCallStack, Show a) => Assignment ast grammar a -> Assignment ast grammar ()
notFollowedBy a = a *> unexpected (show a) <|> pure () notFollowedBy a = (a >>= unexpected . show) <|> pure ()
instance (Enum grammar, Eq1 ast, Ix grammar, Show grammar) => MonadError (Error (Either String grammar)) (Assignment ast grammar) where instance (Enum grammar, Eq1 ast, Ix grammar, Show grammar) => MonadError (Error (Either String grammar)) (Assignment ast grammar) where
throwError :: HasCallStack => Error (Either String grammar) -> Assignment ast grammar a throwError :: HasCallStack => Error (Either String grammar) -> Assignment ast grammar a
@ -381,22 +380,55 @@ instance (Enum grammar, Eq1 ast, Ix grammar, Show grammar) => MonadError (Error
Choose choices atEnd (Just onError) -> Tracing cs (Choose (fmap (>>= continue) choices) (fmap (>>= continue) atEnd) (Just (\ err -> (onError err >>= continue) <|> handler err))) `Then` pure Choose choices atEnd (Just onError) -> Tracing cs (Choose (fmap (>>= continue) choices) (fmap (>>= continue) atEnd) (Just (\ err -> (onError err >>= continue) <|> handler err))) `Then` pure
_ -> Tracing cs assignment `Then` ((`catchError` handler) . continue)) (fmap pure rule) _ -> Tracing cs assignment `Then` ((`catchError` handler) . continue)) (fmap pure rule)
instance Show1 f => Show1 (Tracing f) where
liftShowsPrec sp sl d = liftShowsPrec sp sl d . runTracing
instance (Enum grammar, Ix grammar, Show grammar, Show1 ast) => Show1 (AssignmentF ast grammar) where -- Freer
liftShowsPrec sp sl d a = case a of
End -> showString "End" . showChar ' ' . sp d () data Freer f a where
Location -> showString "Location" . sp d (L.Location (Range 0 0) (Span (Pos 1 1) (Pos 1 1))) Return :: a -> Freer f a
CurrentNode -> showString "CurrentNode" Then :: f x -> (x -> Freer f a) -> Freer f a
Source -> showString "Source" . showChar ' ' . sp d ""
Children a -> showsUnaryWith showChild "Children" d a infixl 1 `Then`
Choose choices atEnd _ -> showsBinaryWith (liftShowsPrec showChild showChildren) (liftShowsPrec showChild showChildren) "Choose" d choices atEnd
Many a -> showsUnaryWith (liftShowsPrec (\ d a -> sp d [a]) (sl . pure)) "Many" d a instance Functor (Freer f) where
Alt as -> showsUnaryWith (const sl) "Alt" d (toList as) fmap f = go
Label child string -> showsBinaryWith (liftShowsPrec sp sl) showsPrec "Label" d child string where go (Return result) = Return (f result)
Fail s -> showsUnaryWith showsPrec "Fail" d s go (Then step yield) = Then step (go . yield)
GetLocals -> showString "GetLocals" {-# INLINE go #-}
PutLocals locals -> showsUnaryWith showsPrec "PutLocals" d locals {-# INLINE fmap #-}
where showChild = liftShowsPrec sp sl
showChildren = liftShowList sp sl instance Applicative (Freer f) where
pure = Return
{-# INLINE pure #-}
Return f <*> param = fmap f param
Then action yield <*> param = Then action ((<*> param) . yield)
{-# INLINE (<*>) #-}
Return _ *> a = a
Then r f *> a = Then r ((*> a) . f)
{-# INLINE (*>) #-}
Return a <* b = b *> Return a
Then r f <* a = Then r ((<* a) . f)
{-# INLINE (<*) #-}
instance Monad (Freer f) where
return = pure
{-# INLINE return #-}
Return a >>= f = f a
Then r f >>= g = Then r (g <=< f)
{-# INLINE (>>=) #-}
(>>) = (*>)
{-# INLINE (>>) #-}
-- | Tear down a 'Freer' 'Monad' using iteration with an explicit continuation.
--
-- This is analogous to 'iter' with a continuation for the interior values, and is therefore suitable for defining interpreters for GADTs/types lacking a 'Functor' instance.
iterFreer :: (forall x. (x -> a) -> f x -> a) -> Freer f a -> a
iterFreer algebra = go
where go (Return result) = result
go (Then action continue) = algebra (go . continue) action
{-# INLINE go #-}
{-# INLINE iterFreer #-}

@ -1 +0,0 @@
Subproject commit 6d94484a08f970877c4e34c9ecd9c219a7e476b5