[create-pull-request] automated change

This commit is contained in:
aryairani 2024-03-12 18:35:54 +00:00 committed by github-actions[bot]
parent 70b937bc76
commit f88d652383
14 changed files with 62 additions and 55 deletions

View File

@ -8,11 +8,11 @@ import Unison.Codebase.Path (Path)
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.ShortCausalHash (ShortCausalHash)
import Unison.Codebase.ShortCausalHash qualified as SCH
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Project (ProjectAndBranch (..), ProjectBranchName, ProjectName)
import Unison.Share.Types
import Unison.Util.Monoid qualified as Monoid
import qualified Unison.NameSegment as NameSegment
data ReadRepo
= ReadRepoGit ReadGitRepo

View File

@ -2823,10 +2823,12 @@ declareForeigns = do
in pure . Bytes.fromArray . hmac alg $ serializeValueLazy x
declareForeign Untracked "crypto.Ed25519.sign.impl" boxBoxBoxToEFBox
. mkForeign $ pure . signEd25519Wrapper
. mkForeign
$ pure . signEd25519Wrapper
declareForeign Untracked "crypto.Ed25519.verify.impl" boxBoxBoxToEFBool
. mkForeign $ pure . verifyEd25519Wrapper
. mkForeign
$ pure . verifyEd25519Wrapper
let catchAll :: (MonadCatch m, MonadIO m, NFData a) => m a -> m (Either Util.Text.Text a)
catchAll e = do
@ -3433,7 +3435,8 @@ signEd25519Wrapper (secret0, public0, msg0) = case validated of
where
msg = Bytes.toArray msg0 :: ByteString
validated =
(,) <$> Ed25519.secretKey (Bytes.toArray secret0 :: ByteString)
(,)
<$> Ed25519.secretKey (Bytes.toArray secret0 :: ByteString)
<*> Ed25519.publicKey (Bytes.toArray public0 :: ByteString)
errMsg CryptoError_PublicKeySizeInvalid =
@ -3454,7 +3457,8 @@ verifyEd25519Wrapper (public0, msg0, sig0) = case validated of
where
msg = Bytes.toArray msg0 :: ByteString
validated =
(,) <$> Ed25519.publicKey (Bytes.toArray public0 :: ByteString)
(,)
<$> Ed25519.publicKey (Bytes.toArray public0 :: ByteString)
<*> Ed25519.signature (Bytes.toArray sig0 :: ByteString)
errMsg CryptoError_PublicKeySizeInvalid =

View File

@ -1,6 +1,7 @@
module Unison.Syntax.FileParser
( file
) where
( file,
)
where
import Control.Lens
import Control.Monad.Reader (asks, local)

View File

@ -1,10 +1,11 @@
{-# LANGUAGE OverloadedStrings #-}
module Unison.Syntax.TypeParser
( computationType
, valueType
, valueTypeLeaf
) where
( computationType,
valueType,
valueTypeLeaf,
)
where
import Control.Monad.Reader (asks)
import Data.Set qualified as Set

View File

@ -61,7 +61,8 @@ import Unison.Sqlite qualified as Sqlite
import Witch (unsafeFrom)
branchRelativePathToAbsolute :: BranchRelativePath -> Cli Path.Absolute
branchRelativePathToAbsolute brp = resolveBranchRelativePath brp <&> \case
branchRelativePathToAbsolute brp =
resolveBranchRelativePath brp <&> \case
BranchRelativePath.ResolvedLoosePath p -> p
BranchRelativePath.ResolvedBranchRelative projectBranch mRel ->
let projectBranchIds = getIds projectBranch
@ -92,7 +93,6 @@ resolveBranchRelativePath = \case
Left branchName -> That branchName
Right (projectName, branchName) -> These projectName branchName
-- | Get the current project that a user is on.
getCurrentProject :: Cli (Maybe Sqlite.Project)
getCurrentProject = do

View File

@ -43,7 +43,7 @@ import Unison.Referent qualified as Referent
import Unison.Runtime.IOSource qualified as IOSource
import Unison.Syntax.DeclPrinter qualified as DeclPrinter
import Unison.Syntax.HashQualified' qualified as HQ' (toText)
import Unison.Syntax.Name qualified as Name (parseText, nameP, toText)
import Unison.Syntax.Name qualified as Name (nameP, parseText, toText)
import Unison.Syntax.TypePrinter qualified as TypePrinter
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Pretty qualified as Pretty

View File

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{- This module kicks off the Transcript Tests.
It doesn't do the transcript parsing itself.
@ -16,8 +17,8 @@ import System.FilePath
splitFileName,
takeDirectory,
takeExtensions,
(</>),
(<.>),
(</>),
)
import System.IO.CodePage (withCP65001)
import System.IO.Silently (silence)

View File

@ -42,9 +42,9 @@ import Network.HTTP.Client.TLS qualified as HTTP
import Stats (recordRtsStats)
import System.Directory
( canonicalizePath,
exeExtension,
getCurrentDirectory,
removeDirectoryRecursive,
exeExtension
)
import System.Environment (getExecutablePath, getProgName, withArgs)
import System.Exit qualified as Exit
@ -52,8 +52,8 @@ import System.FilePath
( replaceExtension,
takeDirectory,
takeExtension,
(</>),
(<.>),
(</>),
)
import System.IO (stderr)
import System.IO.CodePage (withCP65001)

View File

@ -5,4 +5,3 @@ module Unison.Kind where
import Unison.Prelude
data Kind = Star | Arrow Kind Kind deriving (Eq, Ord, Read, Show, Generic)

View File

@ -42,8 +42,8 @@ import Unison.Server.Types
mayDefaultWidth,
)
import Unison.Symbol (Symbol)
import Unison.Syntax.Name qualified as Name
import Unison.Util.Pretty (Width)
import qualified Unison.Syntax.Name as Name
type FuzzyFindAPI =
"find"

View File

@ -1,11 +1,12 @@
module Unison.Server.NameSearch
( Search(..)
, NameSearch(..)
, hoistSearch
, hoistNameSearch
, applySearch
, SearchType(..)
) where
( Search (..),
NameSearch (..),
hoistSearch,
hoistNameSearch,
applySearch,
SearchType (..),
)
where
import Control.Lens
import Data.List qualified as List