Tweaked node API

This commit is contained in:
Paul Chiusano 2014-09-30 13:10:51 -04:00
parent 96d69995b0
commit 1291d1d232
4 changed files with 41 additions and 49 deletions

View File

@ -16,7 +16,6 @@ import Unison.Metadata as MD
import Unison.Metadata (Metadata, Query)
import Unison.Term as E
import Unison.Path as Path
import Unison.Path (Path)
import Unison.Term (Term)
import Unison.Type as T
import Unison.Type (Type)
@ -25,6 +24,7 @@ import Unison.Jsonify (Jsonify)
import Unison.Parser as P
import Unison.Parser (Parser)
import Unison.Var as V
type Path = Path.Path
type Host = String
@ -52,9 +52,9 @@ parseResponse p r = case r of
Http.Waiting -> Http.Waiting
Http.Failure code body -> Http.Failure code body
admissibleTypeOf : Signal Host -> Signal (Hash, Path.Path) -> Signal (Response Type)
admissibleTypeOf : Signal Host -> Signal (Term, Path.Path) -> Signal (Response Type)
admissibleTypeOf host params =
let body = J.tuple2 H.jsonify Path.jsonifyPath
let body = J.tuple2 E.jsonifyTerm Path.jsonifyPath
req host params = jsonGet body host "admissible-type-of" params
in parseResponse T.parseType <~ Http.send (lift2 req host params)
@ -87,18 +87,18 @@ dependents host params =
in parseResponse (P.set H.parse) <~ Http.send (lift2 req host params)
editTerm : Signal Host
-> Signal (Hash, Path.Path, Action)
-> Signal (Response (Hash, Term))
-> Signal (Path, Action, Term)
-> Signal (Response Term)
editTerm host params =
let body = J.tuple3 H.jsonify Path.jsonifyPath A.jsonify
let body = J.tuple3 Path.jsonifyPath A.jsonify E.jsonifyTerm
req host params = jsonGet body host "edit-term" params
parse = parseResponse (P.tuple2 H.parse E.parseTerm)
parse = parseResponse E.parseTerm
in parse <~ Http.send (lift2 req host params)
{-
editType : Signal Host
-> Signal (Hash, Path, Action)
-> Signal (Response (Hash, Term))
-> Signal (Path, Action, Type)
-> Signal (Response Type)
editTerm host params =
let body = J.tuple3 H.jsonify Path.jsonify A.jsonify
req host params = jsonGet body host "edit-type" params
@ -156,16 +156,17 @@ transitiveDependents host params =
req host params = jsonGet body host "transitive-dependents" params
in parseResponse (P.set H.parse) <~ Http.send (lift2 req host params)
typ : Signal Host -> Signal Hash -> Signal (Response Type)
typ host params =
let req host params = Http.get (host ++ "/type/" ++ J.render H.jsonify params)
in parseResponse T.parseType <~ Http.send (lift2 req host params)
types : Signal Host -> Signal [Hash] -> Signal (Response (M.Dict Hash Type))
types host params =
let body = J.array H.jsonify
req host params = jsonGet body host "types" params
in parseResponse (P.object T.parseType) <~ Http.send (lift2 req host params)
typeOf : Signal Host
-> Signal (Hash, Path.Path)
-> Signal (Term, Path)
-> Signal (Response Type)
typeOf host params =
let body = J.tuple2 H.jsonify Path.jsonifyPath
let body = J.tuple2 E.jsonifyTerm Path.jsonifyPath
req host params = jsonGet body host "type-of" params
parse = parseResponse T.parseType
in parse <~ Http.send (lift2 req host params)

View File

@ -11,7 +11,7 @@ import Unison.Note as N
data Node m k t e = Node {
-- | Obtain the type of the given subterm, assuming the path is valid
admissibleTypeOf :: k -> P.Path -> Noted m t,
admissibleTypeOf :: e -> P.Path -> Noted m t,
-- | Create a new term and provide its metadata
createTerm :: e -> MD.Metadata k -> Noted m k,
-- | Create a new type and provide its metadata
@ -21,9 +21,9 @@ data Node m k t e = Node {
-- | Lookup the set of terms/types depending directly on the given @k@, optionally limited to the given set
dependents :: Maybe (S.Set k) -> k -> Noted m (S.Set k),
-- | Modify the given subterm, which may fail
editTerm :: k -> P.Path -> A.Action e -> Noted m (k, e),
editTerm :: P.Path -> A.Action e -> e -> Noted m e,
-- | Modify the given type, which may fail
editType :: k -> P.Path -> A.Action t -> Noted m (k, t),
editType :: P.Path -> A.Action t -> t -> Noted m t,
-- | Access the metadata for the term and/or types identified by @k@
metadatas :: [k] -> Noted m (Map k (MD.Metadata k)),
-- | Search for a term, optionally constrained to be of the given type
@ -39,9 +39,9 @@ data Node m k t e = Node {
-- | Lookup the set of terms or types which depend on the given @k@, optionally limited to those that intersect the given set
transitiveDependents :: Maybe (S.Set k) -> k -> Noted m (S.Set k),
-- | Lookup the source of the type identified by @k@
typ :: k -> Noted m t,
types :: [k] -> Noted m (Map k t),
-- | Obtain the type of the given subterm, assuming the path is valid
typeOf :: k -> P.Path -> Noted m t,
typeOf :: e -> P.Path -> Noted m t,
-- | Obtain the type of a constructor argument of a type
typeOfConstructorArg :: k -> TP.Path -> Noted m t,
-- | Update the metadata associated with the given term or type

View File

@ -10,7 +10,6 @@ import qualified Unison.Type as Type
import Unison.Syntax.Hash as H
import qualified Unison.Syntax.Type as T
import qualified Unison.Syntax.Term as E
import qualified Unison.Edit.Term.Path as P
import qualified Unison.Edit.Term as TE
import Unison.Edit.Term.Eval as Eval
import Unison.Syntax.Type (Type)
@ -25,11 +24,8 @@ node eval store =
readTypeOf h = readMetadata store h >>=
\md -> readType store (MD.annotation md)
admissibleTypeOf h loc = case loc of
P.Path [] -> readTypeOf h
P.Path _ -> do
ctx <- readTerm store h
TE.admissibleTypeOf readTypeOf loc ctx
admissibleTypeOf e loc =
TE.admissibleTypeOf readTypeOf loc e
createTerm e md = do
t <- Type.synthesize readTypeOf e
@ -61,10 +57,8 @@ node eval store =
(S.toList hs)
pure $ S.fromList [x | (x,deps) <- hs', S.member h deps]
edit k path action = do
e <- readTerm store k
e' <- TE.interpret eval (readTerm store) typ path action e
pure $ (E.finalizeHash e', e')
edit path action e = do
TE.interpret eval (readTerm store) (readType store) path action e
editType = error "todo later"
@ -101,14 +95,11 @@ node eval store =
transitiveDependents = error "todo"
typ =
readType store
types hs =
M.fromList <$> sequence (map (\h -> (,) h <$> readType store h) hs)
typeOf h loc = case loc of
P.Path [] -> readTypeOf h
P.Path _ -> do
ctx <- readTerm store h
TE.typeOf readTypeOf loc ctx
typeOf ctx loc =
TE.typeOf readTypeOf loc ctx
typeOfConstructorArg = error "todo"
@ -127,7 +118,7 @@ node eval store =
terms
transitiveDependencies
transitiveDependents
typ
types
typeOf
typeOfConstructorArg
updateMetadata

View File

@ -61,14 +61,14 @@ server port node = S.scotty port $ do
(limit, h) <- S.jsonData
k <- runN $ N.dependents node limit h
S.json k
S.get "/edit-term" $ do -- this merely computes the new term and its hash, hence a GET!
(h, loc, a) <- S.jsonData
(k, e) <- runN $ N.editTerm node h loc a
S.json (k, e) -- we might follow this up with a 'create-term', which is a POST
S.get "/edit-term" $ do -- this merely computes the new term, hence a GET
(loc, a, e) <- S.jsonData
e <- runN $ N.editTerm node loc a e
S.json e -- we might follow this up with a 'create-term', which is a POST
S.get "/edit-type" $ do -- this merely computes the new type and its hash, hence a GET!
(h, loc, a) <- S.jsonData
(k, e) <- runN $ N.editType node h loc a
S.json (k, e)
(loc, a, t) <- S.jsonData
t <- runN $ N.editType node loc a t
S.json t
S.get "/metadatas" $ do
hs <- S.jsonData
md <- runN $ N.metadatas node hs
@ -93,10 +93,10 @@ server port node = S.scotty port $ do
(limit,h) <- S.jsonData
s <- runN $ N.transitiveDependents node limit h
S.json s
S.get "/type/:hash" $ do
h <- jsonParam "hash"
t <- runN $ N.typ node h
S.json t
S.get "/types" $ do
hs <- S.jsonData
ts <- runN $ N.types node hs
S.json ts
S.get "/type-of" $ do
(h,loc) <- S.jsonData
s <- runN $ N.typeOf node h loc