⅄ 21-12-01-db-open-fix → 21-11-30-unknown-schema-ver

This commit is contained in:
Mitchell Rosen 2021-12-02 10:45:16 -05:00
commit 6dd67e4e20
18 changed files with 565 additions and 464 deletions

View File

@ -102,7 +102,6 @@ import Control.Monad.Trans (MonadTrans (lift))
import Control.Monad.Trans.Maybe (MaybeT (MaybeT), runMaybeT)
import Control.Monad.Writer (MonadWriter, WriterT, runWriterT)
import qualified Control.Monad.Writer as Writer
import Data.Bifoldable (bifoldMap)
import Data.Bifunctor (Bifunctor (bimap))
import Data.Bitraversable (Bitraversable (bitraverse))
import Data.ByteString (ByteString)
@ -115,8 +114,7 @@ import Data.Functor.Identity (Identity)
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Map.Merge.Lazy as Map
import Data.Maybe (catMaybes, isJust)
import Data.Monoid (First (First, getFirst))
import Data.Maybe (isJust)
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Set (Set)
@ -524,21 +522,25 @@ saveTermComponent h terms = do
dependencies :: Set S.Reference =
let (tmRefs, tpRefs, tmLinks, tpLinks) = TermUtil.dependencies tm
tpRefs' = Foldable.toList $ C.Type.dependencies tp
getTermSRef :: S.Term.TermRef -> Maybe S.Reference
getTermSRef (C.ReferenceBuiltin t) = Just (C.ReferenceBuiltin (tIds Vector.! fromIntegral t))
getTermSRef (C.Reference.Derived (Just h) i) = Just (C.Reference.Derived (oIds Vector.! fromIntegral h) i)
getTermSRef _selfCycleRef@(C.Reference.Derived Nothing _) = Nothing
getTermSRef :: S.Term.TermRef -> S.Reference
getTermSRef = \case
C.ReferenceBuiltin t -> C.ReferenceBuiltin (tIds Vector.! fromIntegral t)
C.Reference.Derived Nothing i -> C.Reference.Derived oId i -- index self-references
C.Reference.Derived (Just h) i -> C.Reference.Derived (oIds Vector.! fromIntegral h) i
getTypeSRef :: S.Term.TypeRef -> S.Reference
getTypeSRef (C.ReferenceBuiltin t) = C.ReferenceBuiltin (tIds Vector.! fromIntegral t)
getTypeSRef (C.Reference.Derived h i) = C.Reference.Derived (oIds Vector.! fromIntegral h) i
getTypeSRef = \case
C.ReferenceBuiltin t -> C.ReferenceBuiltin (tIds Vector.! fromIntegral t)
C.Reference.Derived h i -> C.Reference.Derived (oIds Vector.! fromIntegral h) i
getSTypeLink = getTypeSRef
getSTermLink :: S.Term.TermLink -> Maybe S.Reference
getSTermLink = getFirst . bifoldMap (First . getTermSRef) (First . Just . getTypeSRef)
getSTermLink :: S.Term.TermLink -> S.Reference
getSTermLink = \case
C.Referent.Con ref _conId -> getTypeSRef ref
C.Referent.Ref ref -> getTermSRef ref
in Set.fromList $
catMaybes
(fmap getTermSRef tmRefs ++ fmap getSTermLink tmLinks)
++ fmap getTypeSRef (tpRefs ++ tpRefs')
++ fmap getSTypeLink tpLinks
map getTermSRef tmRefs
++ map getSTermLink tmLinks
++ map getTypeSRef (tpRefs ++ tpRefs')
++ map getSTypeLink tpLinks
in Set.map (,self) dependencies
traverse_ (uncurry Q.addToDependentsIndex) dependencies
@ -804,7 +806,7 @@ w2cTerm ids tm = do
-- ** Saving & loading type decls
saveDeclComponent :: EDB m => H.Hash -> [(C.Decl Symbol)] -> m Db.ObjectId
saveDeclComponent :: EDB m => H.Hash -> [C.Decl Symbol] -> m Db.ObjectId
saveDeclComponent h decls = do
when debug . traceM $ "Operations.saveDeclComponent " ++ show h
sDeclElements <- traverse (c2sDecl Q.saveText primaryHashToExistingObjectId) decls
@ -818,11 +820,12 @@ saveDeclComponent h decls = do
unlocalizeRefs ((LocalIds tIds oIds, decl), i) =
let self = C.Reference.Id oId i
dependencies :: Set S.Decl.TypeRef = C.Decl.dependencies decl
getSRef :: C.Reference.Reference' LocalTextId (Maybe LocalDefnId) -> Maybe S.Reference.Reference
getSRef (C.ReferenceBuiltin t) = Just (C.ReferenceBuiltin (tIds Vector.! fromIntegral t))
getSRef (C.Reference.Derived (Just h) i) = Just (C.Reference.Derived (oIds Vector.! fromIntegral h) i)
getSRef _selfCycleRef@(C.Reference.Derived Nothing _) = Nothing
in Set.mapMaybe (fmap (,self) . getSRef) dependencies
getSRef :: C.Reference.Reference' LocalTextId (Maybe LocalDefnId) -> S.Reference.Reference
getSRef = \case
C.ReferenceBuiltin t -> C.ReferenceBuiltin (tIds Vector.! fromIntegral t)
C.Reference.Derived Nothing i -> C.Reference.Derived oId i -- index self-references
C.Reference.Derived (Just h) i -> C.Reference.Derived (oIds Vector.! fromIntegral h) i
in Set.map ((,self) . getSRef) dependencies
traverse_ (uncurry Q.addToDependentsIndex) dependencies
pure oId

View File

@ -155,7 +155,8 @@ import Debug.Trace (trace, traceM)
import GHC.Stack (HasCallStack)
import Safe (headMay)
import U.Codebase.HashTags (BranchHash (..), CausalHash (..))
import U.Codebase.Reference (Reference')
import U.Codebase.Reference (Reference' (..))
import qualified U.Codebase.Reference as C.Reference
import U.Codebase.Sqlite.Connection (Connection)
import qualified U.Codebase.Sqlite.Connection as Connection
import U.Codebase.Sqlite.DbId
@ -646,31 +647,60 @@ addToDependentsIndex dependency dependent = execute sql (dependency :. dependent
ON CONFLICT DO NOTHING
|]
-- | Get non-self, user-defined dependents of a dependency.
getDependentsForDependency :: DB m => Reference.Reference -> m [Reference.Id]
getDependentsForDependency dependency = query sql dependency where sql = [here|
SELECT dependent_object_id, dependent_component_index
FROM dependents_index
WHERE dependency_builtin IS ?
AND dependency_object_id IS ?
AND dependency_component_index IS ?
|]
getDependentsForDependency dependency =
filter isNotSelfReference <$> query sql dependency
where
sql =
[here|
SELECT dependent_object_id, dependent_component_index
FROM dependents_index
WHERE dependency_builtin IS ?
AND dependency_object_id IS ?
AND dependency_component_index IS ?
|]
isNotSelfReference :: Reference.Id -> Bool
isNotSelfReference =
case dependency of
ReferenceBuiltin _ -> const True
ReferenceDerived (C.Reference.Id oid0 _pos0) -> \(C.Reference.Id oid1 _pos1) -> oid0 /= oid1
-- | Get non-self dependencies of a user-defined dependent.
getDependenciesForDependent :: DB m => Reference.Id -> m [Reference.Reference]
getDependenciesForDependent dependent = query sql dependent where sql = [here|
SELECT dependency_builtin, dependency_object_id, dependency_component_index
FROM dependents_index
WHERE dependent_object_id IS ?
AND dependent_component_index IS ?
|]
getDependenciesForDependent dependent@(C.Reference.Id oid0 _) =
filter isNotSelfReference <$> query sql dependent
where
sql = [here|
SELECT dependency_builtin, dependency_object_id, dependency_component_index
FROM dependents_index
WHERE dependent_object_id IS ?
AND dependent_component_index IS ?
|]
isNotSelfReference :: Reference.Reference -> Bool
isNotSelfReference = \case
ReferenceBuiltin _ -> True
ReferenceDerived (C.Reference.Id oid1 _) -> oid0 /= oid1
-- | Get non-self, user-defined dependencies of a user-defined dependent.
getDependencyIdsForDependent :: DB m => Reference.Id -> m [Reference.Id]
getDependencyIdsForDependent dependent = query sql dependent where sql = [here|
SELECT dependency_object_id, dependency_component_index
FROM dependents_index
WHERE dependency_builtin IS NULL
AND dependent_object_id = ?
AND dependen_component_index = ?
|]
getDependencyIdsForDependent dependent@(C.Reference.Id oid0 _) =
filter isNotSelfReference <$> query sql dependent
where
sql =
[here|
SELECT dependency_object_id, dependency_component_index
FROM dependents_index
WHERE dependency_builtin IS NULL
AND dependent_object_id = ?
AND dependen_component_index = ?
|]
isNotSelfReference :: Reference.Id -> Bool
isNotSelfReference (C.Reference.Id oid1 _) =
oid0 /= oid1
objectIdByBase32Prefix :: DB m => ObjectType -> Text -> m [ObjectId]
objectIdByBase32Prefix objType prefix = queryAtoms sql (objType, prefix <> "%") where sql = [here|

View File

@ -1,5 +1,6 @@
module Unison.Util.Set
( mapMaybe,
( difference1,
mapMaybe,
symmetricDifference,
Unison.Util.Set.traverse,
)
@ -9,6 +10,13 @@ import qualified Data.Maybe as Maybe
import Data.Set (Set)
import qualified Data.Set as Set
-- | Set difference, but return @Nothing@ if the difference is empty.
difference1 :: Ord a => Set a -> Set a -> Maybe (Set a)
difference1 xs ys =
if null zs then Nothing else Just zs
where
zs = Set.difference xs ys
symmetricDifference :: Ord a => Set a -> Set a -> Set a
symmetricDifference a b = (a `Set.difference` b) `Set.union` (b `Set.difference` a)

View File

@ -1,27 +1,55 @@
{- ORMOLU_DISABLE -} -- Remove this when the file is ready to be auto-formatted
module Main where
import Criterion.Main
import qualified Unison.Util.Relation as R
import System.Random
import Control.Monad
genRelations :: (Random a, Random b, Ord a, Ord b)
=> Int -> Int -> IO (R.Relation a b, R.Relation a b)
genRelations numDomain rangeValuesPerDomain = do
import Control.Monad
import qualified Data.Set as Set
import System.Random
import Test.Tasty.Bench
import Unison.Prelude
import Unison.Util.Relation (Relation)
import qualified Unison.Util.Relation as R
main :: IO ()
main =
defaultMain
[ env (genRelations @Char @Char 10000 20) \rs ->
bgroup
"Relation"
[ bench "difference" $ nf (uncurry R.difference) rs,
bench "intersection" $ nf (uncurry R.intersection) rs,
bench "union" $ nf (uncurry R.union) rs
],
env (genRelation @Char @Char 10000 2) \r ->
env (genSet @Char 100) \s ->
bgroup
"Relation"
[ bgroup
"subtractDom"
[ bench "old implementation" (nf (oldSubtractDom s) r),
bench "new implementation" (nf (R.subtractDom s) r)
]
]
]
oldSubtractDom :: (Ord a, Ord b) => Set a -> Relation a b -> Relation a b
oldSubtractDom s r =
R.fromList [(a, b) | (a, b) <- R.toList r, not (a `Set.member` s)]
genRelation :: (Ord a, Ord b, Random a, Random b) => Int -> Int -> IO (Relation a b)
genRelation numDomain rangeValuesPerDomain = do
let genPairs = do
k <- randomIO
vs <- replicateM rangeValuesPerDomain ((k,) <$> randomIO)
pure vs
r1 <- R.fromList . concat <$> (replicateM numDomain genPairs)
r2 <- R.fromList . concat <$> (replicateM numDomain genPairs)
pure (r1, r2)
R.fromList . concat <$> replicateM numDomain genPairs
main :: IO ()
main = defaultMain
[ env (genRelations @Char @Char 10000 20) $ \rs ->
bgroup "Relation"
[ bench "difference" $ nf (uncurry R.difference) rs
, bench "intersection" $ nf (uncurry R.intersection) rs
, bench "union" $ nf (uncurry R.union) rs
]
]
genRelations ::
(Random a, Random b, Ord a, Ord b) =>
Int ->
Int ->
IO (Relation a b, Relation a b)
genRelations numDomain rangeValuesPerDomain =
(,) <$> genRelation numDomain rangeValuesPerDomain <*> genRelation numDomain rangeValuesPerDomain
genSet :: (Ord a, Random a) => Int -> IO (Set a)
genSet n =
Set.fromList <$> replicateM n randomIO

View File

@ -20,10 +20,10 @@ benchmarks:
main: Main.hs
dependencies:
- base
- criterion
- containers
- unison-util-relation
- random
- tasty-bench
- unison-util-relation
dependencies:
- base

View File

@ -1,4 +1,3 @@
{- ORMOLU_DISABLE -} -- Remove this when the file is ready to be auto-formatted
module Unison.Util.Relation
( Relation,
@ -10,7 +9,6 @@ module Unison.Util.Relation
fromManyRan,
fromMap,
fromMultimap,
fromSet,
unsafeFromMultimaps,
@ -107,6 +105,7 @@ module Unison.Util.Relation
)
where
import Control.DeepSeq
import qualified Control.Monad as Monad
import Data.Function (on)
import qualified Data.List as List
@ -116,8 +115,8 @@ import qualified Data.Map.Internal as Map
import Data.Ord (comparing)
import qualified Data.Set as S
import Unison.Prelude hiding (empty, toList)
import qualified Unison.Util.Set as Set
import Prelude hiding (filter, map, null)
import Control.DeepSeq
-- |
-- This implementation avoids using @"Set (a,b)"@ because
@ -169,15 +168,8 @@ unsafeFromMultimaps domain range =
difference :: (Ord a, Ord b) => Relation a b -> Relation a b -> Relation a b
difference (Relation d1 r1) (Relation d2 r2) =
Relation
(Map.differenceWith setDifference1 d1 d2)
(Map.differenceWith setDifference1 r1 r2)
where
-- Set difference, but return Nothing if the difference is empty.
setDifference1 :: Ord a => Set a -> Set a -> Maybe (Set a)
setDifference1 xs ys =
if S.null zs then Nothing else Just zs
where
zs = S.difference xs ys
(Map.differenceWith Set.difference1 d1 d2)
(Map.differenceWith Set.difference1 r1 r2)
-- | Like 'difference', but returns @Nothing@ if the difference is empty.
difference1 :: (Ord a, Ord b) => Relation a b -> Relation a b -> Maybe (Relation a b)
@ -525,16 +517,28 @@ r |> t =
filtrar x = M.filterWithKey (\k _ -> k == x) rr
rr = range r -- just to memoize the value
-- | Restrict the range to not include these `b`s
-- | Restrict the range to not include these `b`s.
(||>) :: (Ord a, Ord b) => Relation a b -> Set b -> Relation a b
r ||> t = fromList [(a, b) | (a, b) <- toList r, not (b `S.member` t)]
Relation {domain, range} ||> t =
Relation
{ domain = Map.mapMaybe (`Set.difference1` t) domain,
range = range `Map.withoutKeys` t
}
-- | Named version of ('||>').
subtractRan :: (Ord a, Ord b) => Set b -> Relation a b -> Relation a b
subtractRan = flip (||>)
-- | Restrict the domain to not include these `a`
(<||), subtractDom :: (Ord a, Ord b) => Set a -> Relation a b -> Relation a b
s <|| r = fromList [(a, b) | (a, b) <- toList r, not (a `S.member` s)]
-- | Restrict the domain to not include these `a`s.
(<||) :: (Ord a, Ord b) => Set a -> Relation a b -> Relation a b
s <|| Relation {domain, range} =
Relation
{ domain = domain `Map.withoutKeys` s,
range = Map.mapMaybe (`Set.difference1` s) range
}
-- | Named version of ('<||').
subtractDom :: (Ord a, Ord b) => Set a -> Relation a b -> Relation a b
subtractDom = (<||)
-- Note:

View File

@ -108,10 +108,10 @@ benchmark relation
build-depends:
base
, containers
, criterion
, deepseq
, extra
, random
, tasty-bench
, unison-prelude
, unison-util-relation
default-language: Haskell2010

View File

@ -471,6 +471,9 @@ builtinsSrc =
, B "List.++" $ forall1 "a" (\a -> list a --> list a --> list a)
, B "List.size" $ forall1 "a" (\a -> list a --> nat)
, B "List.at" $ forall1 "a" (\a -> nat --> list a --> optionalt a)
, B "Socket.toText" $ socket --> text
, B "Handle.toText" $ handle --> text
, B "ThreadId.toText" $ threadId --> text
, B "Debug.watch" $ forall1 "a" (\a -> text --> a --> a)
, B "unsafe.coerceAbilities" $

View File

@ -13,13 +13,13 @@ module Unison.Codebase.SqliteCodebase
where
import qualified Control.Concurrent
import qualified Control.Exception
import Control.Monad.Except (ExceptT, MonadError (throwError), runExceptT, withExceptT)
import qualified Control.Monad.Except as Except
import qualified Control.Monad.Extra as Monad
import Control.Monad.Reader (ReaderT (runReaderT))
import Control.Monad.State (MonadState)
import qualified Control.Monad.State as State
import Control.Monad.Trans.Except (mapExceptT)
import Data.Bifunctor (Bifunctor (bimap), second)
import qualified Data.Char as Char
import qualified Data.Either.Combinators as Either
@ -38,7 +38,7 @@ import qualified U.Codebase.Reference as C.Reference
import qualified U.Codebase.Referent as C.Referent
import U.Codebase.Sqlite.Connection (Connection (Connection))
import qualified U.Codebase.Sqlite.Connection as Connection
import U.Codebase.Sqlite.DbId (SchemaVersion (SchemaVersion), ObjectId)
import U.Codebase.Sqlite.DbId (ObjectId, SchemaVersion (SchemaVersion))
import qualified U.Codebase.Sqlite.JournalMode as JournalMode
import qualified U.Codebase.Sqlite.ObjectType as OT
import U.Codebase.Sqlite.Operations (EDB)
@ -49,9 +49,7 @@ import qualified U.Codebase.Sync as Sync
import qualified U.Codebase.WatchKind as WK
import qualified U.Util.Cache as Cache
import qualified U.Util.Hash as H2
import qualified Unison.Hashing.V2.Convert as Hashing
import qualified U.Util.Monoid as Monoid
import qualified Unison.Util.Set as Set
import U.Util.Timing (time)
import qualified Unison.Builtin as Builtins
import Unison.Codebase (Codebase, CodebasePath)
@ -73,13 +71,14 @@ import qualified Unison.Codebase.SqliteCodebase.Conversions as Cv
import qualified Unison.Codebase.SqliteCodebase.GitError as GitError
import qualified Unison.Codebase.SqliteCodebase.SyncEphemeral as SyncEphemeral
import Unison.Codebase.SyncMode (SyncMode)
import Unison.Codebase.Type (PushGitBranchOpts(..))
import Unison.Codebase.Type (PushGitBranchOpts (..))
import qualified Unison.Codebase.Type as C
import Unison.ConstructorReference (GConstructorReference(..))
import Unison.ConstructorReference (GConstructorReference (..))
import qualified Unison.ConstructorType as CT
import Unison.DataDeclaration (Decl)
import qualified Unison.DataDeclaration as Decl
import Unison.Hash (Hash)
import qualified Unison.Hashing.V2.Convert as Hashing
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.Reference (Reference)
@ -93,13 +92,13 @@ import Unison.Term (Term)
import qualified Unison.Term as Term
import Unison.Type (Type)
import qualified Unison.Type as Type
import qualified Unison.Util.Set as Set
import qualified Unison.WatchKind as UF
import UnliftIO (catchIO, finally, MonadUnliftIO, throwIO)
import UnliftIO (MonadUnliftIO, catchIO, finally, throwIO)
import qualified UnliftIO
import UnliftIO.Directory (createDirectoryIfMissing, doesDirectoryExist, doesFileExist)
import UnliftIO.Exception (bracket, catch)
import UnliftIO.STM
import UnliftIO.Exception (bracket)
import Control.Monad.Trans.Except (mapExceptT)
debug, debugProcessBranches, debugCommitFailedTransaction :: Bool
debug = False
@ -174,17 +173,6 @@ initSchemaIfNotExist path = liftIO do
unlessM (doesFileExist $ path </> codebasePath) $
withConnection "initSchemaIfNotExist" path $ runReaderT Q.createSchema
-- checks if a db exists at `path` with the minimum schema
codebaseExists :: MonadIO m => CodebasePath -> m Bool
codebaseExists root = liftIO do
Monad.when debug $ traceM $ "codebaseExists " ++ root
Control.Exception.catch @Sqlite.SQLError
( sqliteCodebase "codebaseExists" root (const $ pure ()) >>= \case
Left _ -> pure False
Right _ -> pure True
)
(const $ pure False)
-- 1) buffer up the component
-- 2) in the event that the component is complete, then what?
-- * can write component provided all of its dependency components are complete.
@ -1021,43 +1009,51 @@ viewRemoteBranch' ::
ReadRemoteNamespace ->
((Branch m, CodebasePath) -> m r) ->
m (Either C.GitError r)
viewRemoteBranch' (repo, sbh, path) action = UnliftIO.try $ do
viewRemoteBranch' (repo, sbh, path) action = UnliftIO.try do
-- set up the cache dir
remotePath <- (UnliftIO.fromEitherM . runExceptT . withExceptT C.GitProtocolError . time "Git fetch" $ pullBranch repo)
codebaseExists remotePath >>= \case
-- If there's no initialized codebase at this repo; we pretend there's an empty one.
-- I'm thinking we should probably return an error value instead.
False -> action (Branch.empty, remotePath)
True -> do
result <- sqliteCodebase "viewRemoteBranch.gitCache" remotePath $ \codebase -> do
-- try to load the requested branch from it
branch <- time "Git fetch (sbh)" $ case sbh of
-- no sub-branch was specified, so use the root.
Nothing ->
(time "Get remote root branch" $ Codebase1.getRootBranch codebase) >>= \case
-- this NoRootBranch case should probably be an error too.
Left Codebase1.NoRootBranch -> pure Branch.empty
Left (Codebase1.CouldntLoadRootBranch h) ->
throwIO . C.GitCodebaseError $ GitError.CouldntLoadRootBranch repo h
Left (Codebase1.CouldntParseRootBranch s) ->
throwIO . C.GitSqliteCodebaseError $ GitError.GitCouldntParseRootBranchHash repo s
Right b -> pure b
-- load from a specific `ShortBranchHash`
Just sbh -> do
branchCompletions <- Codebase1.branchHashesByPrefix codebase sbh
case toList branchCompletions of
[] -> throwIO . C.GitCodebaseError $ GitError.NoRemoteNamespaceWithHash repo sbh
[h] ->
(Codebase1.getBranchForHash codebase h) >>= \case
Just b -> pure b
Nothing -> throwIO . C.GitCodebaseError $ GitError.NoRemoteNamespaceWithHash repo sbh
_ -> throwIO . C.GitCodebaseError $ GitError.RemoteNamespaceHashAmbiguous repo sbh branchCompletions
case Branch.getAt path branch of
Just b -> action (b, remotePath)
Nothing -> throwIO . C.GitCodebaseError $ GitError.CouldntFindRemoteBranch repo path
case result of
Left schemaVersion -> throwIO . C.GitSqliteCodebaseError $ GitError.UnrecognizedSchemaVersion repo remotePath schemaVersion
Right inner -> pure inner
remotePath <- UnliftIO.fromEitherM . runExceptT . withExceptT C.GitProtocolError . time "Git fetch" $ pullBranch repo
-- Tickle the database before calling into `sqliteCodebase`; this covers the case that the database file either
-- doesn't exist at all or isn't a SQLite database file, but does not cover the case that the database file itself is
-- somehow corrupt, or not even a Unison database.
--
-- FIXME it would probably make more sense to define some proper preconditions on `sqliteCodebase`, and perhaps update
-- its output type, which currently indicates the only way it can fail is with an `UnknownSchemaVersion` error.
(withConnection "codebase exists check" remotePath \_ -> pure ()) `catch` \sqlError ->
case Sqlite.sqlError sqlError of
Sqlite.ErrorCan'tOpen -> throwIO (C.GitSqliteCodebaseError (GitError.NoDatabaseFile repo remotePath))
-- Unexpected error from sqlite
_ -> throwIO sqlError
result <- sqliteCodebase "viewRemoteBranch.gitCache" remotePath \codebase -> do
-- try to load the requested branch from it
branch <- time "Git fetch (sbh)" $ case sbh of
-- no sub-branch was specified, so use the root.
Nothing ->
(time "Get remote root branch" $ Codebase1.getRootBranch codebase) >>= \case
-- this NoRootBranch case should probably be an error too.
Left Codebase1.NoRootBranch -> pure Branch.empty
Left (Codebase1.CouldntLoadRootBranch h) ->
throwIO . C.GitCodebaseError $ GitError.CouldntLoadRootBranch repo h
Left (Codebase1.CouldntParseRootBranch s) ->
throwIO . C.GitSqliteCodebaseError $ GitError.GitCouldntParseRootBranchHash repo s
Right b -> pure b
-- load from a specific `ShortBranchHash`
Just sbh -> do
branchCompletions <- Codebase1.branchHashesByPrefix codebase sbh
case toList branchCompletions of
[] -> throwIO . C.GitCodebaseError $ GitError.NoRemoteNamespaceWithHash repo sbh
[h] ->
(Codebase1.getBranchForHash codebase h) >>= \case
Just b -> pure b
Nothing -> throwIO . C.GitCodebaseError $ GitError.NoRemoteNamespaceWithHash repo sbh
_ -> throwIO . C.GitCodebaseError $ GitError.RemoteNamespaceHashAmbiguous repo sbh branchCompletions
case Branch.getAt path branch of
Just b -> action (b, remotePath)
Nothing -> throwIO . C.GitCodebaseError $ GitError.CouldntFindRemoteBranch repo path
case result of
Left schemaVersion -> throwIO . C.GitSqliteCodebaseError $ GitError.UnrecognizedSchemaVersion repo remotePath schemaVersion
Right inner -> pure inner
-- Push a branch to a repo. Optionally attempt to set the branch as the new root, which fails if the branch is not after
-- the existing root.

View File

@ -1,11 +1,11 @@
{- ORMOLU_DISABLE -} -- Remove this when the file is ready to be auto-formatted
module Unison.Codebase.SqliteCodebase.GitError where
import U.Codebase.Sqlite.DbId (SchemaVersion)
import Unison.Codebase.Editor.RemoteRepo (ReadRepo)
import Unison.CodebasePath (CodebasePath)
import U.Codebase.Sqlite.DbId (SchemaVersion)
data GitSqliteCodebaseError
= GitCouldntParseRootBranchHash ReadRepo String
| NoDatabaseFile ReadRepo CodebasePath
| UnrecognizedSchemaVersion ReadRepo CodebasePath SchemaVersion
deriving Show
deriving (Show)

View File

@ -22,6 +22,8 @@ import Control.Monad.State.Strict (State, modify, execState)
import qualified Control.Exception.Safe as Exception
import Control.Monad.Catch (MonadCatch)
import Control.DeepSeq (NFData)
import Control.Concurrent (ThreadId)
import System.IO (Handle)
import Unison.ABT.Normalized hiding (TTm)
import Unison.Reference
@ -1646,6 +1648,15 @@ declareForeigns = do
, port) ->
fst <$> SYS.bindSock (hostPreference mhst) port
declareForeign "Socket.toText" boxDirect
. mkForeign $ \(sock :: Socket) -> pure $ show sock
declareForeign "Handle.toText" boxDirect
. mkForeign $ \(hand :: Handle) -> pure $ show hand
declareForeign "ThreadId.toText" boxDirect
. mkForeign $ \(threadId :: ThreadId) -> pure $ show threadId
declareForeign "IO.socketPort.impl.v3" boxToEFNat
. mkForeignIOF $ \(handle :: Socket) -> do
n <- SYS.socketPort handle

View File

@ -50,7 +50,13 @@ import qualified Unison.Codebase.PushBehavior as PushBehavior
import qualified Unison.Codebase.Runtime as Runtime
import Unison.Codebase.ShortBranchHash (ShortBranchHash)
import qualified Unison.Codebase.ShortBranchHash as SBH
import Unison.Codebase.SqliteCodebase.GitError (GitSqliteCodebaseError (GitCouldntParseRootBranchHash, UnrecognizedSchemaVersion))
import Unison.Codebase.SqliteCodebase.GitError
( GitSqliteCodebaseError
( GitCouldntParseRootBranchHash,
NoDatabaseFile,
UnrecognizedSchemaVersion
),
)
import qualified Unison.Codebase.TermEdit as TermEdit
import Unison.Codebase.Type (GitError (GitCodebaseError, GitProtocolError, GitSqliteCodebaseError))
import qualified Unison.Codebase.TypeEdit as TypeEdit
@ -875,6 +881,12 @@ notifyUser dir o = case o of
TodoOutput names todo -> pure (todoOutput names todo)
GitError e -> pure $ case e of
GitSqliteCodebaseError e -> case e of
NoDatabaseFile repo localPath ->
P.wrap $
"I didn't find a codebase in the repository at"
<> prettyReadRepo repo
<> "in the cache directory at"
<> P.backticked' (P.string localPath) "."
UnrecognizedSchemaVersion repo localPath (SchemaVersion v) ->
P.wrap $
"I don't know how to interpret schema version " <> P.shown v

View File

@ -138,334 +138,337 @@ Let's try it!
115. Float.toRepresentation : Float -> Nat
116. Float.toText : Float -> Text
117. Float.truncate : Float -> Int
118. builtin type Int
119. Int.* : Int -> Int -> Int
120. Int.+ : Int -> Int -> Int
121. Int.- : Int -> Int -> Int
122. Int./ : Int -> Int -> Int
123. Int.and : Int -> Int -> Int
124. Int.complement : Int -> Int
125. Int.eq : Int -> Int -> Boolean
126. Int.fromRepresentation : Nat -> Int
127. Int.fromText : Text -> Optional Int
128. Int.gt : Int -> Int -> Boolean
129. Int.gteq : Int -> Int -> Boolean
130. Int.increment : Int -> Int
131. Int.isEven : Int -> Boolean
132. Int.isOdd : Int -> Boolean
133. Int.leadingZeros : Int -> Nat
134. Int.lt : Int -> Int -> Boolean
135. Int.lteq : Int -> Int -> Boolean
136. Int.mod : Int -> Int -> Int
137. Int.negate : Int -> Int
138. Int.or : Int -> Int -> Int
139. Int.popCount : Int -> Nat
140. Int.pow : Int -> Nat -> Int
141. Int.shiftLeft : Int -> Nat -> Int
142. Int.shiftRight : Int -> Nat -> Int
143. Int.signum : Int -> Int
144. Int.toFloat : Int -> Float
145. Int.toRepresentation : Int -> Nat
146. Int.toText : Int -> Text
147. Int.trailingZeros : Int -> Nat
148. Int.truncate0 : Int -> Nat
149. Int.xor : Int -> Int -> Int
150. unique type io2.BufferMode
151. io2.BufferMode.BlockBuffering : BufferMode
152. io2.BufferMode.LineBuffering : BufferMode
153. io2.BufferMode.NoBuffering : BufferMode
154. io2.BufferMode.SizedBlockBuffering : Nat -> BufferMode
155. unique type io2.Failure
156. io2.Failure.Failure : Type -> Text -> Any -> Failure
157. unique type io2.FileMode
158. io2.FileMode.Append : FileMode
159. io2.FileMode.Read : FileMode
160. io2.FileMode.ReadWrite : FileMode
161. io2.FileMode.Write : FileMode
162. builtin type io2.Handle
163. builtin type io2.IO
164. io2.IO.clientSocket.impl : Text
118. Handle.toText : Handle -> Text
119. builtin type Int
120. Int.* : Int -> Int -> Int
121. Int.+ : Int -> Int -> Int
122. Int.- : Int -> Int -> Int
123. Int./ : Int -> Int -> Int
124. Int.and : Int -> Int -> Int
125. Int.complement : Int -> Int
126. Int.eq : Int -> Int -> Boolean
127. Int.fromRepresentation : Nat -> Int
128. Int.fromText : Text -> Optional Int
129. Int.gt : Int -> Int -> Boolean
130. Int.gteq : Int -> Int -> Boolean
131. Int.increment : Int -> Int
132. Int.isEven : Int -> Boolean
133. Int.isOdd : Int -> Boolean
134. Int.leadingZeros : Int -> Nat
135. Int.lt : Int -> Int -> Boolean
136. Int.lteq : Int -> Int -> Boolean
137. Int.mod : Int -> Int -> Int
138. Int.negate : Int -> Int
139. Int.or : Int -> Int -> Int
140. Int.popCount : Int -> Nat
141. Int.pow : Int -> Nat -> Int
142. Int.shiftLeft : Int -> Nat -> Int
143. Int.shiftRight : Int -> Nat -> Int
144. Int.signum : Int -> Int
145. Int.toFloat : Int -> Float
146. Int.toRepresentation : Int -> Nat
147. Int.toText : Int -> Text
148. Int.trailingZeros : Int -> Nat
149. Int.truncate0 : Int -> Nat
150. Int.xor : Int -> Int -> Int
151. unique type io2.BufferMode
152. io2.BufferMode.BlockBuffering : BufferMode
153. io2.BufferMode.LineBuffering : BufferMode
154. io2.BufferMode.NoBuffering : BufferMode
155. io2.BufferMode.SizedBlockBuffering : Nat -> BufferMode
156. unique type io2.Failure
157. io2.Failure.Failure : Type -> Text -> Any -> Failure
158. unique type io2.FileMode
159. io2.FileMode.Append : FileMode
160. io2.FileMode.Read : FileMode
161. io2.FileMode.ReadWrite : FileMode
162. io2.FileMode.Write : FileMode
163. builtin type io2.Handle
164. builtin type io2.IO
165. io2.IO.clientSocket.impl : Text
-> Text
->{IO} Either Failure Socket
165. io2.IO.closeFile.impl : Handle ->{IO} Either Failure ()
166. io2.IO.closeSocket.impl : Socket ->{IO} Either Failure ()
167. io2.IO.createDirectory.impl : Text
166. io2.IO.closeFile.impl : Handle ->{IO} Either Failure ()
167. io2.IO.closeSocket.impl : Socket ->{IO} Either Failure ()
168. io2.IO.createDirectory.impl : Text
->{IO} Either Failure ()
168. io2.IO.createTempDirectory.impl : Text
169. io2.IO.createTempDirectory.impl : Text
->{IO} Either
Failure Text
169. io2.IO.delay.impl : Nat ->{IO} Either Failure ()
170. io2.IO.directoryContents.impl : Text
170. io2.IO.delay.impl : Nat ->{IO} Either Failure ()
171. io2.IO.directoryContents.impl : Text
->{IO} Either
Failure [Text]
171. io2.IO.fileExists.impl : Text
172. io2.IO.fileExists.impl : Text
->{IO} Either Failure Boolean
172. io2.IO.forkComp : '{IO} a ->{IO} ThreadId
173. io2.IO.getArgs.impl : '{IO} Either Failure [Text]
174. io2.IO.getBuffering.impl : Handle
173. io2.IO.forkComp : '{IO} a ->{IO} ThreadId
174. io2.IO.getArgs.impl : '{IO} Either Failure [Text]
175. io2.IO.getBuffering.impl : Handle
->{IO} Either
Failure BufferMode
175. io2.IO.getBytes.impl : Handle
176. io2.IO.getBytes.impl : Handle
-> Nat
->{IO} Either Failure Bytes
176. io2.IO.getCurrentDirectory.impl : '{IO} Either
177. io2.IO.getCurrentDirectory.impl : '{IO} Either
Failure Text
177. io2.IO.getEnv.impl : Text ->{IO} Either Failure Text
178. io2.IO.getFileSize.impl : Text ->{IO} Either Failure Nat
179. io2.IO.getFileTimestamp.impl : Text
178. io2.IO.getEnv.impl : Text ->{IO} Either Failure Text
179. io2.IO.getFileSize.impl : Text ->{IO} Either Failure Nat
180. io2.IO.getFileTimestamp.impl : Text
->{IO} Either Failure Nat
180. io2.IO.getLine.impl : Handle ->{IO} Either Failure Text
181. io2.IO.getTempDirectory.impl : '{IO} Either Failure Text
182. io2.IO.handlePosition.impl : Handle
181. io2.IO.getLine.impl : Handle ->{IO} Either Failure Text
182. io2.IO.getTempDirectory.impl : '{IO} Either Failure Text
183. io2.IO.handlePosition.impl : Handle
->{IO} Either Failure Nat
183. io2.IO.isDirectory.impl : Text
184. io2.IO.isDirectory.impl : Text
->{IO} Either Failure Boolean
184. io2.IO.isFileEOF.impl : Handle
185. io2.IO.isFileEOF.impl : Handle
->{IO} Either Failure Boolean
185. io2.IO.isFileOpen.impl : Handle
186. io2.IO.isFileOpen.impl : Handle
->{IO} Either Failure Boolean
186. io2.IO.isSeekable.impl : Handle
187. io2.IO.isSeekable.impl : Handle
->{IO} Either Failure Boolean
187. io2.IO.kill.impl : ThreadId ->{IO} Either Failure ()
188. io2.IO.listen.impl : Socket ->{IO} Either Failure ()
189. io2.IO.openFile.impl : Text
188. io2.IO.kill.impl : ThreadId ->{IO} Either Failure ()
189. io2.IO.listen.impl : Socket ->{IO} Either Failure ()
190. io2.IO.openFile.impl : Text
-> FileMode
->{IO} Either Failure Handle
190. io2.IO.putBytes.impl : Handle
191. io2.IO.putBytes.impl : Handle
-> Bytes
->{IO} Either Failure ()
191. io2.IO.ref : a ->{IO} Ref {IO} a
192. io2.IO.removeDirectory.impl : Text
192. io2.IO.ref : a ->{IO} Ref {IO} a
193. io2.IO.removeDirectory.impl : Text
->{IO} Either Failure ()
193. io2.IO.removeFile.impl : Text ->{IO} Either Failure ()
194. io2.IO.renameDirectory.impl : Text
194. io2.IO.removeFile.impl : Text ->{IO} Either Failure ()
195. io2.IO.renameDirectory.impl : Text
-> Text
->{IO} Either Failure ()
195. io2.IO.renameFile.impl : Text
196. io2.IO.renameFile.impl : Text
-> Text
->{IO} Either Failure ()
196. io2.IO.seekHandle.impl : Handle
197. io2.IO.seekHandle.impl : Handle
-> SeekMode
-> Int
->{IO} Either Failure ()
197. io2.IO.serverSocket.impl : Optional Text
198. io2.IO.serverSocket.impl : Optional Text
-> Text
->{IO} Either Failure Socket
198. io2.IO.setBuffering.impl : Handle
199. io2.IO.setBuffering.impl : Handle
-> BufferMode
->{IO} Either Failure ()
199. io2.IO.setCurrentDirectory.impl : Text
200. io2.IO.setCurrentDirectory.impl : Text
->{IO} Either
Failure ()
200. io2.IO.socketAccept.impl : Socket
201. io2.IO.socketAccept.impl : Socket
->{IO} Either Failure Socket
201. io2.IO.socketPort.impl : Socket ->{IO} Either Failure Nat
202. io2.IO.socketReceive.impl : Socket
202. io2.IO.socketPort.impl : Socket ->{IO} Either Failure Nat
203. io2.IO.socketReceive.impl : Socket
-> Nat
->{IO} Either Failure Bytes
203. io2.IO.socketSend.impl : Socket
204. io2.IO.socketSend.impl : Socket
-> Bytes
->{IO} Either Failure ()
204. io2.IO.stdHandle : StdHandle -> Handle
205. io2.IO.systemTime.impl : '{IO} Either Failure Nat
206. io2.IO.systemTimeMicroseconds : '{IO} Int
207. unique type io2.IOError
208. io2.IOError.AlreadyExists : IOError
209. io2.IOError.EOF : IOError
210. io2.IOError.IllegalOperation : IOError
211. io2.IOError.NoSuchThing : IOError
212. io2.IOError.PermissionDenied : IOError
213. io2.IOError.ResourceBusy : IOError
214. io2.IOError.ResourceExhausted : IOError
215. io2.IOError.UserError : IOError
216. unique type io2.IOFailure
217. builtin type io2.MVar
218. io2.MVar.isEmpty : MVar a ->{IO} Boolean
219. io2.MVar.new : a ->{IO} MVar a
220. io2.MVar.newEmpty : '{IO} MVar a
221. io2.MVar.put.impl : MVar a -> a ->{IO} Either Failure ()
222. io2.MVar.read.impl : MVar a ->{IO} Either Failure a
223. io2.MVar.swap.impl : MVar a -> a ->{IO} Either Failure a
224. io2.MVar.take.impl : MVar a ->{IO} Either Failure a
225. io2.MVar.tryPut.impl : MVar a
205. io2.IO.stdHandle : StdHandle -> Handle
206. io2.IO.systemTime.impl : '{IO} Either Failure Nat
207. io2.IO.systemTimeMicroseconds : '{IO} Int
208. unique type io2.IOError
209. io2.IOError.AlreadyExists : IOError
210. io2.IOError.EOF : IOError
211. io2.IOError.IllegalOperation : IOError
212. io2.IOError.NoSuchThing : IOError
213. io2.IOError.PermissionDenied : IOError
214. io2.IOError.ResourceBusy : IOError
215. io2.IOError.ResourceExhausted : IOError
216. io2.IOError.UserError : IOError
217. unique type io2.IOFailure
218. builtin type io2.MVar
219. io2.MVar.isEmpty : MVar a ->{IO} Boolean
220. io2.MVar.new : a ->{IO} MVar a
221. io2.MVar.newEmpty : '{IO} MVar a
222. io2.MVar.put.impl : MVar a -> a ->{IO} Either Failure ()
223. io2.MVar.read.impl : MVar a ->{IO} Either Failure a
224. io2.MVar.swap.impl : MVar a -> a ->{IO} Either Failure a
225. io2.MVar.take.impl : MVar a ->{IO} Either Failure a
226. io2.MVar.tryPut.impl : MVar a
-> a
->{IO} Either Failure Boolean
226. io2.MVar.tryRead.impl : MVar a
227. io2.MVar.tryRead.impl : MVar a
->{IO} Either
Failure (Optional a)
227. io2.MVar.tryTake : MVar a ->{IO} Optional a
228. unique type io2.SeekMode
229. io2.SeekMode.AbsoluteSeek : SeekMode
230. io2.SeekMode.RelativeSeek : SeekMode
231. io2.SeekMode.SeekFromEnd : SeekMode
232. builtin type io2.Socket
233. unique type io2.StdHandle
234. io2.StdHandle.StdErr : StdHandle
235. io2.StdHandle.StdIn : StdHandle
236. io2.StdHandle.StdOut : StdHandle
237. builtin type io2.STM
238. io2.STM.atomically : '{STM} a ->{IO} a
239. io2.STM.retry : '{STM} a
240. builtin type io2.ThreadId
241. builtin type io2.Tls
242. builtin type io2.Tls.Cipher
243. builtin type io2.Tls.ClientConfig
244. io2.Tls.ClientConfig.certificates.set : [SignedCert]
228. io2.MVar.tryTake : MVar a ->{IO} Optional a
229. unique type io2.SeekMode
230. io2.SeekMode.AbsoluteSeek : SeekMode
231. io2.SeekMode.RelativeSeek : SeekMode
232. io2.SeekMode.SeekFromEnd : SeekMode
233. builtin type io2.Socket
234. unique type io2.StdHandle
235. io2.StdHandle.StdErr : StdHandle
236. io2.StdHandle.StdIn : StdHandle
237. io2.StdHandle.StdOut : StdHandle
238. builtin type io2.STM
239. io2.STM.atomically : '{STM} a ->{IO} a
240. io2.STM.retry : '{STM} a
241. builtin type io2.ThreadId
242. builtin type io2.Tls
243. builtin type io2.Tls.Cipher
244. builtin type io2.Tls.ClientConfig
245. io2.Tls.ClientConfig.certificates.set : [SignedCert]
-> ClientConfig
-> ClientConfig
245. io2.TLS.ClientConfig.ciphers.set : [Cipher]
246. io2.TLS.ClientConfig.ciphers.set : [Cipher]
-> ClientConfig
-> ClientConfig
246. io2.Tls.ClientConfig.default : Text
247. io2.Tls.ClientConfig.default : Text
-> Bytes
-> ClientConfig
247. io2.Tls.ClientConfig.versions.set : [Version]
248. io2.Tls.ClientConfig.versions.set : [Version]
-> ClientConfig
-> ClientConfig
248. io2.Tls.decodeCert.impl : Bytes
249. io2.Tls.decodeCert.impl : Bytes
-> Either Failure SignedCert
249. io2.Tls.decodePrivateKey : Bytes -> [PrivateKey]
250. io2.Tls.encodeCert : SignedCert -> Bytes
251. io2.Tls.encodePrivateKey : PrivateKey -> Bytes
252. io2.Tls.handshake.impl : Tls ->{IO} Either Failure ()
253. io2.Tls.newClient.impl : ClientConfig
250. io2.Tls.decodePrivateKey : Bytes -> [PrivateKey]
251. io2.Tls.encodeCert : SignedCert -> Bytes
252. io2.Tls.encodePrivateKey : PrivateKey -> Bytes
253. io2.Tls.handshake.impl : Tls ->{IO} Either Failure ()
254. io2.Tls.newClient.impl : ClientConfig
-> Socket
->{IO} Either Failure Tls
254. io2.Tls.newServer.impl : ServerConfig
255. io2.Tls.newServer.impl : ServerConfig
-> Socket
->{IO} Either Failure Tls
255. builtin type io2.Tls.PrivateKey
256. io2.Tls.receive.impl : Tls ->{IO} Either Failure Bytes
257. io2.Tls.send.impl : Tls -> Bytes ->{IO} Either Failure ()
258. builtin type io2.Tls.ServerConfig
259. io2.Tls.ServerConfig.certificates.set : [SignedCert]
256. builtin type io2.Tls.PrivateKey
257. io2.Tls.receive.impl : Tls ->{IO} Either Failure Bytes
258. io2.Tls.send.impl : Tls -> Bytes ->{IO} Either Failure ()
259. builtin type io2.Tls.ServerConfig
260. io2.Tls.ServerConfig.certificates.set : [SignedCert]
-> ServerConfig
-> ServerConfig
260. io2.Tls.ServerConfig.ciphers.set : [Cipher]
261. io2.Tls.ServerConfig.ciphers.set : [Cipher]
-> ServerConfig
-> ServerConfig
261. io2.Tls.ServerConfig.default : [SignedCert]
262. io2.Tls.ServerConfig.default : [SignedCert]
-> PrivateKey
-> ServerConfig
262. io2.Tls.ServerConfig.versions.set : [Version]
263. io2.Tls.ServerConfig.versions.set : [Version]
-> ServerConfig
-> ServerConfig
263. builtin type io2.Tls.SignedCert
264. io2.Tls.terminate.impl : Tls ->{IO} Either Failure ()
265. builtin type io2.Tls.Version
266. unique type io2.TlsFailure
267. builtin type io2.TVar
268. io2.TVar.new : a ->{STM} TVar a
269. io2.TVar.newIO : a ->{IO} TVar a
270. io2.TVar.read : TVar a ->{STM} a
271. io2.TVar.readIO : TVar a ->{IO} a
272. io2.TVar.swap : TVar a -> a ->{STM} a
273. io2.TVar.write : TVar a -> a ->{STM} ()
274. unique type IsPropagated
275. IsPropagated.IsPropagated : IsPropagated
276. unique type IsTest
277. IsTest.IsTest : IsTest
278. unique type Link
279. builtin type Link.Term
280. Link.Term : Term -> Link
281. Link.Term.toText : Term -> Text
282. builtin type Link.Type
283. Link.Type : Type -> Link
284. builtin type List
285. List.++ : [a] -> [a] -> [a]
286. List.+: : a -> [a] -> [a]
287. List.:+ : [a] -> a -> [a]
288. List.at : Nat -> [a] -> Optional a
289. List.cons : a -> [a] -> [a]
290. List.drop : Nat -> [a] -> [a]
291. List.empty : [a]
292. List.size : [a] -> Nat
293. List.snoc : [a] -> a -> [a]
294. List.take : Nat -> [a] -> [a]
295. metadata.isPropagated : IsPropagated
296. metadata.isTest : IsTest
297. builtin type Nat
298. Nat.* : Nat -> Nat -> Nat
299. Nat.+ : Nat -> Nat -> Nat
300. Nat./ : Nat -> Nat -> Nat
301. Nat.and : Nat -> Nat -> Nat
302. Nat.complement : Nat -> Nat
303. Nat.drop : Nat -> Nat -> Nat
304. Nat.eq : Nat -> Nat -> Boolean
305. Nat.fromText : Text -> Optional Nat
306. Nat.gt : Nat -> Nat -> Boolean
307. Nat.gteq : Nat -> Nat -> Boolean
308. Nat.increment : Nat -> Nat
309. Nat.isEven : Nat -> Boolean
310. Nat.isOdd : Nat -> Boolean
311. Nat.leadingZeros : Nat -> Nat
312. Nat.lt : Nat -> Nat -> Boolean
313. Nat.lteq : Nat -> Nat -> Boolean
314. Nat.mod : Nat -> Nat -> Nat
315. Nat.or : Nat -> Nat -> Nat
316. Nat.popCount : Nat -> Nat
317. Nat.pow : Nat -> Nat -> Nat
318. Nat.shiftLeft : Nat -> Nat -> Nat
319. Nat.shiftRight : Nat -> Nat -> Nat
320. Nat.sub : Nat -> Nat -> Int
321. Nat.toFloat : Nat -> Float
322. Nat.toInt : Nat -> Int
323. Nat.toText : Nat -> Text
324. Nat.trailingZeros : Nat -> Nat
325. Nat.xor : Nat -> Nat -> Nat
326. structural type Optional a
327. Optional.None : Optional a
328. Optional.Some : a -> Optional a
329. builtin type Ref
330. Ref.read : Ref g a ->{g} a
331. Ref.write : Ref g a -> a ->{g} ()
332. builtin type Request
333. builtin type Scope
334. Scope.ref : a ->{Scope s} Ref {Scope s} a
335. Scope.run : (∀ s. '{g, Scope s} r) ->{g} r
336. structural type SeqView a b
337. SeqView.VElem : a -> b -> SeqView a b
338. SeqView.VEmpty : SeqView a b
339. unique type Test.Result
340. Test.Result.Fail : Text -> Result
341. Test.Result.Ok : Text -> Result
342. builtin type Text
343. Text.!= : Text -> Text -> Boolean
344. Text.++ : Text -> Text -> Text
345. Text.drop : Nat -> Text -> Text
346. Text.empty : Text
347. Text.eq : Text -> Text -> Boolean
348. Text.fromCharList : [Char] -> Text
349. Text.fromUtf8.impl : Bytes -> Either Failure Text
350. Text.gt : Text -> Text -> Boolean
351. Text.gteq : Text -> Text -> Boolean
352. Text.lt : Text -> Text -> Boolean
353. Text.lteq : Text -> Text -> Boolean
354. Text.repeat : Nat -> Text -> Text
355. Text.size : Text -> Nat
356. Text.take : Nat -> Text -> Text
357. Text.toCharList : Text -> [Char]
358. Text.toUtf8 : Text -> Bytes
359. Text.uncons : Text -> Optional (Char, Text)
360. Text.unsnoc : Text -> Optional (Text, Char)
361. todo : a -> b
362. structural type Tuple a b
363. Tuple.Cons : a -> b -> Tuple a b
364. structural type Unit
365. Unit.Unit : ()
366. Universal.< : a -> a -> Boolean
367. Universal.<= : a -> a -> Boolean
368. Universal.== : a -> a -> Boolean
369. Universal.> : a -> a -> Boolean
370. Universal.>= : a -> a -> Boolean
371. Universal.compare : a -> a -> Int
372. unsafe.coerceAbilities : (a ->{e1} b) -> a ->{e2} b
373. builtin type Value
374. Value.dependencies : Value -> [Term]
375. Value.deserialize : Bytes -> Either Text Value
376. Value.load : Value ->{IO} Either [Term] a
377. Value.serialize : Value -> Bytes
378. Value.value : a -> Value
264. builtin type io2.Tls.SignedCert
265. io2.Tls.terminate.impl : Tls ->{IO} Either Failure ()
266. builtin type io2.Tls.Version
267. unique type io2.TlsFailure
268. builtin type io2.TVar
269. io2.TVar.new : a ->{STM} TVar a
270. io2.TVar.newIO : a ->{IO} TVar a
271. io2.TVar.read : TVar a ->{STM} a
272. io2.TVar.readIO : TVar a ->{IO} a
273. io2.TVar.swap : TVar a -> a ->{STM} a
274. io2.TVar.write : TVar a -> a ->{STM} ()
275. unique type IsPropagated
276. IsPropagated.IsPropagated : IsPropagated
277. unique type IsTest
278. IsTest.IsTest : IsTest
279. unique type Link
280. builtin type Link.Term
281. Link.Term : Term -> Link
282. Link.Term.toText : Term -> Text
283. builtin type Link.Type
284. Link.Type : Type -> Link
285. builtin type List
286. List.++ : [a] -> [a] -> [a]
287. List.+: : a -> [a] -> [a]
288. List.:+ : [a] -> a -> [a]
289. List.at : Nat -> [a] -> Optional a
290. List.cons : a -> [a] -> [a]
291. List.drop : Nat -> [a] -> [a]
292. List.empty : [a]
293. List.size : [a] -> Nat
294. List.snoc : [a] -> a -> [a]
295. List.take : Nat -> [a] -> [a]
296. metadata.isPropagated : IsPropagated
297. metadata.isTest : IsTest
298. builtin type Nat
299. Nat.* : Nat -> Nat -> Nat
300. Nat.+ : Nat -> Nat -> Nat
301. Nat./ : Nat -> Nat -> Nat
302. Nat.and : Nat -> Nat -> Nat
303. Nat.complement : Nat -> Nat
304. Nat.drop : Nat -> Nat -> Nat
305. Nat.eq : Nat -> Nat -> Boolean
306. Nat.fromText : Text -> Optional Nat
307. Nat.gt : Nat -> Nat -> Boolean
308. Nat.gteq : Nat -> Nat -> Boolean
309. Nat.increment : Nat -> Nat
310. Nat.isEven : Nat -> Boolean
311. Nat.isOdd : Nat -> Boolean
312. Nat.leadingZeros : Nat -> Nat
313. Nat.lt : Nat -> Nat -> Boolean
314. Nat.lteq : Nat -> Nat -> Boolean
315. Nat.mod : Nat -> Nat -> Nat
316. Nat.or : Nat -> Nat -> Nat
317. Nat.popCount : Nat -> Nat
318. Nat.pow : Nat -> Nat -> Nat
319. Nat.shiftLeft : Nat -> Nat -> Nat
320. Nat.shiftRight : Nat -> Nat -> Nat
321. Nat.sub : Nat -> Nat -> Int
322. Nat.toFloat : Nat -> Float
323. Nat.toInt : Nat -> Int
324. Nat.toText : Nat -> Text
325. Nat.trailingZeros : Nat -> Nat
326. Nat.xor : Nat -> Nat -> Nat
327. structural type Optional a
328. Optional.None : Optional a
329. Optional.Some : a -> Optional a
330. builtin type Ref
331. Ref.read : Ref g a ->{g} a
332. Ref.write : Ref g a -> a ->{g} ()
333. builtin type Request
334. builtin type Scope
335. Scope.ref : a ->{Scope s} Ref {Scope s} a
336. Scope.run : (∀ s. '{g, Scope s} r) ->{g} r
337. structural type SeqView a b
338. SeqView.VElem : a -> b -> SeqView a b
339. SeqView.VEmpty : SeqView a b
340. Socket.toText : Socket -> Text
341. unique type Test.Result
342. Test.Result.Fail : Text -> Result
343. Test.Result.Ok : Text -> Result
344. builtin type Text
345. Text.!= : Text -> Text -> Boolean
346. Text.++ : Text -> Text -> Text
347. Text.drop : Nat -> Text -> Text
348. Text.empty : Text
349. Text.eq : Text -> Text -> Boolean
350. Text.fromCharList : [Char] -> Text
351. Text.fromUtf8.impl : Bytes -> Either Failure Text
352. Text.gt : Text -> Text -> Boolean
353. Text.gteq : Text -> Text -> Boolean
354. Text.lt : Text -> Text -> Boolean
355. Text.lteq : Text -> Text -> Boolean
356. Text.repeat : Nat -> Text -> Text
357. Text.size : Text -> Nat
358. Text.take : Nat -> Text -> Text
359. Text.toCharList : Text -> [Char]
360. Text.toUtf8 : Text -> Bytes
361. Text.uncons : Text -> Optional (Char, Text)
362. Text.unsnoc : Text -> Optional (Text, Char)
363. ThreadId.toText : ThreadId -> Text
364. todo : a -> b
365. structural type Tuple a b
366. Tuple.Cons : a -> b -> Tuple a b
367. structural type Unit
368. Unit.Unit : ()
369. Universal.< : a -> a -> Boolean
370. Universal.<= : a -> a -> Boolean
371. Universal.== : a -> a -> Boolean
372. Universal.> : a -> a -> Boolean
373. Universal.>= : a -> a -> Boolean
374. Universal.compare : a -> a -> Int
375. unsafe.coerceAbilities : (a ->{e1} b) -> a ->{e2} b
376. builtin type Value
377. Value.dependencies : Value -> [Term]
378. Value.deserialize : Bytes -> Either Text Value
379. Value.load : Value ->{IO} Either [Term] a
380. Value.serialize : Value -> Bytes
381. Value.value : a -> Value
.builtin> alias.many 94-104 .mylib

View File

@ -28,42 +28,45 @@ The `builtins.merge` command adds the known builtins to a `builtin` subnamespace
17. Exception/ (1 definition)
18. Float (builtin type)
19. Float/ (38 definitions)
20. Int (builtin type)
21. Int/ (31 definitions)
22. IsPropagated (type)
23. IsPropagated/ (1 definition)
24. IsTest (type)
25. IsTest/ (1 definition)
26. Link (type)
27. Link/ (5 definitions)
28. List (builtin type)
29. List/ (10 definitions)
30. Nat (builtin type)
31. Nat/ (28 definitions)
32. Optional (type)
33. Optional/ (2 definitions)
34. Ref (builtin type)
35. Ref/ (2 definitions)
36. Request (builtin type)
37. Scope (builtin type)
38. Scope/ (2 definitions)
39. SeqView (type)
40. SeqView/ (2 definitions)
41. Test/ (3 definitions)
42. Text (builtin type)
43. Text/ (18 definitions)
44. Tuple (type)
45. Tuple/ (1 definition)
46. Unit (type)
47. Unit/ (1 definition)
48. Universal/ (6 definitions)
49. Value (builtin type)
50. Value/ (5 definitions)
51. bug (a -> b)
52. crypto/ (12 definitions)
53. io2/ (124 definitions)
54. metadata/ (2 definitions)
55. todo (a -> b)
56. unsafe/ (1 definition)
20. Handle/ (1 definition)
21. Int (builtin type)
22. Int/ (31 definitions)
23. IsPropagated (type)
24. IsPropagated/ (1 definition)
25. IsTest (type)
26. IsTest/ (1 definition)
27. Link (type)
28. Link/ (5 definitions)
29. List (builtin type)
30. List/ (10 definitions)
31. Nat (builtin type)
32. Nat/ (28 definitions)
33. Optional (type)
34. Optional/ (2 definitions)
35. Ref (builtin type)
36. Ref/ (2 definitions)
37. Request (builtin type)
38. Scope (builtin type)
39. Scope/ (2 definitions)
40. SeqView (type)
41. SeqView/ (2 definitions)
42. Socket/ (1 definition)
43. Test/ (3 definitions)
44. Text (builtin type)
45. Text/ (18 definitions)
46. ThreadId/ (1 definition)
47. Tuple (type)
48. Tuple/ (1 definition)
49. Unit (type)
50. Unit/ (1 definition)
51. Universal/ (6 definitions)
52. Value (builtin type)
53. Value/ (5 definitions)
54. bug (a -> b)
55. crypto/ (12 definitions)
56. io2/ (124 definitions)
57. metadata/ (2 definitions)
58. todo (a -> b)
59. unsafe/ (1 definition)
```

View File

@ -23,7 +23,7 @@ Technically, the definitions all exist, but they have no names. `builtins.merge`
.foo> ls
1. builtin/ (378 definitions)
1. builtin/ (381 definitions)
```
And for a limited time, you can get even more builtin goodies:
@ -35,7 +35,7 @@ And for a limited time, you can get even more builtin goodies:
.foo> ls
1. builtin/ (546 definitions)
1. builtin/ (549 definitions)
```
More typically, you'd start out by pulling `base.

View File

@ -112,13 +112,13 @@ We can also delete the fork if we're done with it. (Don't worry, it's still in t
Note: The most recent namespace hash is immediately below this
message.
#4dmogr46d2
#hpg84g7itp
- Deletes:
feature1.y
#fe6mqhfcun
#7qqt9t3qr5
+ Adds / updates:
@ -129,26 +129,26 @@ We can also delete the fork if we're done with it. (Don't worry, it's still in t
Original name New name(s)
feature1.y master.y
#qlrc4272pk
#u86vero990
+ Adds / updates:
feature1.y
#mu2ju8e2ic
#el4liebh4m
> Moves:
Original name New name
x master.x
#4adnodif8j
#pne2sthbc8
+ Adds / updates:
x
#ucb56c3fgj (start of history)
#qnkdl1f20n (start of history)
```
To resurrect an old version of a namespace, you can learn its hash via the `history` command, then use `fork #namespacehash .newname`.

View File

@ -59,16 +59,16 @@ y = 2
most recent, along with the command that got us there. Try:
`fork 2 .old`
`fork #o7ncp4f3j1 .old` to make an old namespace
`fork #7m7gaa64si .old` to make an old namespace
accessible again,
`reset-root #o7ncp4f3j1` to reset the root namespace and
`reset-root #7m7gaa64si` to reset the root namespace and
its history to that of the
specified namespace.
1. #nc81qsj2br : add
2. #o7ncp4f3j1 : add
3. #ucb56c3fgj : builtins.merge
1. #k8o73d0cc0 : add
2. #7m7gaa64si : add
3. #qnkdl1f20n : builtins.merge
4. #sjg2v58vn2 : (initial reflogged namespace)
```

View File

@ -13,7 +13,7 @@ Let's look at some examples. We'll start with a namespace with just the builtins
#edu0qq546n (start of history)
#tfjjgvaq9l (start of history)
.> fork builtin builtin2
@ -42,21 +42,21 @@ Now suppose we `fork` a copy of builtin, then rename `Nat.+` to `frobnicate`, th
Note: The most recent namespace hash is immediately below this
message.
#u7d9er9k2f
#uiahjr3nvu
> Moves:
Original name New name
Nat.frobnicate Nat.+
#4dcjftvejg
#ov2s5dsaba
> Moves:
Original name New name
Nat.+ Nat.frobnicate
#edu0qq546n (start of history)
#tfjjgvaq9l (start of history)
```
If we merge that back into `builtin`, we get that same chain of history:
@ -71,21 +71,21 @@ If we merge that back into `builtin`, we get that same chain of history:
Note: The most recent namespace hash is immediately below this
message.
#u7d9er9k2f
#uiahjr3nvu
> Moves:
Original name New name
Nat.frobnicate Nat.+
#4dcjftvejg
#ov2s5dsaba
> Moves:
Original name New name
Nat.+ Nat.frobnicate
#edu0qq546n (start of history)
#tfjjgvaq9l (start of history)
```
Let's try again, but using a `merge.squash` (or just `squash`) instead. The history will be unchanged:
@ -106,7 +106,7 @@ Let's try again, but using a `merge.squash` (or just `squash`) instead. The hist
#edu0qq546n (start of history)
#tfjjgvaq9l (start of history)
```
The churn that happened in `mybuiltin` namespace ended up back in the same spot, so the squash merge of that namespace with our original namespace had no effect.
@ -485,13 +485,13 @@ This checks to see that squashing correctly preserves deletions:
Note: The most recent namespace hash is immediately below this
message.
#0kh907mpqb
#dp0rpp67if
- Deletes:
Nat.* Nat.+
#edu0qq546n (start of history)
#tfjjgvaq9l (start of history)
```
Notice that `Nat.+` and `Nat.*` are deleted by the squash, and we see them deleted in one atomic step in the history.