mirror of
https://github.com/unisonweb/unison.git
synced 2024-11-12 04:34:38 +03:00
Merge pull request #1797 from stew/feature/Any
Add an Any parameter to the Failure type
This commit is contained in:
commit
7ceadd6e3d
@ -167,6 +167,8 @@ builtinTypesSrc =
|
||||
, B' "Value" CT.Data
|
||||
, B' "Any" CT.Data
|
||||
, B' "crypto.HashAlgorithm" CT.Data
|
||||
, B' "IOFailure" CT.Data, Rename' "IOFailure" "io2.IOFailure"
|
||||
, B' "TlsFailure" CT.Data, Rename' "TlsFailure" "io2.TlsFailure"
|
||||
, B' "Tls" CT.Data, Rename' "Tls" "io2.Tls"
|
||||
, B' "Tls.ClientConfig" CT.Data, Rename' "Tls.ClientConfig" "io2.Tls.ClientConfig"
|
||||
, B' "Tls.ServerConfig" CT.Data, Rename' "Tls.ServerConfig" "io2.Tls.ServerConfig"
|
||||
@ -390,7 +392,7 @@ builtinsSrc =
|
||||
, B "Text.toCharList" $ text --> list char
|
||||
, B "Text.fromCharList" $ list char --> text
|
||||
, B "Text.toUtf8" $ text --> bytes
|
||||
, B "Text.fromUtf8.v2" $ bytes --> eithert failure text
|
||||
, B "Text.fromUtf8.v3" $ bytes --> eithert failure text
|
||||
, B "Char.toNat" $ char --> nat
|
||||
, B "Char.fromNat" $ nat --> char
|
||||
|
||||
@ -504,45 +506,45 @@ hashBuiltins =
|
||||
|
||||
ioBuiltins :: Var v => [(Text, Type v)]
|
||||
ioBuiltins =
|
||||
[ ("IO.openFile.v2", text --> fmode --> iof handle)
|
||||
, ("IO.closeFile.v2", handle --> iof unit)
|
||||
, ("IO.isFileEOF.v2", handle --> iof boolean)
|
||||
, ("IO.isFileOpen.v2", handle --> iof boolean)
|
||||
, ("IO.isSeekable.v2", handle --> iof boolean)
|
||||
, ("IO.seekHandle.v2", handle --> smode --> int --> iof unit)
|
||||
, ("IO.handlePosition.v2", handle --> iof int)
|
||||
, ("IO.getBuffering.v2", handle --> iof bmode)
|
||||
, ("IO.setBuffering.v2", handle --> bmode --> iof unit)
|
||||
, ("IO.getBytes.v2", handle --> nat --> iof bytes)
|
||||
, ("IO.putBytes.v2", handle --> bytes --> iof unit)
|
||||
, ("IO.systemTime.v2", unit --> iof nat)
|
||||
, ("IO.getTempDirectory.v2", unit --> iof text)
|
||||
[ ("IO.openFile.v3", text --> fmode --> iof handle)
|
||||
, ("IO.closeFile.v3", handle --> iof unit)
|
||||
, ("IO.isFileEOF.v3", handle --> iof boolean)
|
||||
, ("IO.isFileOpen.v3", handle --> iof boolean)
|
||||
, ("IO.isSeekable.v3", handle --> iof boolean)
|
||||
, ("IO.seekHandle.v3", handle --> smode --> int --> iof unit)
|
||||
, ("IO.handlePosition.v3", handle --> iof nat)
|
||||
, ("IO.getBuffering.v3", handle --> iof bmode)
|
||||
, ("IO.setBuffering.v3", handle --> bmode --> iof unit)
|
||||
, ("IO.getBytes.v3", handle --> nat --> iof bytes)
|
||||
, ("IO.putBytes.v3", handle --> bytes --> iof unit)
|
||||
, ("IO.systemTime.v3", unit --> iof nat)
|
||||
, ("IO.getTempDirectory.v3", unit --> iof text)
|
||||
, ("IO.createTempDirectory", text --> iof text)
|
||||
, ("IO.getCurrentDirectory.v2", unit --> iof text)
|
||||
, ("IO.setCurrentDirectory.v2", text --> iof unit)
|
||||
, ("IO.fileExists.v2", text --> iof boolean)
|
||||
, ("IO.isDirectory.v2", text --> iof boolean)
|
||||
, ("IO.createDirectory.v2", text --> iof unit)
|
||||
, ("IO.removeDirectory.v2", text --> iof unit)
|
||||
, ("IO.renameDirectory.v2", text --> text --> iof unit)
|
||||
, ("IO.removeFile.v2", text --> iof unit)
|
||||
, ("IO.renameFile.v2", text --> text --> iof unit)
|
||||
, ("IO.getFileTimestamp.v2", text --> iof nat)
|
||||
, ("IO.getFileSize.v2", text --> iof nat)
|
||||
, ("IO.serverSocket.v2", optionalt text --> text --> iof socket)
|
||||
, ("IO.listen.v2", socket --> iof unit)
|
||||
, ("IO.clientSocket.v2", text --> text --> iof socket)
|
||||
, ("IO.closeSocket.v2", socket --> iof unit)
|
||||
, ("IO.getCurrentDirectory.v3", unit --> iof text)
|
||||
, ("IO.setCurrentDirectory.v3", text --> iof unit)
|
||||
, ("IO.fileExists.v3", text --> iof boolean)
|
||||
, ("IO.isDirectory.v3", text --> iof boolean)
|
||||
, ("IO.createDirectory.v3", text --> iof unit)
|
||||
, ("IO.removeDirectory.v3", text --> iof unit)
|
||||
, ("IO.renameDirectory.v3", text --> text --> iof unit)
|
||||
, ("IO.removeFile.v3", text --> iof unit)
|
||||
, ("IO.renameFile.v3", text --> text --> iof unit)
|
||||
, ("IO.getFileTimestamp.v3", text --> iof nat)
|
||||
, ("IO.getFileSize.v3", text --> iof nat)
|
||||
, ("IO.serverSocket.v3", optionalt text --> text --> iof socket)
|
||||
, ("IO.listen.v3", socket --> iof unit)
|
||||
, ("IO.clientSocket.v3", text --> text --> iof socket)
|
||||
, ("IO.closeSocket.v3", socket --> iof unit)
|
||||
, ("IO.socketPort", socket --> iof nat)
|
||||
, ("IO.socketAccept.v2", socket --> iof socket)
|
||||
, ("IO.socketSend.v2", socket --> bytes --> iof unit)
|
||||
, ("IO.socketReceive.v2", socket --> nat --> iof bytes)
|
||||
, ("IO.socketAccept.v3", socket --> iof socket)
|
||||
, ("IO.socketSend.v3", socket --> bytes --> iof unit)
|
||||
, ("IO.socketReceive.v3", socket --> nat --> iof bytes)
|
||||
, ("IO.forkComp.v2"
|
||||
, forall1 "a" $ \a -> (unit --> io a) --> io threadId)
|
||||
, ("IO.stdHandle", stdhandle --> handle)
|
||||
|
||||
, ("IO.delay.v2", nat --> iof unit)
|
||||
, ("IO.kill.v2", threadId --> iof unit)
|
||||
, ("IO.delay.v3", nat --> iof unit)
|
||||
, ("IO.kill.v3", threadId --> iof unit)
|
||||
, ("Tls.newClient", tlsClientConfig --> socket --> iof tls)
|
||||
, ("Tls.newServer", tlsServerConfig --> socket --> iof tls)
|
||||
, ("Tls.handshake", tls --> iof unit)
|
||||
@ -555,12 +557,12 @@ ioBuiltins =
|
||||
, ("Tls.terminate", tls --> iof unit)
|
||||
, ("Tls.ClientConfig.default", text --> bytes --> tlsClientConfig)
|
||||
, ("Tls.ServerConfig.default", list tlsSignedCert --> tlsPrivateKey --> tlsServerConfig)
|
||||
, ("tls.ClientConfig.ciphers.set", list tlsCipher --> tlsClientConfig --> tlsClientConfig)
|
||||
, ("tls.ServerConfig.ciphers.set", list tlsCipher --> tlsServerConfig --> tlsServerConfig)
|
||||
, ("TLS.ClientConfig.ciphers.set", list tlsCipher --> tlsClientConfig --> tlsClientConfig)
|
||||
, ("Tls.ServerConfig.ciphers.set", list tlsCipher --> tlsServerConfig --> tlsServerConfig)
|
||||
, ("Tls.ClientConfig.certificates.set", list tlsSignedCert --> tlsClientConfig --> tlsClientConfig)
|
||||
, ("Tls.ServerConfig.certificates.set", list tlsSignedCert --> tlsServerConfig --> tlsServerConfig)
|
||||
, ("tls.ClientConfig.versions.set", list tlsVersion --> tlsClientConfig --> tlsClientConfig)
|
||||
, ("tls.ServerConfig.versions.set", list tlsVersion --> tlsServerConfig --> tlsServerConfig)
|
||||
, ("Tls.ClientConfig.versions.set", list tlsVersion --> tlsClientConfig --> tlsClientConfig)
|
||||
, ("Tls.ServerConfig.versions.set", list tlsVersion --> tlsServerConfig --> tlsServerConfig)
|
||||
|
||||
]
|
||||
|
||||
@ -568,13 +570,13 @@ mvarBuiltins :: forall v. Var v => [(Text, Type v)]
|
||||
mvarBuiltins =
|
||||
[ ("MVar.new", forall1 "a" $ \a -> a --> io (mvar a))
|
||||
, ("MVar.newEmpty.v2", forall1 "a" $ \a -> unit --> io (mvar a))
|
||||
, ("MVar.take.v2", forall1 "a" $ \a -> mvar a --> iof a)
|
||||
, ("MVar.take.v3", forall1 "a" $ \a -> mvar a --> iof a)
|
||||
, ("MVar.tryTake", forall1 "a" $ \a -> mvar a --> io (optionalt a))
|
||||
, ("MVar.put.v2", forall1 "a" $ \a -> mvar a --> a --> iof unit)
|
||||
, ("MVar.put.v3", forall1 "a" $ \a -> mvar a --> a --> iof unit)
|
||||
, ("MVar.tryPut", forall1 "a" $ \a -> mvar a --> a --> io boolean)
|
||||
, ("MVar.swap.v2", forall1 "a" $ \a -> mvar a --> a --> iof a)
|
||||
, ("MVar.swap.v3", forall1 "a" $ \a -> mvar a --> a --> iof a)
|
||||
, ("MVar.isEmpty", forall1 "a" $ \a -> mvar a --> io boolean)
|
||||
, ("MVar.read.v2", forall1 "a" $ \a -> mvar a --> iof a)
|
||||
, ("MVar.read.v3", forall1 "a" $ \a -> mvar a --> iof a)
|
||||
, ("MVar.tryRead", forall1 "a" $ \a -> mvar a --> io (optionalt a))
|
||||
]
|
||||
where
|
||||
|
@ -105,6 +105,7 @@ builtinDataDecls = rs1 ++ rs
|
||||
, (v "io2.StdHandle" , stdhnd)
|
||||
, (v "io2.Failure" , failure)
|
||||
, (v "io2.TlsFailure" , tlsFailure)
|
||||
, (v "io2.IOFailure" , ioFailure)
|
||||
] of Right a -> a; Left e -> error $ "builtinDataDecls: " <> show e
|
||||
[(_, linkRef, _)] = rs1
|
||||
v = Var.named
|
||||
@ -200,13 +201,15 @@ builtinDataDecls = rs1 ++ rs
|
||||
(Unique "52ad89274a358b9c802792aa05915e25ac83205f7885395cc6c6c988bc5ec69a1")
|
||||
()
|
||||
[]
|
||||
[ ((), v "io2.Failure.Failure", Type.typeLink () `arr` (Type.text () `arr` var "io2.Failure"))
|
||||
[ ((), v "io2.Failure.Failure", Type.typeLink () `arr` (Type.text () `arr` (Type.any () `arr` var "io2.Failure")))
|
||||
]
|
||||
tlsFailure = DataDeclaration
|
||||
(Unique "df5ba835130b227ab83d02d1feff5402455a732d613b51dee32230d2f2d067c6")
|
||||
()
|
||||
|
||||
tlsFailure = DataDeclaration (Unique "df5ba835130b227ab83d02d1feff5402455a732d613b51dee32230d2f2d067c6")()[]
|
||||
[]
|
||||
|
||||
ioFailure = DataDeclaration (Unique "009cb00e78cac9e47485cc3633c7a363939f63866ea07ab330346a2121d69a83")()[]
|
||||
[]
|
||||
|
||||
stdhnd = DataDeclaration
|
||||
(Unique "67bf7a8e517cbb1e9f42bc078e35498212d3be3c")
|
||||
()
|
||||
|
@ -29,7 +29,8 @@ import Unison.Symbol
|
||||
import qualified Unison.Runtime.Stack as Closure
|
||||
import Unison.Runtime.Stack (Closure)
|
||||
import Unison.Runtime.Foreign
|
||||
( Foreign(Wrap), HashAlgorithm(..), Failure(..))
|
||||
( Foreign(Wrap), HashAlgorithm(..), pattern Failure)
|
||||
import qualified Unison.Runtime.Foreign as F
|
||||
import Unison.Runtime.Foreign.Function
|
||||
import Unison.Runtime.IOSource
|
||||
|
||||
@ -75,7 +76,8 @@ import Network.TLS as TLS
|
||||
import Network.TLS.Extra.Cipher as Cipher
|
||||
|
||||
import System.IO as SYS
|
||||
( openFile
|
||||
( IOMode(..)
|
||||
, openFile
|
||||
, hClose
|
||||
, hGetBuffering
|
||||
, hSetBuffering
|
||||
@ -117,6 +119,8 @@ import qualified GHC.Conc as STM
|
||||
|
||||
import GHC.IO (IO(IO))
|
||||
|
||||
type Failure = F.Failure Closure
|
||||
|
||||
freshes :: Var v => Int -> [v]
|
||||
freshes = freshes' mempty
|
||||
|
||||
@ -855,9 +859,6 @@ inBxIomr arg1 arg2 fm result cont instr
|
||||
-- All of these functions will take a Var named result containing the
|
||||
-- result of the foreign call
|
||||
--
|
||||
outInt :: forall v. Var v => v -> ANormal v
|
||||
outInt i = TCon Ty.intRef 0 [i]
|
||||
|
||||
outMaybe :: forall v. Var v => v -> v -> ANormal v
|
||||
outMaybe maybe result =
|
||||
TMatch result . MatchSum $ mapFromList
|
||||
@ -964,14 +965,6 @@ unitToEFBox = inUnit unit result
|
||||
$ outIoFailBox stack1 stack2 fail result
|
||||
where (unit, stack1, stack2, fail, result) = fresh5
|
||||
|
||||
-- a -> Int
|
||||
boxToInt :: ForeignOp
|
||||
boxToInt = inBx arg result
|
||||
$ outInt result
|
||||
where
|
||||
(arg, result) = fresh2
|
||||
|
||||
-- a -> IOMode -> Either Failure b
|
||||
boxIomrToEFBox :: ForeignOp
|
||||
boxIomrToEFBox = inBxIomr arg1 arg2 enum result
|
||||
$ outIoFailBox stack1 stack2 fail result
|
||||
@ -1306,9 +1299,12 @@ mkForeignIOF f = mkForeign $ \a -> tryIOE (f a)
|
||||
tryIOE :: IO a -> IO (Either Failure a)
|
||||
tryIOE = fmap handleIOE . try
|
||||
handleIOE :: Either IOException a -> Either Failure a
|
||||
handleIOE (Left e) = Left $ traceShow e $ Failure ioFailureReference (pack (show e))
|
||||
handleIOE (Left e) = Left $ Failure ioFailureReference (pack (show e)) unitValue
|
||||
handleIOE (Right a) = Right a
|
||||
|
||||
unitValue :: Closure
|
||||
unitValue = Closure.Enum Ty.unitRef 0
|
||||
|
||||
mkForeignTls
|
||||
:: forall a r.(ForeignConvention a, ForeignConvention r)
|
||||
=> (a -> IO r) -> ForeignFunc
|
||||
@ -1318,40 +1314,48 @@ mkForeignTls f = mkForeign $ \a -> fmap flatten (tryIO2 (tryIO1 (f a)))
|
||||
tryIO1 = try
|
||||
tryIO2 :: IO (Either TLS.TLSException r) -> IO (Either IOException (Either TLS.TLSException r))
|
||||
tryIO2 = try
|
||||
flatten :: Either IOException (Either TLS.TLSException r) -> Either Failure r
|
||||
flatten (Left e) = Left (Failure ioFailureReference (pack (show e)))
|
||||
flatten (Right (Left e)) = Left (Failure tlsFailureReference (pack (show e)))
|
||||
flatten :: Either IOException (Either TLS.TLSException r) -> Either (Failure ) r
|
||||
flatten (Left e) = Left (Failure ioFailureReference (pack (show e)) unitValue)
|
||||
flatten (Right (Left e)) = Left (Failure tlsFailureReference (pack (show e)) (unitValue))
|
||||
flatten (Right (Right a)) = Right a
|
||||
|
||||
declareForeigns :: Var v => FDecl v ()
|
||||
declareForeigns = do
|
||||
declareForeign "IO.openFile.v3" boxIomrToEFBox $
|
||||
mkForeignIOF $ \(fnameText :: Text, n :: Int) ->
|
||||
let fname = (unpack fnameText)
|
||||
mode = case n of
|
||||
0 -> ReadMode
|
||||
1 -> WriteMode
|
||||
2 -> AppendMode
|
||||
_ -> ReadWriteMode
|
||||
in openFile fname mode
|
||||
|
||||
declareForeign "IO.openFile.v2" boxIomrToEFBox $ mkForeignIOF (uncurry openFile)
|
||||
declareForeign "IO.closeFile.v2" boxToEF0 $ mkForeignIOF hClose
|
||||
declareForeign "IO.isFileEOF.v2" boxToEFBool $ mkForeignIOF hIsEOF
|
||||
declareForeign "IO.isFileOpen.v2" boxToEFBool $ mkForeignIOF hIsOpen
|
||||
declareForeign "IO.isSeekable.v2" boxToEFBool $ mkForeignIOF hIsSeekable
|
||||
declareForeign "IO.closeFile.v3" boxToEF0 $ mkForeignIOF hClose
|
||||
declareForeign "IO.isFileEOF.v3" boxToEFBool $ mkForeignIOF hIsEOF
|
||||
declareForeign "IO.isFileOpen.v3" boxToEFBool $ mkForeignIOF hIsOpen
|
||||
declareForeign "IO.isSeekable.v3" boxToEFBool $ mkForeignIOF hIsSeekable
|
||||
|
||||
declareForeign "IO.seekHandle.v2" seek'handle
|
||||
declareForeign "IO.seekHandle.v3" seek'handle
|
||||
. mkForeignIOF $ \(h,sm,n) -> hSeek h sm (fromIntegral (n :: Int))
|
||||
|
||||
declareForeign "IO.handlePosition.v2" boxToInt
|
||||
declareForeign "IO.handlePosition.v3" boxToEFNat
|
||||
-- TODO: truncating integer
|
||||
. mkForeignIOF $ \h -> fromInteger @Word64 <$> hTell h
|
||||
|
||||
declareForeign "IO.getBuffering.v2" get'buffering
|
||||
declareForeign "IO.getBuffering.v3" get'buffering
|
||||
$ mkForeignIOF hGetBuffering
|
||||
|
||||
declareForeign "IO.setBuffering.v2" boxBoxToEF0
|
||||
declareForeign "IO.setBuffering.v3" boxBoxToEF0
|
||||
. mkForeignIOF $ uncurry hSetBuffering
|
||||
|
||||
declareForeign "IO.getBytes.v2" boxNatToEFBox . mkForeignIOF $ \(h,n) -> Bytes.fromArray <$> hGet h n
|
||||
declareForeign "IO.getBytes.v3" boxNatToEFBox . mkForeignIOF $ \(h,n) -> Bytes.fromArray <$> hGet h n
|
||||
|
||||
declareForeign "IO.putBytes.v2" boxBoxToEFBox . mkForeignIOF $ \(h,bs) -> hPut h (Bytes.toArray bs)
|
||||
declareForeign "IO.systemTime.v2" unitToEFNat
|
||||
declareForeign "IO.putBytes.v3" boxBoxToEFBox . mkForeignIOF $ \(h,bs) -> hPut h (Bytes.toArray bs)
|
||||
declareForeign "IO.systemTime.v3" unitToEFNat
|
||||
$ mkForeignIOF $ \() -> getPOSIXTime
|
||||
|
||||
declareForeign "IO.getTempDirectory.v2" unitToEFBox
|
||||
declareForeign "IO.getTempDirectory.v3" unitToEFBox
|
||||
$ mkForeignIOF $ \() -> getTemporaryDirectory
|
||||
|
||||
declareForeign "IO.createTempDirectory" boxToEFBox
|
||||
@ -1359,41 +1363,41 @@ declareForeigns = do
|
||||
temp <- getTemporaryDirectory
|
||||
createTempDirectory temp prefix
|
||||
|
||||
declareForeign "IO.getCurrentDirectory.v2" direct
|
||||
declareForeign "IO.getCurrentDirectory.v3" direct
|
||||
. mkForeignIOF $ \() -> getCurrentDirectory
|
||||
|
||||
declareForeign "IO.setCurrentDirectory.v2" boxToEF0
|
||||
declareForeign "IO.setCurrentDirectory.v3" boxToEF0
|
||||
$ mkForeignIOF setCurrentDirectory
|
||||
|
||||
declareForeign "IO.fileExists.v2" boxToEFBool
|
||||
declareForeign "IO.fileExists.v3" boxToEFBool
|
||||
$ mkForeignIOF doesPathExist
|
||||
|
||||
declareForeign "IO.isDirectory.v2" boxToEFBool
|
||||
declareForeign "IO.isDirectory.v3" boxToEFBool
|
||||
$ mkForeignIOF doesDirectoryExist
|
||||
|
||||
declareForeign "IO.createDirectory.v2" boxToEF0
|
||||
declareForeign "IO.createDirectory.v3" boxToEF0
|
||||
$ mkForeignIOF $ createDirectoryIfMissing True
|
||||
|
||||
declareForeign "IO.removeDirectory.v2" boxToEF0
|
||||
declareForeign "IO.removeDirectory.v3" boxToEF0
|
||||
$ mkForeignIOF removeDirectoryRecursive
|
||||
|
||||
declareForeign "IO.renameDirectory.v2" boxBoxToEF0
|
||||
declareForeign "IO.renameDirectory.v3" boxBoxToEF0
|
||||
$ mkForeignIOF $ uncurry renameDirectory
|
||||
|
||||
declareForeign "IO.removeFile.v2" boxToEF0
|
||||
declareForeign "IO.removeFile.v3" boxToEF0
|
||||
$ mkForeignIOF removeFile
|
||||
|
||||
declareForeign "IO.renameFile.v2" boxBoxToEF0
|
||||
declareForeign "IO.renameFile.v3" boxBoxToEF0
|
||||
$ mkForeignIOF $ uncurry renameFile
|
||||
|
||||
declareForeign "IO.getFileTimestamp.v2" boxToEFNat
|
||||
declareForeign "IO.getFileTimestamp.v3" boxToEFNat
|
||||
. mkForeignIOF $ fmap utcTimeToPOSIXSeconds . getModificationTime
|
||||
|
||||
declareForeign "IO.getFileSize.v2" boxToEFNat
|
||||
declareForeign "IO.getFileSize.v3" boxToEFNat
|
||||
-- TODO: truncating integer
|
||||
. mkForeignIOF $ \fp -> fromInteger @Word64 <$> getFileSize fp
|
||||
|
||||
declareForeign "IO.serverSocket.v2" maybeBoxToEFBox
|
||||
declareForeign "IO.serverSocket.v3" maybeBoxToEFBox
|
||||
. mkForeignIOF $ \(mhst :: Maybe Text
|
||||
, port) ->
|
||||
fst <$> SYS.bindSock (hostPreference mhst) port
|
||||
@ -1403,28 +1407,28 @@ declareForeigns = do
|
||||
n <- SYS.socketPort handle
|
||||
return (fromIntegral n :: Word64)
|
||||
|
||||
declareForeign "IO.listen.v2" boxToEF0
|
||||
declareForeign "IO.listen.v3" boxToEF0
|
||||
. mkForeignIOF $ \sk -> SYS.listenSock sk 2
|
||||
|
||||
declareForeign "IO.clientSocket.v2" boxBoxToEFBox
|
||||
declareForeign "IO.clientSocket.v3" boxBoxToEFBox
|
||||
. mkForeignIOF $ fmap fst . uncurry SYS.connectSock
|
||||
|
||||
declareForeign "IO.closeSocket.v2" boxToEF0
|
||||
declareForeign "IO.closeSocket.v3" boxToEF0
|
||||
$ mkForeignIOF SYS.closeSock
|
||||
|
||||
declareForeign "IO.socketAccept.v2" boxToEFBox
|
||||
declareForeign "IO.socketAccept.v3" boxToEFBox
|
||||
. mkForeignIOF $ fmap fst . SYS.accept
|
||||
|
||||
declareForeign "IO.socketSend.v2" boxBoxToEF0
|
||||
declareForeign "IO.socketSend.v3" boxBoxToEF0
|
||||
. mkForeignIOF $ \(sk,bs) -> SYS.send sk (Bytes.toArray bs)
|
||||
|
||||
declareForeign "IO.socketReceive.v2" boxNatToEFBox
|
||||
declareForeign "IO.socketReceive.v3" boxNatToEFBox
|
||||
. mkForeignIOF $ \(hs,n) ->
|
||||
maybe Bytes.empty Bytes.fromArray <$> SYS.recv hs n
|
||||
|
||||
declareForeign "IO.kill.v2" boxTo0 $ mkForeignIOF killThread
|
||||
declareForeign "IO.kill.v3" boxTo0 $ mkForeignIOF killThread
|
||||
|
||||
declareForeign "IO.delay.v2" natToUnit $ mkForeignIOF threadDelay
|
||||
declareForeign "IO.delay.v3" natToUnit $ mkForeignIOF threadDelay
|
||||
|
||||
declareForeign "IO.stdHandle" standard'handle
|
||||
. mkForeign $ \(n :: Int) -> case n of
|
||||
@ -1439,25 +1443,25 @@ declareForeigns = do
|
||||
declareForeign "MVar.newEmpty.v2" unitDirect
|
||||
. mkForeign $ \() -> newEmptyMVar @Closure
|
||||
|
||||
declareForeign "MVar.take.v2" boxToEFBox
|
||||
declareForeign "MVar.take.v3" boxToEFBox
|
||||
. mkForeignIOF $ \(mv :: MVar Closure) -> takeMVar mv
|
||||
|
||||
declareForeign "MVar.tryTake" boxToMaybeBox
|
||||
. mkForeign $ \(mv :: MVar Closure) -> tryTakeMVar mv
|
||||
|
||||
declareForeign "MVar.put.v2" boxBoxToEF0
|
||||
declareForeign "MVar.put.v3" boxBoxToEF0
|
||||
. mkForeignIOF $ \(mv :: MVar Closure, x) -> putMVar mv x
|
||||
|
||||
declareForeign "MVar.tryPut" boxBoxToEFBool
|
||||
. mkForeign $ \(mv :: MVar Closure, x) -> tryPutMVar mv x
|
||||
|
||||
declareForeign "MVar.swap.v2" boxBoxToEFBox
|
||||
declareForeign "MVar.swap.v3" boxBoxToEFBox
|
||||
. mkForeignIOF $ \(mv :: MVar Closure, x) -> swapMVar mv x
|
||||
|
||||
declareForeign "MVar.isEmpty" boxToBool
|
||||
. mkForeign $ \(mv :: MVar Closure) -> isEmptyMVar mv
|
||||
|
||||
declareForeign "MVar.read.v2" boxBoxToEFBox
|
||||
declareForeign "MVar.read.v3" boxBoxToEFBox
|
||||
. mkForeignIOF $ \(mv :: MVar Closure) -> readMVar mv
|
||||
|
||||
declareForeign "MVar.tryRead" boxToMaybeBox
|
||||
@ -1466,8 +1470,8 @@ declareForeigns = do
|
||||
declareForeign "Text.toUtf8" boxDirect . mkForeign
|
||||
$ pure . Bytes.fromArray . encodeUtf8
|
||||
|
||||
declareForeign "Text.fromUtf8.v2" boxToEFBox . mkForeign
|
||||
$ pure . mapLeft (Failure ioFailureReference . pack . show) . decodeUtf8' . Bytes.toArray
|
||||
declareForeign "Text.fromUtf8.v3" boxToEFBox . mkForeign
|
||||
$ pure . mapLeft (\t -> Failure ioFailureReference (pack ( show t)) unitValue) . decodeUtf8' . Bytes.toArray
|
||||
|
||||
declareForeign "Tls.ClientConfig.default" boxBoxDirect . mkForeign
|
||||
$ \(hostName::Text, serverId:: Bytes.Bytes) ->
|
||||
@ -1546,7 +1550,7 @@ declareForeigns = do
|
||||
\(tls :: TLS.Context,
|
||||
bytes :: Bytes.Bytes) -> TLS.sendData tls (Bytes.toLazyByteString bytes)
|
||||
|
||||
let wrapFailure t = Failure tlsFailureReference (pack t)
|
||||
let wrapFailure t = Failure tlsFailureReference (pack t) unitValue
|
||||
decoded :: Bytes.Bytes -> Either String PEM
|
||||
decoded bytes = fmap head $ pemParseLBS $ Bytes.toLazyByteString bytes
|
||||
asCert :: PEM -> Either String X.SignedCertificate
|
||||
|
@ -106,7 +106,7 @@ data HashAlgorithm where
|
||||
|
||||
newtype Tls = Tls TLS.Context
|
||||
|
||||
data Failure = Failure Reference Text -- todo: Failure a = Failure Reference Text (Any a)
|
||||
data Failure a = Failure Reference Text a
|
||||
|
||||
instance BuiltinForeign HashAlgorithm where foreignRef = Tagged Ty.hashAlgorithmRef
|
||||
|
||||
|
@ -258,13 +258,15 @@ instance (ForeignConvention a, ForeignConvention b)
|
||||
(ustk, bstk) <- writeForeign ustk bstk y
|
||||
writeForeign ustk bstk x
|
||||
|
||||
instance ForeignConvention Failure where
|
||||
instance ForeignConvention a => ForeignConvention (Failure a) where
|
||||
readForeign us bs ustk bstk = do
|
||||
(us,bs,typeref) <- readTypelink us bs ustk bstk
|
||||
(us,bs,message) <- readForeign us bs ustk bstk
|
||||
pure (us, bs, Failure typeref message)
|
||||
(us,bs,any) <- readForeign us bs ustk bstk
|
||||
pure (us, bs, Failure typeref message any)
|
||||
|
||||
writeForeign ustk bstk (Failure typeref message) = do
|
||||
writeForeign ustk bstk (Failure typeref message any) = do
|
||||
(ustk, bstk) <- writeForeign ustk bstk any
|
||||
(ustk, bstk) <- writeForeign ustk bstk message
|
||||
writeTypeLink ustk bstk typeref
|
||||
|
||||
|
@ -265,6 +265,9 @@ valueRef = Reference.Builtin "Value"
|
||||
anyRef :: Reference
|
||||
anyRef = Reference.Builtin "Any"
|
||||
|
||||
any :: Ord v => a -> Type v a
|
||||
any a = ref a anyRef
|
||||
|
||||
builtin :: Ord v => a -> Text -> Type v a
|
||||
builtin a = ref a . Reference.Builtin
|
||||
|
||||
|
@ -72,7 +72,7 @@ autoCleaned.handler _ =
|
||||
Left _ -> handle k dir with go dirs
|
||||
|
||||
{ TempDirs.removeDir dir -> k } ->
|
||||
handle k (removeDirectory dir) with go (filter (d -> not (d == dir)) dirs)
|
||||
handle k (removeDirectory dir) with go (filter (d -> not (d == dir)) dirs)
|
||||
|
||||
go []
|
||||
|
||||
@ -134,7 +134,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO, TempDirs} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
```
|
||||
|
||||
@ -157,13 +157,13 @@ testAutoClean _ =
|
||||
dir
|
||||
|
||||
match evalTest go with
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
(results, Right dir) ->
|
||||
match isDirectory dir with
|
||||
Right b -> if b
|
||||
then results :+ (Fail "our temporary directory should no longer exist")
|
||||
else results :+ (Ok "our temporary directory should no longer exist")
|
||||
Left (Failure _ t) -> results :+ (Fail t)
|
||||
Left (Failure _ t _) -> results :+ (Fail t)
|
||||
```
|
||||
|
||||
```ucm
|
||||
@ -249,18 +249,19 @@ testSeek : '{io2.IO} [Result]
|
||||
testSeek _ =
|
||||
test = 'let
|
||||
tempDir = toException (newTempDir "seek")
|
||||
emit (Ok "seeked")
|
||||
fooFile = tempDir ++ "/foo"
|
||||
handle1 = toException (openFile fooFile FileMode.Write)
|
||||
handle1 = toException (openFile fooFile FileMode.Append)
|
||||
putBytes handle1 (toUtf8 "12345678")
|
||||
closeFile handle1
|
||||
|
||||
handle3 = toException (openFile fooFile FileMode.Read)
|
||||
check "readable file should be seekable" (toException (isSeekable handle3))
|
||||
check "shouldn't be the EOF" (not (toException (isFileEOF handle3)))
|
||||
expectU "we should be at position 0" +0 (toException (handlePosition handle3))
|
||||
expectU "we should be at position 0" 0 (toException (handlePosition handle3))
|
||||
|
||||
toException (seekHandle handle3 AbsoluteSeek +1)
|
||||
expectU "we should be at position 1" +1 (toException (handlePosition handle3))
|
||||
expectU "we should be at position 1" 1 (toException (handlePosition handle3))
|
||||
bytes3a = toException (getBytes handle3 1000)
|
||||
text3a = toException (Text.fromUtf8 bytes3a)
|
||||
expectU "should be able to read our temporary file after seeking" "2345678" text3a
|
||||
@ -272,25 +273,24 @@ testAppend : '{io2.IO} [Result]
|
||||
testAppend _ =
|
||||
test = 'let
|
||||
tempDir = toException (newTempDir "openFile")
|
||||
|
||||
fooFile = tempDir ++ "/foo"
|
||||
handle1 = toException (openFile fooFile FileMode.Write)
|
||||
putBytes handle1 (toUtf8 "test1")
|
||||
closeFile handle1
|
||||
toException (putBytes handle1 (toUtf8 "test1"))
|
||||
toException (closeFile handle1)
|
||||
|
||||
handle2 = toException (openFile fooFile FileMode.Append)
|
||||
putBytes handle2 (toUtf8 "test2")
|
||||
expectU "we should be at position 4" +4 (toException (handlePosition handle2))
|
||||
check "which is the EOF" (toException (isFileEOF handle2))
|
||||
closeFile handle2
|
||||
toException (putBytes handle2 (toUtf8 "test2"))
|
||||
toException (closeFile handle2)
|
||||
|
||||
handle3 = toException (openFile fooFile FileMode.Read)
|
||||
bytes3 = toException (getBytes handle3 1000)
|
||||
text3 = toException (Text.fromUtf8 bytes3)
|
||||
|
||||
expectU "should be able to read our temporary file" "test1test2" text3
|
||||
|
||||
closeFile handle3
|
||||
|
||||
|
||||
runTest test
|
||||
```
|
||||
```ucm
|
||||
|
@ -67,7 +67,7 @@ autoCleaned.handler _ =
|
||||
Left _ -> handle k dir with go dirs
|
||||
|
||||
{ TempDirs.removeDir dir -> k } ->
|
||||
handle k (removeDirectory dir) with go (filter (d -> not (d == dir)) dirs)
|
||||
handle k (removeDirectory dir) with go (filter (d -> not (d == dir)) dirs)
|
||||
|
||||
go []
|
||||
|
||||
@ -129,7 +129,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO, TempDirs} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
```
|
||||
|
||||
@ -148,13 +148,13 @@ testAutoClean _ =
|
||||
dir
|
||||
|
||||
match evalTest go with
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
(results, Right dir) ->
|
||||
match isDirectory dir with
|
||||
Right b -> if b
|
||||
then results :+ (Fail "our temporary directory should no longer exist")
|
||||
else results :+ (Ok "our temporary directory should no longer exist")
|
||||
Left (Failure _ t) -> results :+ (Fail t)
|
||||
Left (Failure _ t _) -> results :+ (Fail t)
|
||||
```
|
||||
|
||||
```ucm
|
||||
@ -322,18 +322,19 @@ testSeek : '{io2.IO} [Result]
|
||||
testSeek _ =
|
||||
test = 'let
|
||||
tempDir = toException (newTempDir "seek")
|
||||
emit (Ok "seeked")
|
||||
fooFile = tempDir ++ "/foo"
|
||||
handle1 = toException (openFile fooFile FileMode.Write)
|
||||
handle1 = toException (openFile fooFile FileMode.Append)
|
||||
putBytes handle1 (toUtf8 "12345678")
|
||||
closeFile handle1
|
||||
|
||||
handle3 = toException (openFile fooFile FileMode.Read)
|
||||
check "readable file should be seekable" (toException (isSeekable handle3))
|
||||
check "shouldn't be the EOF" (not (toException (isFileEOF handle3)))
|
||||
expectU "we should be at position 0" +0 (toException (handlePosition handle3))
|
||||
expectU "we should be at position 0" 0 (toException (handlePosition handle3))
|
||||
|
||||
toException (seekHandle handle3 AbsoluteSeek +1)
|
||||
expectU "we should be at position 1" +1 (toException (handlePosition handle3))
|
||||
expectU "we should be at position 1" 1 (toException (handlePosition handle3))
|
||||
bytes3a = toException (getBytes handle3 1000)
|
||||
text3a = toException (Text.fromUtf8 bytes3a)
|
||||
expectU "should be able to read our temporary file after seeking" "2345678" text3a
|
||||
@ -345,25 +346,24 @@ testAppend : '{io2.IO} [Result]
|
||||
testAppend _ =
|
||||
test = 'let
|
||||
tempDir = toException (newTempDir "openFile")
|
||||
|
||||
fooFile = tempDir ++ "/foo"
|
||||
handle1 = toException (openFile fooFile FileMode.Write)
|
||||
putBytes handle1 (toUtf8 "test1")
|
||||
closeFile handle1
|
||||
toException (putBytes handle1 (toUtf8 "test1"))
|
||||
toException (closeFile handle1)
|
||||
|
||||
handle2 = toException (openFile fooFile FileMode.Append)
|
||||
putBytes handle2 (toUtf8 "test2")
|
||||
expectU "we should be at position 4" +4 (toException (handlePosition handle2))
|
||||
check "which is the EOF" (toException (isFileEOF handle2))
|
||||
closeFile handle2
|
||||
toException (putBytes handle2 (toUtf8 "test2"))
|
||||
toException (closeFile handle2)
|
||||
|
||||
handle3 = toException (openFile fooFile FileMode.Read)
|
||||
bytes3 = toException (getBytes handle3 1000)
|
||||
text3 = toException (Text.fromUtf8 bytes3)
|
||||
|
||||
expectU "should be able to read our temporary file" "test1test2" text3
|
||||
|
||||
closeFile handle3
|
||||
|
||||
|
||||
runTest test
|
||||
```
|
||||
|
||||
@ -391,10 +391,14 @@ testAppend _ =
|
||||
|
||||
New test results:
|
||||
|
||||
◉ testSeek seeked
|
||||
◉ testSeek readable file should be seekable
|
||||
◉ testSeek shouldn't be the EOF
|
||||
◉ testSeek we should be at position 0
|
||||
◉ testSeek we should be at position 1
|
||||
◉ testSeek should be able to read our temporary file after seeking
|
||||
|
||||
✅ 2 test(s) passing
|
||||
✅ 6 test(s) passing
|
||||
|
||||
Tip: Use view testSeek to view the source of a test.
|
||||
|
||||
@ -402,7 +406,11 @@ testAppend _ =
|
||||
|
||||
New test results:
|
||||
|
||||
😶 No tests available.
|
||||
◉ testAppend should be able to read our temporary file
|
||||
|
||||
✅ 1 test(s) passing
|
||||
|
||||
Tip: Use view testAppend to view the source of a test.
|
||||
|
||||
```
|
||||
### SystemTime
|
||||
|
@ -71,7 +71,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
|
||||
--
|
||||
@ -193,7 +193,7 @@ serverThread portVar toSend = 'let
|
||||
toException (closeSocket sock')
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
clientThread : MVar Nat -> MVar Text -> '{io2.IO}()
|
||||
@ -206,7 +206,7 @@ clientThread portVar resultVar = 'let
|
||||
toException (MVar.put resultVar msg)
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
testTcpConnect : '{io2.IO}[Result]
|
||||
|
@ -65,7 +65,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
|
||||
--
|
||||
@ -216,7 +216,7 @@ serverThread portVar toSend = 'let
|
||||
toException (closeSocket sock')
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
clientThread : MVar Nat -> MVar Text -> '{io2.IO}()
|
||||
@ -229,7 +229,7 @@ clientThread portVar resultVar = 'let
|
||||
toException (MVar.put resultVar msg)
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
testTcpConnect : '{io2.IO}[Result]
|
||||
|
@ -69,7 +69,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
|
||||
--
|
||||
@ -127,7 +127,7 @@ thread1 mv = 'let
|
||||
toException (put mv (increment x))
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
|
||||
@ -158,7 +158,7 @@ sendingThread toSend mv = 'let
|
||||
toException (put mv (increment toSend))
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
|
||||
@ -170,7 +170,7 @@ receivingThread recv send = 'let
|
||||
toException (put send (toText recvd))
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
testTwoThreads: '{io2.IO}[Result]
|
||||
|
@ -63,7 +63,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
|
||||
--
|
||||
@ -125,7 +125,7 @@ thread1 mv = 'let
|
||||
toException (put mv (increment x))
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
|
||||
@ -183,7 +183,7 @@ sendingThread toSend mv = 'let
|
||||
toException (put mv (increment toSend))
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
|
||||
@ -195,7 +195,7 @@ receivingThread recv send = 'let
|
||||
toException (put send (toText recvd))
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch t ()
|
||||
Left (Failure _ t _) -> watch t ()
|
||||
_ -> ()
|
||||
|
||||
testTwoThreads: '{io2.IO}[Result]
|
||||
|
@ -89,7 +89,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
|
||||
--
|
||||
@ -127,7 +127,7 @@ First lets make sure we can load our cert and private key
|
||||
|
||||
```unison
|
||||
test> match (decodeCert (toUtf8 self_signed_cert_pem) with
|
||||
Left (Failure _ t) -> [Fail t]
|
||||
Left (Failure _ t _) -> [Fail t]
|
||||
Right _ -> [Ok "succesfully decoded self_signed_pem"]
|
||||
|
||||
```
|
||||
@ -183,7 +183,7 @@ serverThread portVar toSend = 'let
|
||||
closeSocket sock' |> toException
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch ("error in server: " ++ t) ()
|
||||
Left (Failure _ t _) -> watch ("error in server: " ++ t) ()
|
||||
_ -> watch "server finished" ()
|
||||
|
||||
testClient : Optional SignedCert -> Text -> MVar Nat -> '{io2.IO, Exception Failure} Text
|
||||
@ -239,7 +239,7 @@ testCAReject _ =
|
||||
checkError : Either Failure a -> Result
|
||||
checkError = cases
|
||||
Right _ -> Fail "expected a handshake exception"
|
||||
Left (Failure _ t) ->
|
||||
Left (Failure _ t _) ->
|
||||
if contains "UnknownCa" t && contains "HandshakeFailed" t then Ok "correctly rejected self-signed cert" else
|
||||
Fail ("expected UnknownCa, got: " ++ t)
|
||||
|
||||
@ -263,8 +263,7 @@ testCNReject _ =
|
||||
checkError : Either Failure a -> Result
|
||||
checkError = cases
|
||||
Right _ -> Fail "expected a handshake exception"
|
||||
Left (Failure _ t) ->
|
||||
if contains "NameMismatch" t && contains "HandshakeFailed" t then Ok "correctly rejected self-signed cert" else
|
||||
Left (Failure _ t _) -> if contains "NameMismatch" t && contains "HandshakeFailed" t then Ok "correctly rejected self-signed cert" else
|
||||
Fail ("expected UnknownCa, got: " ++ t)
|
||||
|
||||
test _ =
|
||||
@ -278,11 +277,8 @@ testCNReject _ =
|
||||
|
||||
|
||||
runTest test
|
||||
|
||||
|
||||
```
|
||||
|
||||
|
||||
```ucm
|
||||
.> add
|
||||
.> io.test testConnectSelfSigned
|
||||
|
@ -83,7 +83,7 @@ evalTest a = handle
|
||||
runTest: '{Stream Result, Exception Failure, io2.IO} a -> [Result]
|
||||
runTest t = match evalTest t with
|
||||
(results, Right _) -> results
|
||||
(results, Left (Failure _ t)) -> results :+ (Fail t)
|
||||
(results, Left (Failure _ t _)) -> results :+ (Fail t)
|
||||
|
||||
|
||||
--
|
||||
@ -117,7 +117,7 @@ First lets make sure we can load our cert and private key
|
||||
|
||||
```unison
|
||||
test> match (decodeCert (toUtf8 self_signed_cert_pem) with
|
||||
Left (Failure _ t) -> [Fail t]
|
||||
Left (Failure _ t _) -> [Fail t]
|
||||
Right _ -> [Ok "succesfully decoded self_signed_pem"]
|
||||
|
||||
```
|
||||
@ -191,7 +191,7 @@ serverThread portVar toSend = 'let
|
||||
closeSocket sock' |> toException
|
||||
|
||||
match (toEither go) with
|
||||
Left (Failure _ t) -> watch ("error in server: " ++ t) ()
|
||||
Left (Failure _ t _) -> watch ("error in server: " ++ t) ()
|
||||
_ -> watch "server finished" ()
|
||||
|
||||
testClient : Optional SignedCert -> Text -> MVar Nat -> '{io2.IO, Exception Failure} Text
|
||||
@ -247,7 +247,7 @@ testCAReject _ =
|
||||
checkError : Either Failure a -> Result
|
||||
checkError = cases
|
||||
Right _ -> Fail "expected a handshake exception"
|
||||
Left (Failure _ t) ->
|
||||
Left (Failure _ t _) ->
|
||||
if contains "UnknownCa" t && contains "HandshakeFailed" t then Ok "correctly rejected self-signed cert" else
|
||||
Fail ("expected UnknownCa, got: " ++ t)
|
||||
|
||||
@ -271,8 +271,7 @@ testCNReject _ =
|
||||
checkError : Either Failure a -> Result
|
||||
checkError = cases
|
||||
Right _ -> Fail "expected a handshake exception"
|
||||
Left (Failure _ t) ->
|
||||
if contains "NameMismatch" t && contains "HandshakeFailed" t then Ok "correctly rejected self-signed cert" else
|
||||
Left (Failure _ t _) -> if contains "NameMismatch" t && contains "HandshakeFailed" t then Ok "correctly rejected self-signed cert" else
|
||||
Fail ("expected UnknownCa, got: " ++ t)
|
||||
|
||||
test _ =
|
||||
@ -286,8 +285,6 @@ testCNReject _ =
|
||||
|
||||
|
||||
runTest test
|
||||
|
||||
|
||||
```
|
||||
|
||||
```ucm
|
||||
|
@ -54,6 +54,6 @@ greek_bytes = Bytes.fromList [206, 145, 206, 146, 206, 147, 206, 148, 206]
|
||||
|
||||
-- Its an error if we drop the first byte
|
||||
> match fromUtf8 (drop 1 greek_bytes) with
|
||||
Left (Failure _ t) -> t
|
||||
Left (Failure _ t _) -> t
|
||||
|
||||
```
|
||||
|
@ -108,7 +108,7 @@ greek_bytes = Bytes.fromList [206, 145, 206, 146, 206, 147, 206, 148, 206]
|
||||
|
||||
-- Its an error if we drop the first byte
|
||||
> match fromUtf8 (drop 1 greek_bytes) with
|
||||
Left (Failure _ t) -> t
|
||||
Left (Failure _ t _) -> t
|
||||
|
||||
```
|
||||
|
||||
|
@ -239,7 +239,7 @@ Let's try it!
|
||||
216. io2.BufferMode.NoBuffering : BufferMode
|
||||
217. io2.BufferMode.SizedBlockBuffering : Nat -> BufferMode
|
||||
218. unique type io2.Failure
|
||||
219. io2.Failure.Failure : Type -> Text -> Failure
|
||||
219. io2.Failure.Failure : Type -> Text -> Any -> Failure
|
||||
220. unique type io2.FileMode
|
||||
221. io2.FileMode.Append : FileMode
|
||||
222. io2.FileMode.Read : FileMode
|
||||
@ -267,7 +267,7 @@ Let's try it!
|
||||
238. io2.IO.getFileSize : Text ->{IO} Either Failure Nat
|
||||
239. io2.IO.getFileTimestamp : Text ->{IO} Either Failure Nat
|
||||
240. io2.IO.getTempDirectory : '{IO} Either Failure Text
|
||||
241. io2.IO.handlePosition : Handle ->{IO} Either Failure Int
|
||||
241. io2.IO.handlePosition : Handle ->{IO} Either Failure Nat
|
||||
242. io2.IO.isDirectory : Text ->{IO} Either Failure Boolean
|
||||
243. io2.IO.isFileEOF : Handle ->{IO} Either Failure Boolean
|
||||
244. io2.IO.isFileOpen : Handle ->{IO} Either Failure Boolean
|
||||
@ -317,82 +317,85 @@ Let's try it!
|
||||
270. io2.IOError.ResourceBusy : IOError
|
||||
271. io2.IOError.ResourceExhausted : IOError
|
||||
272. io2.IOError.UserError : IOError
|
||||
273. builtin type io2.MVar
|
||||
274. io2.MVar.isEmpty : MVar a ->{IO} Boolean
|
||||
275. io2.MVar.new : a ->{IO} MVar a
|
||||
276. io2.MVar.newEmpty : '{IO} MVar a
|
||||
277. io2.MVar.put : MVar a -> a ->{IO} Either Failure ()
|
||||
278. io2.MVar.read : MVar a ->{IO} Either Failure a
|
||||
279. io2.MVar.swap : MVar a -> a ->{IO} Either Failure a
|
||||
280. io2.MVar.take : MVar a ->{IO} Either Failure a
|
||||
281. io2.MVar.tryPut : MVar a -> a ->{IO} Boolean
|
||||
282. io2.MVar.tryRead : MVar a ->{IO} Optional a
|
||||
283. io2.MVar.tryTake : MVar a ->{IO} Optional a
|
||||
284. builtin type io2.STM
|
||||
285. io2.STM.atomically : '{STM} a ->{IO} a
|
||||
286. io2.STM.retry : '{STM} a
|
||||
287. unique type io2.SeekMode
|
||||
288. io2.SeekMode.AbsoluteSeek : SeekMode
|
||||
289. io2.SeekMode.RelativeSeek : SeekMode
|
||||
290. io2.SeekMode.SeekFromEnd : SeekMode
|
||||
291. builtin type io2.Socket
|
||||
292. unique type io2.StdHandle
|
||||
293. io2.StdHandle.StdErr : StdHandle
|
||||
294. io2.StdHandle.StdIn : StdHandle
|
||||
295. io2.StdHandle.StdOut : StdHandle
|
||||
296. builtin type io2.TVar
|
||||
297. io2.TVar.new : a ->{STM} TVar a
|
||||
298. io2.TVar.newIO : a ->{IO} TVar a
|
||||
299. io2.TVar.read : TVar a ->{STM} a
|
||||
300. io2.TVar.readIO : TVar a ->{IO} a
|
||||
301. io2.TVar.swap : TVar a -> a ->{STM} a
|
||||
302. io2.TVar.write : TVar a -> a ->{STM} ()
|
||||
303. builtin type io2.ThreadId
|
||||
304. builtin type io2.Tls
|
||||
305. builtin type io2.Tls.ClientConfig
|
||||
306. io2.Tls.ClientConfig.certificates.set : [SignedCert]
|
||||
273. builtin type io2.IOFailure##IOFailure
|
||||
274. unique type io2.IOFailure#gro
|
||||
275. builtin type io2.MVar
|
||||
276. io2.MVar.isEmpty : MVar a ->{IO} Boolean
|
||||
277. io2.MVar.new : a ->{IO} MVar a
|
||||
278. io2.MVar.newEmpty : '{IO} MVar a
|
||||
279. io2.MVar.put : MVar a -> a ->{IO} Either Failure ()
|
||||
280. io2.MVar.read : MVar a ->{IO} Either Failure a
|
||||
281. io2.MVar.swap : MVar a -> a ->{IO} Either Failure a
|
||||
282. io2.MVar.take : MVar a ->{IO} Either Failure a
|
||||
283. io2.MVar.tryPut : MVar a -> a ->{IO} Boolean
|
||||
284. io2.MVar.tryRead : MVar a ->{IO} Optional a
|
||||
285. io2.MVar.tryTake : MVar a ->{IO} Optional a
|
||||
286. builtin type io2.STM
|
||||
287. io2.STM.atomically : '{STM} a ->{IO} a
|
||||
288. io2.STM.retry : '{STM} a
|
||||
289. unique type io2.SeekMode
|
||||
290. io2.SeekMode.AbsoluteSeek : SeekMode
|
||||
291. io2.SeekMode.RelativeSeek : SeekMode
|
||||
292. io2.SeekMode.SeekFromEnd : SeekMode
|
||||
293. builtin type io2.Socket
|
||||
294. unique type io2.StdHandle
|
||||
295. io2.StdHandle.StdErr : StdHandle
|
||||
296. io2.StdHandle.StdIn : StdHandle
|
||||
297. io2.StdHandle.StdOut : StdHandle
|
||||
298. io2.TLS.ClientConfig.ciphers.set : [##Tls.Cipher]
|
||||
-> ClientConfig
|
||||
-> ClientConfig
|
||||
299. builtin type io2.TVar
|
||||
300. io2.TVar.new : a ->{STM} TVar a
|
||||
301. io2.TVar.newIO : a ->{IO} TVar a
|
||||
302. io2.TVar.read : TVar a ->{STM} a
|
||||
303. io2.TVar.readIO : TVar a ->{IO} a
|
||||
304. io2.TVar.swap : TVar a -> a ->{STM} a
|
||||
305. io2.TVar.write : TVar a -> a ->{STM} ()
|
||||
306. builtin type io2.ThreadId
|
||||
307. builtin type io2.Tls
|
||||
308. builtin type io2.Tls.ClientConfig
|
||||
309. io2.Tls.ClientConfig.certificates.set : [SignedCert]
|
||||
-> ClientConfig
|
||||
-> ClientConfig
|
||||
307. io2.Tls.ClientConfig.default : Text
|
||||
310. io2.Tls.ClientConfig.default : Text
|
||||
-> Bytes
|
||||
-> ClientConfig
|
||||
308. builtin type io2.Tls.PrivateKey
|
||||
309. builtin type io2.Tls.ServerConfig
|
||||
310. io2.Tls.ServerConfig.certificates.set : [SignedCert]
|
||||
311. io2.Tls.ClientConfig.versions.set : [##Tls.Version]
|
||||
-> ClientConfig
|
||||
-> ClientConfig
|
||||
312. builtin type io2.Tls.PrivateKey
|
||||
313. builtin type io2.Tls.ServerConfig
|
||||
314. io2.Tls.ServerConfig.certificates.set : [SignedCert]
|
||||
-> ServerConfig
|
||||
-> ServerConfig
|
||||
311. io2.Tls.ServerConfig.default : [SignedCert]
|
||||
315. io2.Tls.ServerConfig.ciphers.set : [##Tls.Cipher]
|
||||
-> ServerConfig
|
||||
-> ServerConfig
|
||||
316. io2.Tls.ServerConfig.default : [SignedCert]
|
||||
-> PrivateKey
|
||||
-> ServerConfig
|
||||
312. builtin type io2.Tls.SignedCert
|
||||
313. io2.Tls.decodeCert : Bytes -> Either Failure SignedCert
|
||||
314. io2.Tls.decodePrivateKey : Bytes -> [PrivateKey]
|
||||
315. io2.Tls.encodeCert : SignedCert -> Bytes
|
||||
316. io2.Tls.encodePrivateKey : PrivateKey -> Bytes
|
||||
317. io2.Tls.handshake : Tls ->{IO} Either Failure ()
|
||||
318. io2.Tls.newClient : ClientConfig
|
||||
-> Socket
|
||||
->{IO} Either Failure Tls
|
||||
319. io2.Tls.newServer : ServerConfig
|
||||
-> Socket
|
||||
->{IO} Either Failure Tls
|
||||
320. io2.Tls.receive : Tls ->{IO} Either Failure Bytes
|
||||
321. io2.Tls.send : Tls -> Bytes ->{IO} Either Failure ()
|
||||
322. io2.Tls.terminate : Tls ->{IO} Either Failure ()
|
||||
323. unique type io2.TlsFailure
|
||||
324. io2.tls.ClientConfig.ciphers.set : [##Tls.Cipher]
|
||||
-> ClientConfig
|
||||
-> ClientConfig
|
||||
325. io2.tls.ClientConfig.versions.set : [##Tls.Version]
|
||||
-> ClientConfig
|
||||
-> ClientConfig
|
||||
326. io2.tls.ServerConfig.ciphers.set : [##Tls.Cipher]
|
||||
-> ServerConfig
|
||||
-> ServerConfig
|
||||
327. io2.tls.ServerConfig.versions.set : [##Tls.Version]
|
||||
317. io2.Tls.ServerConfig.versions.set : [##Tls.Version]
|
||||
-> ServerConfig
|
||||
-> ServerConfig
|
||||
328. todo : a -> b
|
||||
318. builtin type io2.Tls.SignedCert
|
||||
319. io2.Tls.decodeCert : Bytes -> Either Failure SignedCert
|
||||
320. io2.Tls.decodePrivateKey : Bytes -> [PrivateKey]
|
||||
321. io2.Tls.encodeCert : SignedCert -> Bytes
|
||||
322. io2.Tls.encodePrivateKey : PrivateKey -> Bytes
|
||||
323. io2.Tls.handshake : Tls ->{IO} Either Failure ()
|
||||
324. io2.Tls.newClient : ClientConfig
|
||||
-> Socket
|
||||
->{IO} Either Failure Tls
|
||||
325. io2.Tls.newServer : ServerConfig
|
||||
-> Socket
|
||||
->{IO} Either Failure Tls
|
||||
326. io2.Tls.receive : Tls ->{IO} Either Failure Bytes
|
||||
327. io2.Tls.send : Tls -> Bytes ->{IO} Either Failure ()
|
||||
328. io2.Tls.terminate : Tls ->{IO} Either Failure ()
|
||||
329. builtin type io2.TlsFailure##TlsFailure
|
||||
330. unique type io2.TlsFailure#o6b
|
||||
331. todo : a -> b
|
||||
|
||||
|
||||
.builtin> alias.many 94-104 .mylib
|
||||
|
@ -51,7 +51,7 @@ The `builtins.merge` command adds the known builtins to a `builtin` subnamespace
|
||||
40. Value/ (5 definitions)
|
||||
41. bug (a -> b)
|
||||
42. crypto/ (12 definitions)
|
||||
43. io2/ (115 definitions)
|
||||
43. io2/ (118 definitions)
|
||||
44. todo (a -> b)
|
||||
|
||||
```
|
||||
|
@ -23,7 +23,7 @@ Technically, the definitions all exist, but they have no names. `builtins.merge`
|
||||
|
||||
.foo> ls
|
||||
|
||||
1. builtin/ (328 definitions)
|
||||
1. builtin/ (331 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/ (491 definitions)
|
||||
1. builtin/ (494 definitions)
|
||||
|
||||
```
|
||||
More typically, you'd start out by pulling `base.
|
||||
|
@ -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.
|
||||
|
||||
⊙ #hdb2qmoob9
|
||||
⊙ #t6bsshdq9e
|
||||
|
||||
- Deletes:
|
||||
|
||||
feature1.y
|
||||
|
||||
⊙ #bg9tk5ai3i
|
||||
⊙ #a52hdge0ur
|
||||
|
||||
+ 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
|
||||
|
||||
⊙ #ak1kamiv9o
|
||||
⊙ #7cn7ulvqt4
|
||||
|
||||
+ Adds / updates:
|
||||
|
||||
feature1.y
|
||||
|
||||
⊙ #o7jv334moc
|
||||
⊙ #icg0klduhn
|
||||
|
||||
> Moves:
|
||||
|
||||
Original name New name
|
||||
x master.x
|
||||
|
||||
⊙ #tab428em20
|
||||
⊙ #0ehm1cc89a
|
||||
|
||||
+ Adds / updates:
|
||||
|
||||
x
|
||||
|
||||
⊙ #s8vqfp4ot8
|
||||
⊙ #fahbg0pqso
|
||||
|
||||
+ Adds / updates:
|
||||
|
||||
@ -273,40 +273,43 @@ We can also delete the fork if we're done with it. (Don't worry, it's still in t
|
||||
builtin.io2.IOError.PermissionDenied
|
||||
builtin.io2.IOError.ResourceBusy
|
||||
builtin.io2.IOError.ResourceExhausted
|
||||
builtin.io2.IOError.UserError builtin.io2.MVar
|
||||
builtin.io2.MVar.isEmpty builtin.io2.MVar.new
|
||||
builtin.io2.MVar.newEmpty builtin.io2.MVar.put
|
||||
builtin.io2.MVar.read builtin.io2.MVar.swap
|
||||
builtin.io2.MVar.take builtin.io2.MVar.tryPut
|
||||
builtin.io2.MVar.tryRead builtin.io2.MVar.tryTake
|
||||
builtin.io2.STM builtin.io2.STM.atomically
|
||||
builtin.io2.STM.retry builtin.io2.SeekMode
|
||||
builtin.io2.SeekMode.AbsoluteSeek
|
||||
builtin.io2.IOError.UserError
|
||||
builtin.io2.IOFailure##IOFailure builtin.io2.IOFailure#gro
|
||||
builtin.io2.MVar builtin.io2.MVar.isEmpty
|
||||
builtin.io2.MVar.new builtin.io2.MVar.newEmpty
|
||||
builtin.io2.MVar.put builtin.io2.MVar.read
|
||||
builtin.io2.MVar.swap builtin.io2.MVar.take
|
||||
builtin.io2.MVar.tryPut builtin.io2.MVar.tryRead
|
||||
builtin.io2.MVar.tryTake builtin.io2.STM
|
||||
builtin.io2.STM.atomically builtin.io2.STM.retry
|
||||
builtin.io2.SeekMode builtin.io2.SeekMode.AbsoluteSeek
|
||||
builtin.io2.SeekMode.RelativeSeek
|
||||
builtin.io2.SeekMode.SeekFromEnd builtin.io2.Socket
|
||||
builtin.io2.StdHandle builtin.io2.StdHandle.StdErr
|
||||
builtin.io2.StdHandle.StdIn builtin.io2.StdHandle.StdOut
|
||||
builtin.io2.TVar builtin.io2.TVar.new
|
||||
builtin.io2.TVar.newIO builtin.io2.TVar.read
|
||||
builtin.io2.TVar.readIO builtin.io2.TVar.swap
|
||||
builtin.io2.TVar.write builtin.io2.ThreadId
|
||||
builtin.io2.Tls builtin.io2.Tls.ClientConfig
|
||||
builtin.io2.TLS.ClientConfig.ciphers.set builtin.io2.TVar
|
||||
builtin.io2.TVar.new builtin.io2.TVar.newIO
|
||||
builtin.io2.TVar.read builtin.io2.TVar.readIO
|
||||
builtin.io2.TVar.swap builtin.io2.TVar.write
|
||||
builtin.io2.ThreadId builtin.io2.Tls
|
||||
builtin.io2.Tls.ClientConfig
|
||||
builtin.io2.Tls.ClientConfig.certificates.set
|
||||
builtin.io2.Tls.ClientConfig.default
|
||||
builtin.io2.Tls.ClientConfig.versions.set
|
||||
builtin.io2.Tls.PrivateKey builtin.io2.Tls.ServerConfig
|
||||
builtin.io2.Tls.ServerConfig.certificates.set
|
||||
builtin.io2.Tls.ServerConfig.ciphers.set
|
||||
builtin.io2.Tls.ServerConfig.default
|
||||
builtin.io2.Tls.ServerConfig.versions.set
|
||||
builtin.io2.Tls.SignedCert builtin.io2.Tls.decodeCert
|
||||
builtin.io2.Tls.decodePrivateKey
|
||||
builtin.io2.Tls.encodeCert
|
||||
builtin.io2.Tls.encodePrivateKey builtin.io2.Tls.handshake
|
||||
builtin.io2.Tls.newClient builtin.io2.Tls.newServer
|
||||
builtin.io2.Tls.receive builtin.io2.Tls.send
|
||||
builtin.io2.Tls.terminate builtin.io2.TlsFailure
|
||||
builtin.io2.tls.ClientConfig.ciphers.set
|
||||
builtin.io2.tls.ClientConfig.versions.set
|
||||
builtin.io2.tls.ServerConfig.ciphers.set
|
||||
builtin.io2.tls.ServerConfig.versions.set builtin.todo
|
||||
builtin.io2.Tls.terminate
|
||||
builtin.io2.TlsFailure##TlsFailure
|
||||
builtin.io2.TlsFailure#o6b builtin.todo
|
||||
|
||||
□ #7asfbtqmoj (start of history)
|
||||
|
||||
|
@ -59,16 +59,16 @@ y = 2
|
||||
most recent, along with the command that got us there. Try:
|
||||
|
||||
`fork 2 .old`
|
||||
`fork #c2isrgss72 .old` to make an old namespace
|
||||
`fork #28ghl51r6b .old` to make an old namespace
|
||||
accessible again,
|
||||
|
||||
`reset-root #c2isrgss72` to reset the root namespace and
|
||||
`reset-root #28ghl51r6b` to reset the root namespace and
|
||||
its history to that of the
|
||||
specified namespace.
|
||||
|
||||
1. #2a6716f77m : add
|
||||
2. #c2isrgss72 : add
|
||||
3. #s8vqfp4ot8 : builtins.merge
|
||||
1. #j6opirfedr : add
|
||||
2. #28ghl51r6b : add
|
||||
3. #fahbg0pqso : builtins.merge
|
||||
4. #7asfbtqmoj : (initial reflogged namespace)
|
||||
|
||||
```
|
||||
|
@ -13,7 +13,7 @@ Let's look at some examples. We'll start with a namespace with just the builtins
|
||||
|
||||
|
||||
|
||||
□ #dkeu9bg399 (start of history)
|
||||
□ #e0t0e4fjhb (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.
|
||||
|
||||
⊙ #gieeiaclmr
|
||||
⊙ #unvfioknvd
|
||||
|
||||
> Moves:
|
||||
|
||||
Original name New name
|
||||
Nat.frobnicate Nat.+
|
||||
|
||||
⊙ #8oolo648l6
|
||||
⊙ #60qpdkiu69
|
||||
|
||||
> Moves:
|
||||
|
||||
Original name New name
|
||||
Nat.+ Nat.frobnicate
|
||||
|
||||
□ #dkeu9bg399 (start of history)
|
||||
□ #e0t0e4fjhb (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.
|
||||
|
||||
⊙ #gieeiaclmr
|
||||
⊙ #unvfioknvd
|
||||
|
||||
> Moves:
|
||||
|
||||
Original name New name
|
||||
Nat.frobnicate Nat.+
|
||||
|
||||
⊙ #8oolo648l6
|
||||
⊙ #60qpdkiu69
|
||||
|
||||
> Moves:
|
||||
|
||||
Original name New name
|
||||
Nat.+ Nat.frobnicate
|
||||
|
||||
□ #dkeu9bg399 (start of history)
|
||||
□ #e0t0e4fjhb (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
|
||||
|
||||
|
||||
|
||||
□ #dkeu9bg399 (start of history)
|
||||
□ #e0t0e4fjhb (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.
|
||||
|
Loading…
Reference in New Issue
Block a user