Skip to content

Commit

Permalink
Merge trunk back into inline-foreign-calls
Browse files Browse the repository at this point in the history
  • Loading branch information
ChrisPenner committed Dec 9, 2024
2 parents fe3a9e8 + d3c9c69 commit 6b63eb1
Show file tree
Hide file tree
Showing 12 changed files with 2,281 additions and 1,540 deletions.
2 changes: 1 addition & 1 deletion unison-cli/src/Unison/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -238,7 +238,7 @@ main version = do
Right (Right (v, rf, combIx, sto))
| not vmatch -> mismatchMsg
| otherwise ->
withArgs args (RTI.runStandalone sto combIx) >>= \case
withArgs args (RTI.runStandalone False sto combIx) >>= \case
Left err -> exitError err
Right () -> pure ()
where
Expand Down
11 changes: 4 additions & 7 deletions unison-runtime/src/Unison/Runtime/ANF.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,6 @@ module Unison.Runtime.ANF
SuperGroup (..),
arities,
POp (..),
FOp,
close,
saturate,
float,
Expand Down Expand Up @@ -117,6 +116,7 @@ import Unison.Prelude
import Unison.Reference (Id, Reference, Reference' (Builtin, DerivedId))
import Unison.Referent (Referent, pattern Con, pattern Ref)
import Unison.Runtime.Array qualified as PA
import Unison.Runtime.Foreign.Function.Type (ForeignFunc (..))
import Unison.Runtime.TypeTags (CTag (..), PackedTag (..), RTag (..), Tag (..), maskTags, packTags, unpackTags)
import Unison.Symbol (Symbol)
import Unison.Term hiding (List, Ref, Text, arity, float, fresh, resolve)
Expand Down Expand Up @@ -1030,12 +1030,12 @@ pattern TPrm ::
ABTN.Term ANormalF v
pattern TPrm p args = TApp (FPrim (Left p)) args

pattern AFOp :: FOp -> [v] -> ANormalF v e
pattern AFOp :: ForeignFunc -> [v] -> ANormalF v e
pattern AFOp p args = AApp (FPrim (Right p)) args

pattern TFOp ::
(ABT.Var v) =>
FOp ->
ForeignFunc ->
[v] ->
ABTN.Term ANormalF v
pattern TFOp p args = TApp (FPrim (Right p)) args
Expand Down Expand Up @@ -1232,9 +1232,6 @@ instance Semigroup (BranchAccum v) where
instance Monoid (BranchAccum e) where
mempty = AccumEmpty

-- Foreign operation, indexed by words
type FOp = Word64

data Func v
= -- variable
FVar v
Expand All @@ -1247,7 +1244,7 @@ data Func v
| -- ability request
FReq !Reference !CTag
| -- prim op
FPrim (Either POp FOp)
FPrim (Either POp ForeignFunc)
deriving (Show, Eq, Functor, Foldable, Traversable)

data Lit
Expand Down
22 changes: 11 additions & 11 deletions unison-runtime/src/Unison/Runtime/ANF/Serialize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@ import Unison.ABT.Normalized (Term (..))
import Unison.Reference (Reference, Reference' (Builtin), pattern Derived)
import Unison.Runtime.ANF as ANF hiding (Tag)
import Unison.Runtime.Exception
import Unison.Runtime.Foreign.Function.Type (ForeignFunc)
import Unison.Runtime.Serialize
import Unison.Util.EnumContainers qualified as EC
import Unison.Util.Text qualified as Util.Text
import Unison.Var (Type (ANFBlank), Var (..))
import Prelude hiding (getChar, putChar)
Expand Down Expand Up @@ -317,7 +317,7 @@ putGroup ::
(MonadPut m) =>
(Var v) =>
Map Reference Word64 ->
EC.EnumMap FOp Text ->
Map ForeignFunc Text ->
SuperGroup v ->
m ()
putGroup refrep fops (Rec bs e) =
Expand All @@ -338,7 +338,7 @@ getGroup = do
cs <- replicateM l (getComb ctx n)
Rec (zip vs cs) <$> getComb ctx n

putCode :: (MonadPut m) => EC.EnumMap FOp Text -> Code -> m ()
putCode :: (MonadPut m) => Map ForeignFunc Text -> Code -> m ()
putCode fops (CodeRep g c) = putGroup mempty fops g *> putCacheability c

getCode :: (MonadGet m) => Word32 -> m Code
Expand All @@ -363,7 +363,7 @@ putComb ::
(MonadPut m) =>
(Var v) =>
Map Reference Word64 ->
EC.EnumMap FOp Text ->
Map ForeignFunc Text ->
[v] ->
SuperNormal v ->
m ()
Expand All @@ -384,7 +384,7 @@ putNormal ::
(MonadPut m) =>
(Var v) =>
Map Reference Word64 ->
EC.EnumMap FOp Text ->
Map ForeignFunc Text ->
[v] ->
ANormal v ->
m ()
Expand Down Expand Up @@ -482,7 +482,7 @@ putFunc ::
(MonadPut m) =>
(Var v) =>
Map Reference Word64 ->
EC.EnumMap FOp Text ->
Map ForeignFunc Text ->
[v] ->
Func v ->
m ()
Expand All @@ -496,7 +496,7 @@ putFunc refrep fops ctx f = case f of
FReq r c -> putTag FReqT *> putReference r *> putCTag c
FPrim (Left p) -> putTag FPrimT *> putPOp p
FPrim (Right f)
| Just nm <- EC.lookup f fops ->
| Just nm <- Map.lookup f fops ->
putTag FForeignT *> putText nm
| otherwise ->
exn $ "putFunc: could not serialize foreign operation: " ++ show f
Expand Down Expand Up @@ -757,7 +757,7 @@ putBranches ::
(MonadPut m) =>
(Var v) =>
Map Reference Word64 ->
EC.EnumMap FOp Text ->
Map ForeignFunc Text ->
[v] ->
Branched (ANormal v) ->
m ()
Expand Down Expand Up @@ -825,7 +825,7 @@ putCase ::
(MonadPut m) =>
(Var v) =>
Map Reference Word64 ->
EC.EnumMap FOp Text ->
Map ForeignFunc Text ->
[v] ->
([Mem], ANormal v) ->
m ()
Expand Down Expand Up @@ -997,7 +997,7 @@ deserializeCode bs = runGetS (getVersion >>= getCode) bs
n | 1 <= n && n <= 3 -> pure n
n -> fail $ "deserializeGroup: unknown version: " ++ show n

serializeCode :: EC.EnumMap FOp Text -> Code -> ByteString
serializeCode :: Map ForeignFunc Text -> Code -> ByteString
serializeCode fops co = runPutS (putVersion *> putCode fops co)
where
putVersion = putWord32be codeVersion
Expand All @@ -1023,7 +1023,7 @@ serializeCode fops co = runPutS (putVersion *> putCode fops co)
-- shouldn't be subject to rehashing.
serializeGroupForRehash ::
(Var v) =>
EC.EnumMap FOp Text ->
Map ForeignFunc Text ->
Reference ->
SuperGroup v ->
L.ByteString
Expand Down
Loading

0 comments on commit 6b63eb1

Please sign in to comment.