⅄ trunk → 24-02-26-upgrade-tweak

This commit is contained in:
Mitchell Rosen 2024-02-27 12:37:47 -05:00
commit a90c394000
144 changed files with 4006 additions and 3106 deletions

View File

@ -1,4 +1,4 @@
Copyright (c) 2013-2023, Unison Computing, public benefit corp and contributors
Copyright (c) 2013-2024, Unison Computing, public benefit corp and contributors
Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal

View File

@ -34,7 +34,7 @@ verifyDeclFormatHash (ComponentHash hash) (DeclFormat.Decl (DeclFormat.LocallyIn
& Map.toList
& fmap (\(_refId, (v, decl, ())) -> (v, either H2.toDataDecl id $ H2.v2ToH2Decl decl))
& Map.fromList
& H2.hashDecls Name.unsafeFromVar
& H2.hashDecls Name.unsafeParseVar
& \case
Left _err -> Just HH.DeclHashResolutionFailure
Right m ->

View File

@ -117,7 +117,6 @@ v2ToH2Branch V2.Branch {terms, types, patches, children} = do
v2ToH2MdValues :: V2Branch.MdValues -> H2.MdValues
v2ToH2MdValues (V2Branch.MdValues mdMap) =
mdMap
& Map.keysSet
& Set.map v2ToH2Reference
& H2.MdValues

View File

@ -200,8 +200,7 @@ import U.Util.Base32Hex qualified as Base32Hex
import U.Util.Serialization qualified as S
import Unison.Hash qualified as H
import Unison.Hash32 qualified as Hash32
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment qualified as NameSegment
import Unison.NameSegment (NameSegment)
import Unison.Prelude
import Unison.ShortHash (ShortCausalHash (..), ShortNamespaceHash (..))
import Unison.Sqlite
@ -215,11 +214,6 @@ import Unison.Util.Set qualified as Set
debug :: Bool
debug = False
newtype NeedTypeForBuiltinMetadata
= NeedTypeForBuiltinMetadata Text
deriving stock (Show)
deriving anyclass (SqliteExceptionReason)
-- * Database lookups
objectExistsForHash :: H.Hash -> Transaction Bool
@ -558,51 +552,37 @@ s2cBranch (S.Branch.Full.Branch tms tps patches children) =
<*> doPatches patches
<*> doChildren children
where
loadMetadataType :: S.Reference -> Transaction C.Reference
loadMetadataType = \case
C.ReferenceBuiltin tId ->
Q.expectTextCheck tId (Left . NeedTypeForBuiltinMetadata)
C.ReferenceDerived id ->
typeReferenceForTerm id >>= h2cReference
loadTypesForMetadata :: Set S.Reference -> Transaction (Map C.Reference C.Reference)
loadTypesForMetadata rs =
Map.fromList
<$> traverse
(\r -> (,) <$> s2cReference r <*> loadMetadataType r)
(Foldable.toList rs)
doTerms ::
Map Db.TextId (Map S.Referent S.DbMetadataSet) ->
Transaction (Map NameSegment (Map C.Referent (Transaction C.Branch.MdValues)))
doTerms =
Map.bitraverse
(fmap NameSegment . Q.expectText)
Q.expectNameSegment
( Map.bitraverse s2cReferent \case
S.MetadataSet.Inline rs ->
pure $ C.Branch.MdValues <$> loadTypesForMetadata rs
pure $ C.Branch.MdValues <$> Set.traverse s2cReference rs
)
doTypes ::
Map Db.TextId (Map S.Reference S.DbMetadataSet) ->
Transaction (Map NameSegment (Map C.Reference (Transaction C.Branch.MdValues)))
doTypes =
Map.bitraverse
(fmap NameSegment . Q.expectText)
Q.expectNameSegment
( Map.bitraverse s2cReference \case
S.MetadataSet.Inline rs ->
pure $ C.Branch.MdValues <$> loadTypesForMetadata rs
pure $ C.Branch.MdValues <$> Set.traverse s2cReference rs
)
doPatches ::
Map Db.TextId Db.PatchObjectId ->
Transaction (Map NameSegment (PatchHash, Transaction C.Branch.Patch))
doPatches = Map.bitraverse (fmap NameSegment . Q.expectText) \patchId -> do
doPatches = Map.bitraverse Q.expectNameSegment \patchId -> do
h <- PatchHash <$> (Q.expectPrimaryHashByObjectId . Db.unPatchObjectId) patchId
pure (h, expectPatch patchId)
doChildren ::
Map Db.TextId (Db.BranchObjectId, Db.CausalHashId) ->
Transaction (Map NameSegment (C.Branch.CausalBranch Transaction))
doChildren = Map.bitraverse (fmap NameSegment . Q.expectText) \(boId, chId) ->
doChildren = Map.bitraverse Q.expectNameSegment \(boId, chId) ->
C.Causal
<$> Q.expectCausalHash chId
<*> expectValueHashByCausalHashId chId
@ -718,21 +698,21 @@ saveNamespace hh bhId me = do
c2sBranch :: BranchV Transaction -> Transaction DbBranchV
c2sBranch = \case
BranchV2 branch -> do
terms <- Map.bitraverse saveNameSegment (Map.bitraverse c2sReferent c2sMetadata) (branch ^. #terms)
types <- Map.bitraverse saveNameSegment (Map.bitraverse c2sReference c2sMetadata) (branch ^. #types)
patches <- Map.bitraverse saveNameSegment savePatchObjectId (branch ^. #patches)
children <- Map.bitraverse saveNameSegment (saveBranch hh) (branch ^. #children)
terms <- Map.bitraverse Q.saveNameSegment (Map.bitraverse c2sReferent c2sMetadata) (branch ^. #terms)
types <- Map.bitraverse Q.saveNameSegment (Map.bitraverse c2sReference c2sMetadata) (branch ^. #types)
patches <- Map.bitraverse Q.saveNameSegment savePatchObjectId (branch ^. #patches)
children <- Map.bitraverse Q.saveNameSegment (saveBranch hh) (branch ^. #children)
pure (DbBranchV2 S.Branch {terms, types, patches, children})
BranchV3 branch -> do
children <- Map.bitraverse saveNameSegment (saveBranchV3 hh) (branch ^. #children)
terms <- Map.bitraverse saveNameSegment c2sReferent (branch ^. #terms)
types <- Map.bitraverse saveNameSegment c2sReference (branch ^. #types)
children <- Map.bitraverse Q.saveNameSegment (saveBranchV3 hh) (branch ^. #children)
terms <- Map.bitraverse Q.saveNameSegment c2sReferent (branch ^. #terms)
types <- Map.bitraverse Q.saveNameSegment c2sReference (branch ^. #types)
pure (DbBranchV3 S.BranchV3 {children, terms, types})
c2sMetadata :: Transaction C.Branch.MdValues -> Transaction S.Branch.Full.DbMetadataSet
c2sMetadata mm = do
C.Branch.MdValues m <- mm
S.Branch.Full.Inline <$> Set.traverse c2sReference (Map.keysSet m)
S.Branch.Full.Inline <$> Set.traverse c2sReference m
savePatchObjectId :: (PatchHash, Transaction C.Branch.Patch) -> Transaction Db.PatchObjectId
savePatchObjectId (h, mp) = do
@ -740,9 +720,6 @@ saveNamespace hh bhId me = do
patch <- mp
savePatch hh h patch
saveNameSegment :: NameSegment -> Transaction Db.TextId
saveNameSegment = Q.saveText . NameSegment.toText
-- Save just the causal object (i.e. the `causal` row and its associated `causal_parents`). Internal helper shared by
-- `saveBranch` and `saveBranchV3`.
saveCausalObject ::
@ -1068,9 +1045,6 @@ filterTermsByReferentHavingType cTypeRef cTermRefIds =
matches <- Q.filterTermsByReferentHavingType sTypeRef sTermRefIds
traverse s2cReferentId matches
typeReferenceForTerm :: S.Reference.Id -> Transaction S.ReferenceH
typeReferenceForTerm = Q.getTypeReferenceForReferent . C.Referent.RefId
termsMentioningType :: C.Reference -> Transaction (Set C.Referent.Id)
termsMentioningType cTypeRef =
runMaybeT (c2hReference cTypeRef) >>= \case

View File

@ -16,6 +16,10 @@ module U.Codebase.Sqlite.Queries
expectText,
expectTextCheck,
-- ** name segments
saveNameSegment,
expectNameSegment,
-- * hash table
saveHash,
saveHashes,
@ -389,6 +393,8 @@ import Unison.Hash qualified as Hash
import Unison.Hash32 (Hash32)
import Unison.Hash32 qualified as Hash32
import Unison.Hash32.Orphans.Sqlite ()
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Sqlite
import Unison.Util.Alternative qualified as Alternative
@ -646,6 +652,14 @@ loadTextSql h =
WHERE id = :h
|]
saveNameSegment :: NameSegment -> Transaction TextId
saveNameSegment =
saveText . NameSegment.toUnescapedText
expectNameSegment :: TextId -> Transaction NameSegment
expectNameSegment =
fmap NameSegment . expectText
saveHashObject :: HashId -> ObjectId -> HashVersion -> Transaction ()
saveHashObject hId oId version =
execute
@ -4229,7 +4243,7 @@ data JsonParseFailure = JsonParseFailure
deriving anyclass (SqliteExceptionReason)
-- | Get the most recent namespace the user has visited.
expectMostRecentNamespace :: Transaction [Text]
expectMostRecentNamespace :: Transaction [NameSegment]
expectMostRecentNamespace =
queryOneColCheck
[sql|
@ -4238,11 +4252,11 @@ expectMostRecentNamespace =
|]
check
where
check :: Text -> Either JsonParseFailure [Text]
check :: Text -> Either JsonParseFailure [NameSegment]
check bytes =
case Aeson.eitherDecodeStrict (Text.encodeUtf8 bytes) of
Left failure -> Left JsonParseFailure {bytes, failure = Text.pack failure}
Right namespace -> Right namespace
Right namespace -> Right (map NameSegment namespace)
-- | Set the most recent namespace the user has visited.
setMostRecentNamespace :: [Text] -> Transaction ()

View File

@ -29,7 +29,7 @@ type MetadataType = Reference
type MetadataValue = Reference
newtype MdValues = MdValues {unMdValues :: Map MetadataValue MetadataType} deriving (Eq, Ord, Show)
newtype MdValues = MdValues {unMdValues :: Set MetadataValue} deriving (Eq, Ord, Show)
type CausalBranch m = Causal m CausalHash BranchHash (Branch m) (Branch m)

View File

@ -1,63 +1,57 @@
module Unison.NameSegment where
module Unison.NameSegment
( NameSegment (..),
toUnescapedText,
isPrefixOf,
-- * Sentinel name segments
defaultPatchSegment,
docSegment,
libSegment,
)
where
import Data.Text qualified as Text
import Data.Text.Lazy.Builder qualified as Text (Builder)
import Data.Text.Lazy.Builder qualified as Text.Builder
import Unison.Prelude
import Unison.Util.Alphabetical (Alphabetical, compareAlphabetical)
import Unison.Util.Alphabetical (Alphabetical)
-- Represents the parts of a name between the `.`s
newtype NameSegment = NameSegment {toText :: Text}
newtype NameSegment
= NameSegment Text
deriving stock (Eq, Ord, Generic)
instance Alphabetical NameSegment where
compareAlphabetical n1 n2 = compareAlphabetical (toText n1) (toText n2)
-- Split text into segments. A smarter version of `Text.splitOn` that handles
-- the name `.` properly.
segments' :: Text -> [Text]
segments' n = go split
where
split = Text.splitOn "." n
go [] = []
go ("" : "" : z) = "." : go z
go ("" : z) = go z
go (x : y) = x : go y
-- Same as reverse . segments', but produces the output as a
-- lazy list, suitable for suffix-based ordering purposes or
-- building suffix tries. Examples:
--
-- reverseSegments' "foo.bar.baz" => ["baz","bar","foo"]
-- reverseSegments' ".foo.bar.baz" => ["baz","bar","foo"]
-- reverseSegments' ".." => ["."]
-- reverseSegments' "Nat.++" => ["++","Nat"]
-- reverseSegments' "Nat.++.zoo" => ["zoo","++","Nat"]
reverseSegments' :: Text -> [Text]
reverseSegments' = go
where
go "" = []
go t =
let seg0 = Text.takeWhileEnd (/= '.') t
seg = if Text.null seg0 then Text.takeEnd 1 t else seg0
rem = Text.dropEnd (Text.length seg + 1) t
in seg : go rem
isEmpty :: NameSegment -> Bool
isEmpty ns = toText ns == mempty
isPrefixOf :: NameSegment -> NameSegment -> Bool
isPrefixOf n1 n2 = Text.isPrefixOf (toText n1) (toText n2)
toString :: NameSegment -> String
toString = Text.unpack . toText
toTextBuilder :: NameSegment -> Text.Builder
toTextBuilder =
coerce Text.Builder.fromText
deriving newtype (Alphabetical)
instance IsString NameSegment where
fromString = NameSegment . Text.pack
fromString =
NameSegment . Text.pack
instance Show NameSegment where
show = show . toText
show =
Text.unpack . toUnescapedText
-- | Convert a name segment to unescaped text.
--
-- You might use this when storing a name segment as text in a database, where the literal name segment bytes are all
-- that matter. However, you wouldn't use this to display the name segment to a user - that depends on concrete syntax.
-- See Unison.Syntax.NameSegment (or indeed, some actual yet-built interface that abstracts concrete syntax) for that
-- kind of function.
--
-- > toUnescapedText (unsafeFromText ".~") = ".~"
toUnescapedText :: NameSegment -> Text
toUnescapedText =
coerce
isPrefixOf :: NameSegment -> NameSegment -> Bool
isPrefixOf =
coerce Text.isPrefixOf
defaultPatchSegment :: NameSegment
defaultPatchSegment =
"patch"
docSegment :: NameSegment
docSegment =
"doc"
libSegment :: NameSegment
libSegment =
"lib"

View File

@ -1,5 +1,3 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Unison.ShortHash

View File

@ -108,10 +108,13 @@ $ UNISON_READONLY="true" ucm
### `UNISON_ENTITY_VALIDATION`
Enable validation of entities pulled from a codebase server.
Allows disabling validation of entities pulled from a codebase server.
It's generally a good idea to leave this enabled unless you know exactly what you're doing.
Defaults to enabled.
```sh
$ UNISON_ENTITY_VALIDATION="true" ucm
$ UNISON_ENTITY_VALIDATION="false" ucm
```
### Local Codebase Server

View File

@ -11,7 +11,7 @@ import U.Codebase.Causal qualified as Causal
import U.Codebase.HashTags (BranchHash (..))
import Unison.Codebase.Path
import Unison.Codebase.Path qualified as Path
import Unison.Name (libSegment)
import Unison.NameSegment (libSegment)
import Unison.Prelude
import Unison.Sqlite qualified as Sqlite
import Unison.Util.Monoid (ifoldMapM)

View File

@ -38,7 +38,7 @@ import Unison.Prelude
import Unison.Reference qualified as R
import Unison.Referent qualified as Referent
import Unison.Symbol (Symbol)
import Unison.Syntax.Name qualified as Name (unsafeFromText, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (unsafeParseText, unsafeParseVar)
import Unison.Type qualified as Type
import Unison.Typechecker.TypeLookup qualified as TL
import Unison.Util.Relation qualified as Rel
@ -56,24 +56,24 @@ names = Names terms types
terms =
Rel.mapRan Referent.Ref (Rel.fromMap termNameRefs)
<> Rel.fromList
[ (Name.unsafeFromVar vc, Referent.Con (ConstructorReference (R.DerivedId r) cid) ct)
[ (Name.unsafeParseVar vc, Referent.Con (ConstructorReference (R.DerivedId r) cid) ct)
| (ct, (_, (r, decl))) <-
((CT.Data,) <$> builtinDataDecls)
<> ((CT.Effect,) . (second . second) DD.toDataDecl <$> builtinEffectDecls),
((_, vc, _), cid) <- DD.constructors' decl `zip` [0 ..]
]
<> Rel.fromList
[ (Name.unsafeFromVar v, Referent.Ref (R.DerivedId i))
[ (Name.unsafeParseVar v, Referent.Ref (R.DerivedId i))
| (v, i) <- Map.toList TD.builtinTermsRef
]
types =
Rel.fromList builtinTypes
<> Rel.fromList
[ (Name.unsafeFromVar v, R.DerivedId r)
[ (Name.unsafeParseVar v, R.DerivedId r)
| (v, (r, _)) <- builtinDataDecls
]
<> Rel.fromList
[ (Name.unsafeFromVar v, R.DerivedId r)
[ (Name.unsafeParseVar v, R.DerivedId r)
| (v, (r, _)) <- builtinEffectDecls
]
@ -147,7 +147,7 @@ builtinTypeDependentsOfComponent h0 = Rel.searchRan ord builtinDependencies
-- if we decide to change their names.
builtinTypes :: [(Name, R.Reference)]
builtinTypes =
Map.toList . Map.mapKeys Name.unsafeFromText $
Map.toList . Map.mapKeys Name.unsafeParseText $
foldl' go mempty builtinTypesSrc
where
go m = \case
@ -286,7 +286,7 @@ instance Show BuiltinDSL where
show _ = ""
termNameRefs :: Map Name R.Reference
termNameRefs = Map.mapKeys Name.unsafeFromText $ foldl' go mempty (stripVersion builtinsSrc)
termNameRefs = Map.mapKeys Name.unsafeParseText $ foldl' go mempty (stripVersion builtinsSrc)
where
go m = \case
B r _tp -> Map.insert r (R.Builtin r) m
@ -704,6 +704,7 @@ builtinsSrc =
++ moveUnder "io2" stmBuiltins
++ moveUnder "io2" refPromiseBuiltins
++ hashBuiltins
++ cryptoBuiltins
++ fmap (uncurry B) codeBuiltins
moveUnder :: Text -> [(Text, Type)] -> [BuiltinDSL]
@ -761,6 +762,14 @@ hashBuiltins =
hashAlgo = Type.ref () Type.hashAlgorithmRef
h name = B ("crypto.HashAlgorithm." <> name) hashAlgo
cryptoBuiltins :: [BuiltinDSL]
cryptoBuiltins =
[ B "crypto.Ed25519.sign.impl" $
bytes --> bytes --> bytes --> eithert failure bytes,
B "crypto.Ed25519.verify.impl" $
bytes --> bytes --> bytes --> eithert failure boolean
]
ioBuiltins :: [(Text, Type)]
ioBuiltins =
[ ("IO.openFile.impl.v3", text --> fmode --> iof handle),

View File

@ -48,6 +48,7 @@ eitherRef = lookupDeclRef "Either"
testResultRef, linkRef, docRef, ioErrorRef, stdHandleRef :: Reference
failureRef, ioFailureRef, tlsFailureRef, arrayFailureRef :: Reference
cryptoFailureRef :: Reference
exceptionRef, tlsSignedCertRef, tlsPrivateKeyRef :: Reference
isPropagatedRef, isTestRef :: Reference
isPropagatedRef = lookupDeclRef "IsPropagated"
@ -74,6 +75,8 @@ tlsFailureRef = lookupDeclRef "io2.TlsFailure"
arrayFailureRef = lookupDeclRef "io2.ArrayFailure"
cryptoFailureRef = lookupDeclRef "crypto.CryptoFailure"
tlsSignedCertRef = lookupDeclRef "io2.Tls.SignedCert"
tlsPrivateKeyRef = lookupDeclRef "io2.Tls.PrivateKey"
@ -267,6 +270,7 @@ builtinDataDecls = rs1 ++ rs
(v "io2.MiscFailure", miscFailure),
(v "io2.STMFailure", stmFailure),
(v "io2.ThreadKilledFailure", threadKilledFailure),
(v "crypto.CryptoFailure", cryptoFailure),
(v "RewriteTerm", rewriteTerm),
(v "RewriteSignature", rewriteType),
(v "RewriteCase", rewriteCase),
@ -508,6 +512,13 @@ builtinDataDecls = rs1 ++ rs
[]
[]
cryptoFailure =
DataDeclaration
(Unique "09132bf0cc3f07db75be127d141da91fdd545adcff88866268dfd428e9879742")
()
[]
[]
stdhnd =
DataDeclaration
(Unique "67bf7a8e517cbb1e9f42bc078e35498212d3be3c")

View File

@ -124,6 +124,7 @@ import Unison.Hashing.V2.Convert qualified as H
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment)
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude hiding (empty)
import Unison.Reference (TermReference, TypeReference)
import Unison.Referent (Referent)
@ -133,7 +134,7 @@ import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Relation qualified as R
import Unison.Util.Relation qualified as Relation
import Unison.Util.Set qualified as Set
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
import Witherable (FilterableWithIndex (imapMaybe))
import Prelude hiding (head, read, subtract)
@ -155,7 +156,7 @@ withoutLib Branch0 {..} =
_children
& imapMaybe
( \nameSegment child ->
if nameSegment == Name.libSegment
if nameSegment == NameSegment.libSegment
then Nothing
else Just (child & head_ %~ withoutLib)
)
@ -169,7 +170,7 @@ withoutTransitiveLibs Branch0 {..} =
_children
& imapMaybe
( \nameSegment child ->
if nameSegment == Name.libSegment
if nameSegment == NameSegment.libSegment
then Just (child & head_ %~ withoutLib)
else Just (child & head_ %~ withoutTransitiveLibs)
)
@ -178,12 +179,12 @@ withoutTransitiveLibs Branch0 {..} =
-- | @deleteLibdep name branch@ deletes the libdep named @name@ from @branch@, if it exists.
deleteLibdep :: NameSegment -> Branch0 m -> Branch0 m
deleteLibdep dep =
over (children . ix Name.libSegment . head_ . children) (Map.delete dep)
over (children . ix NameSegment.libSegment . head_ . children) (Map.delete dep)
-- | @deleteLibdeps branch@ deletes all libdeps from @branch@.
deleteLibdeps :: Branch0 m -> Branch0 m
deleteLibdeps =
over children (Map.delete Name.libSegment)
over children (Map.delete NameSegment.libSegment)
deepReferents :: Branch0 m -> Set Referent
deepReferents = R.dom . deepTerms
@ -243,8 +244,8 @@ branch0 terms types children edits =
_children = children,
_edits = edits,
isEmpty0 =
R.null (Star3.d1 terms)
&& R.null (Star3.d1 types)
R.null (Star2.d1 terms)
&& R.null (Star2.d1 types)
&& Map.null edits
&& all (isEmpty0 . head) children,
-- These are all overwritten immediately
@ -280,7 +281,7 @@ deriveDeepTerms branch =
terms =
map
(second (Name.fromReverseSegments . (NonEmpty.:| reversePrefix)))
(R.toList (Star3.d1 (_terms b0)))
(R.toList (Star2.d1 (_terms b0)))
children <- deepChildrenHelper e
go (work <> children) (terms <> acc)
@ -299,7 +300,7 @@ deriveDeepTypes branch =
go Seq.Empty acc = pure acc
go (e@(reversePrefix, _, b0) Seq.:<| work) acc = do
let types :: [(TypeReference, Name)]
types = map (second (Name.fromReverseSegments . (NonEmpty.:| reversePrefix))) (R.toList (Star3.d1 (_types b0)))
types = map (second (Name.fromReverseSegments . (NonEmpty.:| reversePrefix))) (R.toList (Star2.d1 (_types b0)))
children <- deepChildrenHelper e
go (work <> children) (types <> acc)
@ -362,7 +363,7 @@ deepChildrenHelper (reversePrefix, libDepth, b0) = do
pure
if isShallowDependency || isUnseenNamespace
then
let libDepth' = if ns == "lib" then libDepth + 1 else libDepth
let libDepth' = if ns == NameSegment.libSegment then libDepth + 1 else libDepth
in Seq.singleton (ns : reversePrefix, libDepth', head b)
else Seq.empty
State.modify' (Set.insert h)
@ -690,28 +691,28 @@ batchUpdatesM (toList -> actions) curBranch = foldM execActions curBranch (group
-- todo: consider inlining these into Actions2
addTermName :: Referent -> NameSegment -> Branch0 m -> Branch0 m
addTermName r new =
over terms (Star3.insertD1 (r, new))
over terms (Star2.insertD1 (r, new))
addTypeName :: TypeReference -> NameSegment -> Branch0 m -> Branch0 m
addTypeName r new =
over types (Star3.insertD1 (r, new))
over types (Star2.insertD1 (r, new))
deleteTermName :: Referent -> NameSegment -> Branch0 m -> Branch0 m
deleteTermName r n b
| Star3.memberD1 (r, n) (view terms b) =
over terms (Star3.deletePrimaryD1 (r, n)) b
| Star2.memberD1 (r, n) (view terms b) =
over terms (Star2.deletePrimaryD1 (r, n)) b
deleteTermName _ _ b = b
annihilateTermName :: NameSegment -> Branch0 m -> Branch0 m
annihilateTermName = over terms . Star3.deleteD1
annihilateTermName = over terms . Star2.deleteD1
annihilateTypeName :: NameSegment -> Branch0 m -> Branch0 m
annihilateTypeName = over types . Star3.deleteD1
annihilateTypeName = over types . Star2.deleteD1
deleteTypeName :: TypeReference -> NameSegment -> Branch0 m -> Branch0 m
deleteTypeName r n b
| Star3.memberD1 (r, n) (view types b) =
over types (Star3.deletePrimaryD1 (r, n)) b
| Star2.memberD1 (r, n) (view types b) =
over types (Star2.deletePrimaryD1 (r, n)) b
deleteTypeName _ _ b = b
lca :: (Monad m) => Branch m -> Branch m -> m (Maybe (Branch m))

View File

@ -9,7 +9,7 @@ import Unison.Codebase.Patch qualified as Patch
import Unison.NameSegment (NameSegment)
import Unison.Reference (Reference)
import Unison.Referent (Referent)
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
type Star r n = Metadata.Star r n
@ -38,10 +38,10 @@ diff0 old new = do
oldEdits
pure $
BranchDiff
{ addedTerms = Star3.difference (_terms new) (_terms old),
removedTerms = Star3.difference (_terms old) (_terms new),
addedTypes = Star3.difference (_types new) (_types old),
removedTypes = Star3.difference (_types old) (_types new),
{ addedTerms = Star2.difference (_terms new) (_terms old),
removedTerms = Star2.difference (_terms old) (_terms new),
addedTypes = Star2.difference (_types new) (_types old),
removedTypes = Star2.difference (_types old) (_types new),
changedPatches = diffEdits
}

View File

@ -33,7 +33,7 @@ import Unison.Hashing.V2.Convert qualified as H
import Unison.Prelude hiding (empty)
import Unison.Util.Map (unionWithM)
import Unison.Util.Relation qualified as R
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
import Prelude hiding (head, read, subtract)
data MergeMode = RegularMerge | SquashMerge deriving (Eq, Ord, Show)
@ -91,8 +91,8 @@ merge'' lca mode (Branch x) (Branch y) =
in (PatchHash (H.hashPatch p), pure p)
pure $
branch0
(Star3.difference (_terms b0) removedTerms <> addedTerms)
(Star3.difference (_types b0) removedTypes <> addedTypes)
(Star2.difference (_terms b0) removedTerms <> addedTerms)
(Star2.difference (_types b0) removedTypes <> addedTypes)
(_children b0)
(patches <> newPatches)
patchMerge mhp Patch.PatchDiff {..} = Just $ do

View File

@ -37,7 +37,7 @@ import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.ShortHash qualified as SH
import Unison.Util.Relation qualified as R
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
-- | Creates a branch containing all of the given names, with a single history node.
fromNames :: (Monad m) => Names -> Branch m
@ -50,16 +50,16 @@ fromNames names0 = Branch.stepManyAt (typeActions <> termActions) Branch.empty
getTerm :: Path.HQSplit -> Branch0 m -> Set Referent
getTerm (p, hq) b = case hq of
NameOnly n -> Star3.lookupD1 n terms
HashQualified n sh -> filter sh $ Star3.lookupD1 n terms
NameOnly n -> Star2.lookupD1 n terms
HashQualified n sh -> filter sh $ Star2.lookupD1 n terms
where
filter sh = Set.filter (SH.isPrefixOf sh . Referent.toShortHash)
terms = Branch._terms (Branch.getAt0 p b)
getType :: Path.HQSplit -> Branch0 m -> Set Reference.TypeReference
getType (p, hq) b = case hq of
NameOnly n -> Star3.lookupD1 n types
HashQualified n sh -> filter sh $ Star3.lookupD1 n types
NameOnly n -> Star2.lookupD1 n types
HashQualified n sh -> filter sh $ Star2.lookupD1 n types
where
filter sh = Set.filter (SH.isPrefixOf sh . Reference.toShortHash)
types = Branch._types (Branch.getAt0 p b)

View File

@ -12,6 +12,7 @@ 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
@ -131,7 +132,7 @@ data ReadShareLooseCode = ReadShareLooseCode
isPublic :: ReadShareLooseCode -> Bool
isPublic ReadShareLooseCode {path} =
case path of
("public" Path.:< _) -> True
((NameSegment.toUnescapedText -> "public") Path.:< _) -> True
_ -> False
data WriteRemoteNamespace a

View File

@ -1,7 +1,3 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PartialTypeSignatures #-}
-- | Execute a computation of type '{IO} () that has been previously added to
-- the codebase, without setting up an interactive environment.
--
@ -20,6 +16,7 @@ import Unison.Codebase.Runtime (Runtime)
import Unison.Codebase.Runtime qualified as Runtime
import Unison.Names qualified as Names
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.PrettyPrintEnv qualified as PPE
import Unison.Symbol (Symbol)
import Unison.Util.Pretty qualified as P
@ -27,7 +24,7 @@ import Unison.Util.Pretty qualified as P
execute ::
Codebase.Codebase IO Symbol Ann ->
Runtime Symbol ->
String ->
Text ->
IO (Either Runtime.Error ())
execute codebase runtime mainName =
(`finally` Runtime.terminate runtime) . runExceptT $ do
@ -37,9 +34,9 @@ execute codebase runtime mainName =
let mainType = Runtime.mainType runtime
mt <- liftIO $ Codebase.runTransaction codebase $ getMainTerm loadTypeOfTerm parseNames mainName mainType
case mt of
MainTerm.NotAFunctionName s -> throwError ("Not a function name: " <> P.string s)
MainTerm.NotFound s -> throwError ("Not found: " <> P.string s)
MainTerm.BadType s _ -> throwError (P.string s <> " is not of type '{IO} ()")
MainTerm.NotAFunctionName s -> throwError ("Not a function name: " <> P.text s)
MainTerm.NotFound s -> throwError ("Not found: " <> P.text s)
MainTerm.BadType s _ -> throwError (P.text s <> " is not of type '{IO} ()")
MainTerm.Success _ tm _ -> do
let codeLookup = Codebase.toCodeLookup codebase
ppe = PPE.empty

View File

@ -16,7 +16,7 @@ import Unison.Parser.Ann qualified as Parser.Ann
import Unison.Prelude
import Unison.Reference (Reference)
import Unison.Referent qualified as Referent
import Unison.Syntax.HashQualified qualified as HQ (fromString)
import Unison.Syntax.HashQualified qualified as HQ (parseText)
import Unison.Term (Term)
import Unison.Term qualified as Term
import Unison.Type (Type)
@ -26,20 +26,20 @@ import Unison.Var (Var)
import Unison.Var qualified as Var
data MainTerm v
= NotAFunctionName String
| NotFound String
| BadType String (Maybe (Type v Ann))
= NotAFunctionName Text
| NotFound Text
| BadType Text (Maybe (Type v Ann))
| Success (HQ.HashQualified Name) (Term v Ann) (Type v Ann)
getMainTerm ::
(Monad m, Var v) =>
(Reference -> m (Maybe (Type v Ann))) ->
Names.Names ->
String ->
Text ->
Type.Type v Ann ->
m (MainTerm v)
getMainTerm loadTypeOfTerm parseNames mainName mainType =
case HQ.fromString mainName of
case HQ.parseText mainName of
Nothing -> pure (NotAFunctionName mainName)
Just hq -> do
let refs = Names.lookupHQTerm Names.IncludeSuffixes hq parseNames

View File

@ -1,39 +1,24 @@
module Unison.Codebase.Metadata
( Star,
Type,
Value,
insert,
delete,
)
where
import Data.Map qualified as Map
import Unison.Prelude
import Unison.Reference (Reference)
import Unison.Util.List qualified as List
import Unison.Util.Relation qualified as R
import Unison.Util.Star3 (Star3)
import Unison.Util.Star3 qualified as Star3
import Unison.Reference (TermReference)
import Unison.Util.Star2 (Star2)
import Unison.Util.Star2 qualified as Star2
type Type = Reference
type Value = Reference
type Value = TermReference
-- `a` is generally the type of references or hashes
-- `n` is generally the the type of name associated with the references
-- `Type` is the type of metadata. Duplicate info to speed up certain queries.
-- `(Type, Value)` is the metadata value itself along with its type.
type Star a n = Star3 a n Type (Type, Value)
-- `Value` is the metadata value itself.
type Star a n = Star2 a n Value
insert :: (Ord a, Ord n) => (a, Type, Value) -> Star a n -> Star a n
insert (a, ty, v) = Star3.insertD23 (a, ty, (ty, v))
insert :: (Ord a, Ord n) => (a, Value) -> Star a n -> Star a n
insert (a, v) = Star2.insertD2 (a, v)
delete :: (Ord a, Ord n) => (a, Type, Value) -> Star a n -> Star a n
delete (a, ty, v) s =
let s' = Star3.deleteD3 (a, (ty, v)) s
-- if (ty,v) is the last metadata of type ty
-- we also delete (a, ty) from the d2 index
metadataByType = List.multimap (toList (R.lookupDom a (Star3.d3 s)))
in case Map.lookup ty metadataByType of
Just vs | all (== v) vs -> Star3.deleteD2 (a, ty) s'
_ -> s'
delete :: (Ord a, Ord n) => (a, Value) -> Star a n -> Star a n
delete (a, v) s = Star2.deleteD2 (a, v) s

View File

@ -45,8 +45,8 @@ module Unison.Codebase.Path
fromName,
fromName',
fromPath',
fromText,
fromText',
unsafeParseText,
unsafeParseText',
toAbsoluteSplit,
toSplit',
toList,
@ -54,7 +54,6 @@ module Unison.Codebase.Path
toName',
unsafeToName,
unsafeToName',
toPath',
toText,
toText',
unsplit,
@ -65,6 +64,7 @@ module Unison.Codebase.Path
-- * things that could be replaced with `Parse` instances
splitFromName,
splitFromName',
hqSplitFromName',
-- * things that could be replaced with `Cons` instances
@ -91,12 +91,10 @@ import GHC.Exts qualified as GHC
import Unison.HashQualified' qualified as HQ'
import Unison.Name (Convert (..), Name, Parse)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment qualified as NameSegment
import Unison.NameSegment (NameSegment)
import Unison.Prelude hiding (empty, toList)
import Unison.Syntax.Name qualified as Name (toString, unsafeFromText)
import Unison.Syntax.Name qualified as Name (toText, unsafeParseText)
import Unison.Util.List qualified as List
import Unison.Util.Monoid (intercalateMap)
-- `Foo.Bar.baz` becomes ["Foo", "Bar", "baz"]
newtype Path = Path {toSeq :: Seq NameSegment}
@ -225,12 +223,6 @@ relativeEmpty' = RelativePath' (Relative empty)
absoluteEmpty' :: Path'
absoluteEmpty' = AbsolutePath' (Absolute empty)
-- | Mitchell: this function is bogus, because an empty name segment is bogus
toPath' :: Path -> Path'
toPath' = \case
Path (NameSegment "" :<| tail) -> AbsolutePath' . Absolute . Path $ tail
p -> Path' . Right . Relative $ p
-- Forget whether the path is absolute or relative
fromPath' :: Path' -> Path
fromPath' = \case
@ -256,9 +248,19 @@ hqSplitFromName' = fmap (fmap HQ'.fromName) . Lens.unsnoc . fromName'
-- >>> splitFromName "foo"
-- (,foo)
splitFromName :: Name -> Split
splitFromName name =
splitFromName =
over _1 fromPath' . splitFromName'
splitFromName' :: Name -> Split'
splitFromName' name =
case Name.reverseSegments name of
(seg :| pathSegments) -> (fromList $ reverse pathSegments, seg)
(seg :| pathSegments) ->
let path = fromList (reverse pathSegments)
in ( if Name.isAbsolute name
then AbsolutePath' (Absolute path)
else RelativePath' (Relative path),
seg
)
-- | Remove a path prefix from a name.
-- Returns 'Nothing' if there are no remaining segments to construct the name from.
@ -302,19 +304,20 @@ fromName :: Name -> Path
fromName = fromList . List.NonEmpty.toList . Name.segments
fromName' :: Name -> Path'
fromName' n = case take 1 (Name.toString n) of
"." -> AbsolutePath' . Absolute $ Path seq
_ -> RelativePath' $ Relative path
fromName' n
| Name.isAbsolute n = AbsolutePath' (Absolute path)
| otherwise = RelativePath' (Relative path)
where
path = fromName n
seq = toSeq path
unsafeToName :: Path -> Name
unsafeToName = Name.unsafeFromText . toText
unsafeToName =
fromMaybe (error "empty path") . toName
-- | Convert a Path' to a Name
unsafeToName' :: Path' -> Name
unsafeToName' = Name.unsafeFromText . toText'
unsafeToName' =
fromMaybe (error "empty path") . toName'
toName :: Path -> Maybe Name
toName = \case
@ -347,12 +350,13 @@ instance Show Path where
-- | Note: This treats the path as relative.
toText :: Path -> Text
toText (Path nss) = intercalateMap "." NameSegment.toText nss
toText =
maybe Text.empty Name.toText . toName
fromText :: Text -> Path
fromText = \case
unsafeParseText :: Text -> Path
unsafeParseText = \case
"" -> empty
t -> fromList $ NameSegment <$> NameSegment.segments' t
text -> fromName (Name.unsafeParseText text)
-- | Construct a Path' from a text
--
@ -364,17 +368,17 @@ fromText = \case
--
-- >>> show $ fromText' ""
-- ""
fromText' :: Text -> Path'
fromText' txt =
case Text.uncons txt of
Nothing -> relativeEmpty'
Just ('.', p) -> AbsolutePath' . Absolute $ fromText p
Just _ -> RelativePath' . Relative $ fromText txt
unsafeParseText' :: Text -> Path'
unsafeParseText' = \case
"" -> RelativePath' (Relative mempty)
"." -> AbsolutePath' (Absolute mempty)
text -> fromName' (Name.unsafeParseText text)
toText' :: Path' -> Text
toText' = \case
AbsolutePath' (Absolute path) -> Text.cons '.' (toText path)
RelativePath' (Relative path) -> toText path
toText' path =
case toName' path of
Nothing -> if isAbsolute path then "." else ""
Just name -> Name.toText name
{-# COMPLETE Empty, (:<) #-}
@ -523,7 +527,8 @@ instance Convert HQSplit (HQ'.HashQualified Path) where convert = unsplitHQ
instance Convert HQSplit' (HQ'.HashQualified Path') where convert = unsplitHQ'
instance Convert Name Split where convert = splitFromName
instance Convert Name Split where
convert = splitFromName
instance Convert (path, NameSegment) (path, HQ'.HQSegment) where
convert (path, name) =

View File

@ -1,167 +1,104 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Unison.Codebase.Path.Parse
( parsePath',
parsePathImpl',
( -- * Path parsing functions
parsePath,
parsePath',
parseSplit,
parseSplit',
definitionNameSegment,
parseHQSplit,
parseHQSplit',
parseShortHashOrHQSplit',
wordyNameSegment,
-- * Path parsers
pathP,
pathP',
splitP,
splitP',
)
where
import Control.Lens (over, _1)
import Control.Lens qualified as Lens
import Data.List.Extra (stripPrefix)
import Data.Text qualified as Text
import Text.Megaparsec (Parsec)
import Text.Megaparsec qualified as P
import Text.Megaparsec.Char qualified as P (char)
import Text.Megaparsec.Internal qualified as P (withParsecT)
import Unison.Codebase.Path
import Unison.HashQualified' qualified as HQ'
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude hiding (empty, toList)
import Unison.ShortHash (ShortHash)
import Unison.ShortHash qualified as SH
import Unison.Syntax.Lexer qualified as Lexer
import Unison.Syntax.Name qualified as Name
import Unison.Syntax.NameSegment qualified as NameSegment (renderParseErr)
import Unison.Syntax.ShortHash qualified as ShortHash
-- .libs.blah.poo is Absolute
-- libs.blah.poo is Relative
-- Left is some parse error tbd
parsePath' :: String -> Either String Path'
parsePath' p = case parsePathImpl' p of
Left e -> Left e
Right (p, "") -> Right p
Right (p, rem) -> case parseSegment rem of
Right (seg, "") -> Right (unsplit' (p, NameSegment . Text.pack $ seg))
Right (_, rem) ->
Left ("extra characters after " <> show p <> ": " <> show rem)
Left e -> Left e
------------------------------------------------------------------------------------------------------------------------
-- Path parsing functions
-- implementation detail of parsePath' and parseSplit'
-- foo.bar.baz.34 becomes `Right (foo.bar.baz, "34")
-- foo.bar.baz becomes `Right (foo.bar, "baz")
-- baz becomes `Right (, "baz")
-- foo.bar.baz#a8fj becomes `Left`; we don't hash-qualify paths.
-- TODO: Get rid of this thing.
parsePathImpl' :: String -> Either String (Path', String)
parsePathImpl' p = case p of
"." -> Right (Path' . Left $ absoluteEmpty, "")
'.' : p -> over _1 (Path' . Left . Absolute . fromList) <$> segs p
p -> over _1 (Path' . Right . Relative . fromList) <$> segs p
where
go f p = case f p of
Right (a, "") -> case Lens.unsnoc (NameSegment.segments' $ Text.pack a) of
Nothing -> Left "empty path"
Just (segs, last) -> Right (NameSegment <$> segs, Text.unpack last)
Right (segs, '.' : rem) ->
let segs' = NameSegment.segments' (Text.pack segs)
in Right (NameSegment <$> segs', rem)
Right (segs, rem) ->
Left $ "extra characters after " <> segs <> ": " <> show rem
Left e -> Left e
segs p = go parseSegment p
parsePath :: String -> Either Text Path
parsePath =
runParser pathP
parseSegment :: String -> Either String (String, String)
parseSegment s =
first show
. (Lexer.wordyId <> Lexer.symbolyId)
<> unit'
<> const (Left ("I expected an identifier but found " <> s))
$ s
parsePath' :: String -> Either Text Path'
parsePath' = \case
"" -> Right relativeEmpty'
"." -> Right absoluteEmpty'
path -> unsplit' <$> parseSplit' path
wordyNameSegment, definitionNameSegment :: String -> Either String NameSegment
wordyNameSegment s = case Lexer.wordyId0 s of
Left e -> Left (show e)
Right (a, "") -> Right (NameSegment (Text.pack a))
Right (a, rem) ->
Left $ "trailing characters after " <> show a <> ": " <> show rem
parseSplit :: String -> Either Text Split
parseSplit =
runParser splitP
-- Parse a name segment like "()"
unit' :: String -> Either String (String, String)
unit' s = case stripPrefix "()" s of
Nothing -> Left $ "Expected () but found: " <> s
Just rem -> Right ("()", rem)
parseSplit' :: String -> Either Text Split'
parseSplit' =
runParser splitP'
unit :: String -> Either String NameSegment
unit s = case unit' s of
Right (_, "") -> Right $ NameSegment "()"
Right (_, rem) -> Left $ "trailing characters after (): " <> show rem
Left _ -> Left $ "I don't know how to parse " <> s
parseShortHashOrHQSplit' :: String -> Either Text (Either ShortHash HQSplit')
parseShortHashOrHQSplit' =
runParser shortHashOrHqSplitP'
definitionNameSegment s = wordyNameSegment s <> symbolyNameSegment s <> unit s
where
symbolyNameSegment s = case Lexer.symbolyId0 s of
Left e -> Left (show e)
Right (a, "") -> Right (NameSegment (Text.pack a))
Right (a, rem) ->
Left $ "trailing characters after " <> show a <> ": " <> show rem
parseHQSplit :: String -> Either Text HQSplit
parseHQSplit s =
parseHQSplit' s >>= \case
(RelativePath' (Relative p), hqseg) -> Right (p, hqseg)
_ -> Left $ "Sorry, you can't use an absolute name like " <> Text.pack s <> " here."
-- parseSplit' wordyNameSegment "foo.bar.baz" returns Right (foo.bar, baz)
-- parseSplit' wordyNameSegment "foo.bar.+" returns Left err
-- parseSplit' definitionNameSegment "foo.bar.+" returns Right (foo.bar, +)
parseSplit' ::
(String -> Either String NameSegment) ->
String ->
Either String Split'
parseSplit' lastSegment p = do
(p', rem) <- parsePathImpl' p
seg <- lastSegment rem
pure (p', seg)
parseHQSplit' :: String -> Either Text HQSplit'
parseHQSplit' =
runParser hqSplitP'
parseShortHashOrHQSplit' :: String -> Either String (Either ShortHash HQSplit')
parseShortHashOrHQSplit' s =
case Text.breakOn "#" $ Text.pack s of
("", "") -> error $ "encountered empty string parsing '" <> s <> "'"
(n, "") -> do
(p, rem) <- parsePathImpl' (Text.unpack n)
seg <- definitionNameSegment rem
pure $ Right (p, HQ'.NameOnly seg)
("", sh) -> do
sh <- maybeToRight (shError s) . SH.fromText $ sh
pure $ Left sh
(n, sh) -> do
(p, rem) <- parsePathImpl' (Text.unpack n)
seg <- definitionNameSegment rem
hq <-
maybeToRight (shError s)
. fmap (\sh -> (p, HQ'.HashQualified seg sh))
. SH.fromText
$ sh
pure $ Right hq
where
shError s = "couldn't parse shorthash from " <> s
runParser :: Parsec (Lexer.Token Text) [Char] a -> String -> Either Text a
runParser p =
mapLeft (Text.pack . P.errorBundlePretty) . P.runParser (p <* P.eof) ""
parseHQSplit :: String -> Either String HQSplit
parseHQSplit s = case parseHQSplit' s of
Right (Path' (Right (Relative p)), hqseg) -> Right (p, hqseg)
Right (Path' Left {}, _) ->
Left $ "Sorry, you can't use an absolute name like " <> s <> " here."
Left e -> Left e
------------------------------------------------------------------------------------------------------------------------
-- Path parsers
parseHQSplit' :: String -> Either String HQSplit'
parseHQSplit' s = case Text.breakOn "#" $ Text.pack s of
("", "") -> error $ "encountered empty string parsing '" <> s <> "'"
("", _) -> Left "Sorry, you can't use a hash-only reference here."
(n, "") -> do
(p, rem) <- parsePath n
seg <- definitionNameSegment rem
pure (p, HQ'.NameOnly seg)
(n, sh) -> do
(p, rem) <- parsePath n
seg <- definitionNameSegment rem
maybeToRight (shError s)
. fmap (\sh -> (p, HQ'.HashQualified seg sh))
. SH.fromText
$ sh
where
shError s = "couldn't parse shorthash from " <> s
parsePath n = do
x <- parsePathImpl' $ Text.unpack n
pure $ case x of
(Path' (Left e), "") | e == absoluteEmpty -> (relativeEmpty', ".")
x -> x
pathP :: Parsec (Lexer.Token Text) [Char] Path
pathP =
(unsplit <$> splitP) <|> pure empty
pathP' :: Parsec (Lexer.Token Text) [Char] Path'
pathP' =
asum
[ unsplit' <$> splitP',
P.char '.' $> absoluteEmpty',
pure relativeEmpty'
]
splitP :: Parsec (Lexer.Token Text) [Char] Split
splitP =
splitFromName <$> P.withParsecT (fmap NameSegment.renderParseErr) Name.relativeNameP
splitP' :: Parsec (Lexer.Token Text) [Char] Split'
splitP' =
splitFromName' <$> P.withParsecT (fmap NameSegment.renderParseErr) Name.nameP
shortHashOrHqSplitP' :: Parsec (Lexer.Token Text) [Char] (Either ShortHash HQSplit')
shortHashOrHqSplitP' =
Left <$> ShortHash.shortHashP <|> Right <$> hqSplitP'
hqSplitP' :: Parsec (Lexer.Token Text) [Char] HQSplit'
hqSplitP' = do
(segs, seg) <- splitP'
P.optional (P.withParsecT (fmap ("invalid hash: " <>)) ShortHash.shortHashP) <&> \case
Nothing -> (segs, HQ'.fromName seg)
Just hash -> (segs, HQ'.HashQualified seg hash)

View File

@ -23,7 +23,7 @@ import Unison.Reference (Reference, pattern Derived)
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Util.Relation qualified as R
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
type Branches m = [(CausalHash, m (Branch m))]
@ -67,9 +67,9 @@ fromBranch0 b =
fromChildren :: (Applicative m) => Map NameSegment (Branch m) -> Branches m
fromChildren m = [(Branch.headHash b, pure b) | b <- toList m]
references :: Branch.Star r NameSegment -> [r]
references = toList . R.dom . Star3.d1
references = toList . R.dom . Star2.d1
mdValues :: Branch.Star r NameSegment -> [Reference]
mdValues = fmap snd . toList . R.ran . Star3.d3
mdValues = toList . R.ran . Star2.d2
fromTermsStar :: Branch.Star Referent NameSegment -> Dependencies
fromTermsStar s = Dependencies mempty terms decls
where

View File

@ -51,7 +51,7 @@ import Unison.Term qualified as V1.Term
import Unison.Type qualified as V1.Type
import Unison.Util.Map qualified as Map
import Unison.Util.Relation qualified as Relation
import Unison.Util.Star3 qualified as V1.Star3
import Unison.Util.Star2 qualified as V1.Star2
import Unison.Var qualified as Var
import Unison.WatchKind qualified as V1.WK
@ -435,13 +435,12 @@ causalbranch1to2 (V1.Branch.Branch c) =
doTerms s =
Map.fromList
[ (ns, m2)
| ns <- toList . Relation.ran $ V1.Star3.d1 s,
| ns <- toList . Relation.ran $ V1.Star2.d1 s,
let m2 =
Map.fromList
[ (referent1to2 r, pure md)
| r <- toList . Relation.lookupRan ns $ V1.Star3.d1 s,
let mdrefs1to2 (typeR1, valR1) = (reference1to2 valR1, reference1to2 typeR1)
md = V2.Branch.MdValues . Map.fromList . map mdrefs1to2 . toList . Relation.lookupDom r $ V1.Star3.d3 s
| r <- toList . Relation.lookupRan ns $ V1.Star2.d1 s,
let md = V2.Branch.MdValues . Set.map reference1to2 . Relation.lookupDom r $ V1.Star2.d2 s
]
]
@ -449,13 +448,12 @@ causalbranch1to2 (V1.Branch.Branch c) =
doTypes s =
Map.fromList
[ (ns, m2)
| ns <- toList . Relation.ran $ V1.Star3.d1 s,
| ns <- toList . Relation.ran $ V1.Star2.d1 s,
let m2 =
Map.fromList
[ (reference1to2 r, pure md)
| r <- toList . Relation.lookupRan ns $ V1.Star3.d1 s,
let mdrefs1to2 (typeR1, valR1) = (reference1to2 valR1, reference1to2 typeR1)
md = V2.Branch.MdValues . Map.fromList . map mdrefs1to2 . toList . Relation.lookupDom r $ V1.Star3.d3 s
| r <- toList . Relation.lookupRan ns $ V1.Star2.d1 s,
let md = V2.Branch.MdValues . Set.map reference1to2 . Relation.lookupDom r $ V1.Star2.d2 s
]
]
@ -529,11 +527,9 @@ branch2to1 branchCache lookupCT (V2.Branch.Branch v2terms v2types v2patches v2ch
insert' name star (ref, V2.Branch.MdValues mdvals) =
let facts = Set.singleton ref
names = Relation.singleton ref name
types :: Relation.Relation ref V1.Metadata.Type =
Relation.insertManyRan ref (fmap mdref2to1 (Map.elems mdvals)) mempty
vals :: Relation.Relation ref (V1.Metadata.Type, V1.Metadata.Value) =
Relation.insertManyRan ref (fmap (\(v, t) -> (mdref2to1 t, mdref2to1 v)) (Map.toList mdvals)) mempty
in star <> V1.Star3.Star3 facts names types vals
vals :: Relation.Relation ref V1.Metadata.Value =
Relation.insertManyRan ref (map mdref2to1 (Set.toList mdvals)) mempty
in star <> V1.Star2.Star2 facts names vals
-- | Generates a v1 short hash from a v2 referent.
-- Also shortens the hash to the provided length. If 'Nothing', it will include the full

View File

@ -27,6 +27,7 @@ import Unison.Reference qualified as Reference
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Result qualified as Result
import Unison.Syntax.Var qualified as Var (namespaced)
import Unison.Term qualified as Term
import Unison.Type qualified as Type
import Unison.Typechecker qualified as Typechecker
@ -83,7 +84,7 @@ hashFieldAccessors ::
)
hashFieldAccessors ppe declName vars declRef dd = do
let accessors :: [(v, (), Term.Term v ())]
accessors = DD.generateRecordAccessors mempty (map (,()) vars) declName declRef
accessors = DD.generateRecordAccessors Var.namespaced mempty (map (,()) vars) declName declRef
let typeLookup :: TypeLookup v ()
typeLookup =
TypeLookup

View File

@ -26,7 +26,7 @@ import Unison.Reference (Reference)
import Unison.Referent qualified as Referent
import Unison.Result (CompilerBug (..), Note (..), ResultT, pattern Result)
import Unison.Result qualified as Result
import Unison.Syntax.Name qualified as Name (toText, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toText, unsafeParseVar)
import Unison.Syntax.Parser qualified as Parser
import Unison.Term qualified as Term
import Unison.Type qualified as Type
@ -96,7 +96,7 @@ computeTypecheckingEnvironment shouldUseTndr ambientAbilities typeLookupf uf =
[ (Name.toText name, Var.name v, r)
| (name, r) <- Rel.toList (Names.terms preexistingNames),
v <- Set.toList (Term.freeVars tm),
name `Name.endsWithReverseSegments` List.NonEmpty.toList (Name.reverseSegments (Name.unsafeFromVar v))
name `Name.endsWithReverseSegments` List.NonEmpty.toList (Name.reverseSegments (Name.unsafeParseVar v))
]
possibleRefs = Referent.toReference . view _3 <$> possibleDeps
tl <- fmap (UF.declsToTypeLookup uf <>) (typeLookupf (UF.dependencies uf <> Set.fromList possibleRefs))
@ -122,7 +122,7 @@ computeTypecheckingEnvironment shouldUseTndr ambientAbilities typeLookupf uf =
[ (Var.name v, nr)
| (name, r) <- Rel.toList (Names.terms $ UF.toNames uf),
v <- Set.toList (Term.freeVars tm),
name `Name.endsWithReverseSegments` List.NonEmpty.toList (Name.reverseSegments (Name.unsafeFromVar v)),
name `Name.endsWithReverseSegments` List.NonEmpty.toList (Name.reverseSegments (Name.unsafeParseVar v)),
typ <- toList $ TL.typeOfReferent tl r,
let nr = Typechecker.NamedReference (Name.toText name) typ (Right r)
]

View File

@ -45,12 +45,12 @@ import Unison.Names.ResolutionResult (ResolutionResult)
import Unison.Pattern qualified as Memory.Pattern
import Unison.Reference qualified as Memory.Reference
import Unison.Referent qualified as Memory.Referent
import Unison.Syntax.Name qualified as Name (unsafeFromVar)
import Unison.Syntax.Name qualified as Name (unsafeParseVar)
import Unison.Term qualified as Memory.Term
import Unison.Type qualified as Memory.Type
import Unison.Util.Map qualified as Map
import Unison.Util.Relation qualified as Relation
import Unison.Util.Star3 qualified as Memory.Star3
import Unison.Util.Star2 qualified as Memory.Star2
import Unison.Var (Var)
typeToReference :: (Var v) => Memory.Type.Type v a -> Memory.Reference.Reference
@ -230,7 +230,7 @@ hashDataDecls ::
ResolutionResult v a [(v, Memory.Reference.Id, Memory.DD.DataDeclaration v a)]
hashDataDecls memDecls = do
let hashingDecls = fmap m2hDecl memDecls
hashingResult <- Hashing.hashDecls Name.unsafeFromVar hashingDecls
hashingResult <- Hashing.hashDecls Name.unsafeParseVar hashingDecls
pure $ map h2mDeclResult hashingResult
where
h2mDeclResult :: (Ord v) => (v, Hashing.ReferenceId, Hashing.DataDeclaration v a) -> (v, Memory.Reference.Id, Memory.DD.DataDeclaration v a)
@ -374,13 +374,12 @@ m2hBranch0 b =
doTerms s =
Map.fromList
[ (m2hNameSegment ns, m2)
| ns <- toList . Relation.ran $ Memory.Star3.d1 s,
| ns <- toList . Relation.ran $ Memory.Star2.d1 s,
let m2 =
Map.fromList
[ (fst (Writer.runWriter (m2hReferent r)), md)
| r <- toList . Relation.lookupRan ns $ Memory.Star3.d1 s,
let mdrefs1to2 (_typeR1, valR1) = m2hReference valR1
md = Hashing.MdValues . Set.map mdrefs1to2 . Relation.lookupDom r $ Memory.Star3.d3 s
| r <- toList . Relation.lookupRan ns $ Memory.Star2.d1 s,
let md = Hashing.MdValues . Set.map m2hReference . Relation.lookupDom r $ Memory.Star2.d2 s
]
]
@ -390,14 +389,13 @@ m2hBranch0 b =
doTypes s =
Map.fromList
[ (m2hNameSegment ns, m2)
| ns <- toList . Relation.ran $ Memory.Star3.d1 s,
| ns <- toList . Relation.ran $ Memory.Star2.d1 s,
let m2 =
Map.fromList
[ (m2hReference r, md)
| r <- toList . Relation.lookupRan ns $ Memory.Star3.d1 s,
let mdrefs1to2 (_typeR1, valR1) = m2hReference valR1
md :: Hashing.MdValues
md = Hashing.MdValues . Set.map mdrefs1to2 . Relation.lookupDom r $ Memory.Star3.d3 s
| r <- toList . Relation.lookupRan ns $ Memory.Star2.d1 s,
let md :: Hashing.MdValues
md = Hashing.MdValues . Set.map m2hReference . Relation.lookupDom r $ Memory.Star2.d2 s
]
]
@ -412,4 +410,5 @@ m2hBranch0 b =
doChildren = Map.bimap m2hNameSegment (unCausalHash . Memory.Branch.headHash)
m2hNameSegment :: Memory.NameSegment.NameSegment -> Hashing.NameSegment
m2hNameSegment (Memory.NameSegment.NameSegment s) = Hashing.NameSegment s
m2hNameSegment =
Hashing.NameSegment . Memory.NameSegment.toUnescapedText

View File

@ -4,7 +4,7 @@ import Data.Map qualified as Map
import Unison.HashQualified qualified as HQ
import Unison.Name (Name)
import Unison.Prelude
import Unison.Syntax.Name qualified as Name (unsafeFromText)
import Unison.Syntax.Name qualified as Name (unsafeParseText)
-- Type aliases relating to Fully-Qualified Names, e.g. 'Acme.API.foo'
-- Used primarily by the FQN elision code - see TermPrinter.PrintAnnotation.
@ -25,7 +25,7 @@ elideFQN imports hq =
let hash = HQ.toHash hq
name' = do
name <- HQ.toName hq
let hit = fmap Name.unsafeFromText (Map.lookup name imports)
let hit = fmap Name.unsafeParseText (Map.lookup name imports)
-- Cut out the "const id $" to get tracing of FQN elision attempts.
let t = const id $ trace ("hit: " ++ show hit ++ " finding: " ++ show hq ++ " in imports: " ++ show imports)
t (pure $ fromMaybe name hit)

View File

@ -39,7 +39,6 @@ import Unison.Kind qualified as Kind
import Unison.KindInference.Error.Pretty (prettyKindError)
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (..))
import Unison.Names qualified as Names
import Unison.Names.ResolutionResult qualified as Names
import Unison.Parser.Ann (Ann (..))
@ -53,7 +52,7 @@ import Unison.Result (Note (..))
import Unison.Result qualified as Result
import Unison.Settings qualified as Settings
import Unison.Symbol (Symbol)
import Unison.Syntax.HashQualified qualified as HQ (toString)
import Unison.Syntax.HashQualified qualified as HQ (toText)
import Unison.Syntax.Lexer qualified as L
import Unison.Syntax.Name qualified as Name (toText)
import Unison.Syntax.NamePrinter (prettyHashQualified0)
@ -1223,15 +1222,15 @@ renderKind Kind.Star = "*"
renderKind (Kind.Arrow k1 k2) = renderKind k1 <> " -> " <> renderKind k2
showTermRef :: (IsString s) => Env -> Referent -> s
showTermRef env r = fromString . HQ.toString $ PPE.termName env r
showTermRef env r = fromString . Text.unpack . HQ.toText $ PPE.termName env r
showTypeRef :: (IsString s) => Env -> R.Reference -> s
showTypeRef env r = fromString . HQ.toString $ PPE.typeName env r
showTypeRef env r = fromString . Text.unpack . HQ.toText $ PPE.typeName env r
-- todo: do something different/better if cid not found
showConstructor :: (IsString s) => Env -> ConstructorReference -> s
showConstructor env r =
fromString . HQ.toString $
fromString . Text.unpack . HQ.toText $
PPE.patternName env r
_posToEnglish :: (IsString s) => L.Pos -> s
@ -1679,7 +1678,7 @@ renderParseErrors s = \case
else unknownTypesMsg <> "\n\n" <> dupDataAndAbilitiesMsg
in (msgs, allRanges)
go (Parser.DidntExpectExpression _tok (Just t@(L.payload -> L.SymbolyId (HQ'.NameOnly name))))
| name == Name.fromSegment (NameSegment "::") =
| name == Name.fromSegment "::" =
let msg =
mconcat
[ "This looks like the start of an expression here but I was expecting a binding.",
@ -1783,10 +1782,10 @@ renderParseErrors s = \case
let msg =
Pr.lines
[ if missing
then "I couldn't resolve the reference " <> style ErrorSite (HQ.toString (L.payload tok)) <> "."
else "The reference " <> style ErrorSite (HQ.toString (L.payload tok)) <> " was ambiguous.",
then "I couldn't resolve the reference " <> style ErrorSite (Text.unpack (HQ.toText (L.payload tok))) <> "."
else "The reference " <> style ErrorSite (Text.unpack (HQ.toText (L.payload tok))) <> " was ambiguous.",
"",
tokenAsErrorSite s $ HQ.toString <$> tok,
tokenAsErrorSite s $ HQ.toText <$> tok,
if missing
then "Make sure it's spelled correctly."
else "Try hash-qualifying the term you meant to reference."
@ -1798,10 +1797,10 @@ renderParseErrors s = \case
let msg =
Pr.lines
[ if Set.null referents
then "I couldn't find a term for " <> style ErrorSite (HQ.toString (L.payload tok)) <> "."
else "The term reference " <> style ErrorSite (HQ.toString (L.payload tok)) <> " was ambiguous.",
then "I couldn't find a term for " <> style ErrorSite (Text.unpack (HQ.toText (L.payload tok))) <> "."
else "The term reference " <> style ErrorSite (Text.unpack (HQ.toText (L.payload tok))) <> " was ambiguous.",
"",
tokenAsErrorSite s $ HQ.toString <$> tok,
tokenAsErrorSite s $ HQ.toText <$> tok,
if missing
then "Make sure it's spelled correctly."
else "Try hash-qualifying the term you meant to reference."
@ -1813,10 +1812,10 @@ renderParseErrors s = \case
let msg =
Pr.lines
[ if Set.null referents
then "I couldn't find a type for " <> style ErrorSite (HQ.toString (L.payload tok)) <> "."
else "The type reference " <> style ErrorSite (HQ.toString (L.payload tok)) <> " was ambiguous.",
then "I couldn't find a type for " <> style ErrorSite (Text.unpack (HQ.toText (L.payload tok))) <> "."
else "The type reference " <> style ErrorSite (Text.unpack (HQ.toText (L.payload tok))) <> " was ambiguous.",
"",
tokenAsErrorSite s $ HQ.toString <$> tok,
tokenAsErrorSite s $ HQ.toText <$> tok,
if missing
then "Make sure it's spelled correctly."
else "Try hash-qualifying the type you meant to reference."

View File

@ -8,6 +8,8 @@ module Unison.Project.Util
projectContextFromPath,
pattern UUIDNameSegment,
ProjectContext (..),
pattern ProjectsNameSegment,
pattern BranchesNameSegment,
)
where
@ -18,6 +20,7 @@ import Data.UUID qualified as UUID
import U.Codebase.Sqlite.DbId (ProjectBranchId (..), ProjectId (..))
import Unison.Codebase.Path qualified as Path
import Unison.NameSegment (NameSegment (..))
import Unison.NameSegment qualified as NameSegment
import Unison.Project (ProjectAndBranch (..))
-- | Get the path that a project is stored at. Users aren't supposed to go here.
@ -34,7 +37,7 @@ projectPath projectId =
-- .__projects._ABCD.branches
projectBranchesPath :: ProjectId -> Path.Absolute
projectBranchesPath projectId =
snoc (projectPath projectId) "branches"
snoc (projectPath projectId) BranchesNameSegment
-- | Get the path that a branch is stored at. Users aren't supposed to go here.
--
@ -54,9 +57,12 @@ projectBranchSegment (ProjectBranchId branchId) =
pattern UUIDNameSegment :: UUID -> NameSegment
pattern UUIDNameSegment uuid <-
NameSegment (Text.uncons -> Just ('_', UUID.fromText . Text.map (\c -> if c == '_' then '-' else c) -> Just uuid))
( NameSegment.toUnescapedText ->
(Text.uncons -> Just ('_', UUID.fromText . Text.map (\c -> if c == '_' then '-' else c) -> Just uuid))
)
where
UUIDNameSegment uuid = NameSegment (Text.cons '_' (Text.map (\c -> if c == '-' then '_' else c) (UUID.toText uuid)))
UUIDNameSegment uuid =
NameSegment (Text.cons '_' (Text.map (\c -> if c == '-' then '_' else c) (UUID.toText uuid)))
-- | The prism between paths like
--
@ -75,16 +81,12 @@ projectPathPrism =
where
toPath :: ProjectId -> Path.Absolute
toPath projectId =
Path.Absolute $
Path.fromList
[ "__projects",
UUIDNameSegment (unProjectId projectId)
]
Path.Absolute (Path.fromList [ProjectsNameSegment, UUIDNameSegment (unProjectId projectId)])
toId :: Path.Absolute -> Maybe ProjectId
toId path =
case Path.toList (Path.unabsolute path) of
["__projects", UUIDNameSegment projectId] -> Just (ProjectId projectId)
[ProjectsNameSegment, UUIDNameSegment projectId] -> Just (ProjectId projectId)
_ -> Nothing
-- | The prism between paths like
@ -106,9 +108,9 @@ projectBranchPathPrism =
toPath (ProjectAndBranch {project = projectId, branch = branchId}, restPath) =
Path.Absolute $
Path.fromList
( [ "__projects",
( [ ProjectsNameSegment,
UUIDNameSegment (unProjectId projectId),
"branches",
BranchesNameSegment,
UUIDNameSegment (unProjectBranchId branchId)
]
++ Path.toList restPath
@ -117,7 +119,7 @@ projectBranchPathPrism =
toIds :: Path.Absolute -> Maybe (ProjectAndBranch ProjectId ProjectBranchId, Path.Path)
toIds path =
case Path.toList (Path.unabsolute path) of
"__projects" : UUIDNameSegment projectId : "branches" : UUIDNameSegment branchId : restPath ->
ProjectsNameSegment : UUIDNameSegment projectId : BranchesNameSegment : UUIDNameSegment branchId : restPath ->
Just (ProjectAndBranch {project = ProjectId projectId, branch = ProjectBranchId branchId}, Path.fromList restPath)
_ -> Nothing
@ -136,3 +138,23 @@ projectContextFromPath path =
ProjectBranchPath projectId branchId restPath
Nothing ->
LooseCodePath path
pattern ProjectsNameSegment :: NameSegment
pattern ProjectsNameSegment <-
((== projectsNameSegment) -> True)
where
ProjectsNameSegment = projectsNameSegment
pattern BranchesNameSegment :: NameSegment
pattern BranchesNameSegment <-
((== branchesNameSegment) -> True)
where
BranchesNameSegment = branchesNameSegment
projectsNameSegment :: NameSegment
projectsNameSegment =
"__projects"
branchesNameSegment :: NameSegment
branchesNameSegment =
"branches"

View File

@ -101,7 +101,7 @@ import Unison.ConstructorReference (ConstructorReference, GConstructorReference
import Unison.Hashing.V2.Convert (hashTermComponentsWithoutTypes)
import Unison.Pattern (SeqOp (..))
import Unison.Pattern qualified as P
import Unison.Prelude hiding (Text)
import Unison.Prelude
import Unison.Reference (Id, Reference, Reference' (Builtin, DerivedId))
import Unison.Referent (Referent, pattern Con, pattern Ref)
import Unison.Symbol (Symbol)
@ -621,11 +621,11 @@ saturate dat = ABT.visitPure $ \case
fvs = foldMap freeVars args
args' = saturate dat <$> args
addDefaultCases :: (Var v) => (Monoid a) => String -> Term v a -> Term v a
addDefaultCases :: (Var v) => (Monoid a) => Text -> Term v a -> Term v a
addDefaultCases = ABT.visitPure . defaultCaseVisitor
defaultCaseVisitor ::
(Var v) => (Monoid a) => String -> Term v a -> Maybe (Term v a)
(Var v) => (Monoid a) => Text -> Term v a -> Maybe (Term v a)
defaultCaseVisitor func m@(Match' scrut cases)
| scrut <- addDefaultCases func scrut,
cases <- fmap (addDefaultCases func) <$> cases =
@ -634,7 +634,7 @@ defaultCaseVisitor func m@(Match' scrut cases)
a = ABT.annotation m
v = Var.freshIn mempty $ typed Var.Blank
txt = "pattern match failure in function `" <> func <> "`"
msg = text a $ Data.Text.pack txt
msg = text a txt
bu = ref a (Builtin "bug")
dflt =
MatchCase (P.Var a) Nothing

View File

@ -35,8 +35,10 @@ import Control.Monad.Catch (MonadCatch)
import Control.Monad.Primitive qualified as PA
import Control.Monad.Reader (ReaderT (..), ask, runReaderT)
import Control.Monad.State.Strict (State, execState, modify)
import Crypto.Error (CryptoError(..), CryptoFailable(..))
import Crypto.Hash qualified as Hash
import Crypto.MAC.HMAC qualified as HMAC
import Crypto.PubKey.Ed25519 qualified as Ed25519
import Crypto.Random (getRandomBytes)
import Data.Bits (shiftL, shiftR, (.|.))
import Data.ByteArray qualified as BA
@ -1400,6 +1402,8 @@ outMaybeTup a b u bp ap result =
)
]
-- Note: the Io part doesn't really do anything. There's no actual
-- representation of `IO`.
outIoFail :: forall v. (Var v) => v -> v -> v -> v -> v -> v -> ANormal v
outIoFail stack1 stack2 stack3 any fail result =
TMatch result . MatchSum $
@ -1830,6 +1834,14 @@ boxBoxToEFBool =
where
(arg1, arg2, stack1, stack2, stack3, bool, fail, result) = fresh
-- a -> b -> c -> Either Failure Bool
boxBoxBoxToEFBool :: ForeignOp
boxBoxBoxToEFBool =
inBxBxBx arg1 arg2 arg3 result $
outIoFailBool stack1 stack2 stack3 bool fail result
where
(arg1, arg2, arg3, stack1, stack2, stack3, bool, fail, result) = fresh
-- a -> Either Failure ()
boxToEF0 :: ForeignOp
boxToEF0 =
@ -1870,6 +1882,14 @@ boxBoxToEFBox =
where
(arg1, arg2, result, stack1, stack2, stack3, any, fail) = fresh
-- a -> b -> c -> Either Failure d
boxBoxBoxToEFBox :: ForeignOp
boxBoxBoxToEFBox =
inBxBxBx arg1 arg2 arg3 result $
outIoFail stack1 stack2 stack3 any fail result
where
(arg1, arg2, arg3, result, stack1, stack2, stack3, any, fail) = fresh
-- Nat -> a
-- Nat only
natToBox :: ForeignOp
@ -2802,6 +2822,12 @@ declareForeigns = do
$ L.toChunks s
in pure . Bytes.fromArray . hmac alg $ serializeValueLazy x
declareForeign Untracked "crypto.Ed25519.sign.impl" boxBoxBoxToEFBox
. mkForeign $ pure . signEd25519Wrapper
declareForeign Untracked "crypto.Ed25519.verify.impl" boxBoxBoxToEFBool
. mkForeign $ pure . verifyEd25519Wrapper
let catchAll :: (MonadCatch m, MonadIO m, NFData a) => m a -> m (Either Util.Text.Text a)
catchAll e = do
e <- Exception.tryAnyDeep e
@ -3397,6 +3423,48 @@ hostPreference :: Maybe Util.Text.Text -> SYS.HostPreference
hostPreference Nothing = SYS.HostAny
hostPreference (Just host) = SYS.Host $ Util.Text.unpack host
signEd25519Wrapper ::
(Bytes.Bytes, Bytes.Bytes, Bytes.Bytes) -> Either Failure Bytes.Bytes
signEd25519Wrapper (secret0, public0, msg0) = case validated of
CryptoFailed err ->
Left (Failure Ty.cryptoFailureRef (errMsg err) unitValue)
CryptoPassed (secret, public) ->
Right . Bytes.fromArray $ Ed25519.sign secret public msg
where
msg = Bytes.toArray msg0 :: ByteString
validated =
(,) <$> Ed25519.secretKey (Bytes.toArray secret0 :: ByteString)
<*> Ed25519.publicKey (Bytes.toArray public0 :: ByteString)
errMsg CryptoError_PublicKeySizeInvalid =
"ed25519: Public key size invalid"
errMsg CryptoError_SecretKeySizeInvalid =
"ed25519: Secret key size invalid"
errMsg CryptoError_SecretKeyStructureInvalid =
"ed25519: Secret key structure invalid"
errMsg _ = "ed25519: unexpected error"
verifyEd25519Wrapper ::
(Bytes.Bytes, Bytes.Bytes, Bytes.Bytes) -> Either Failure Bool
verifyEd25519Wrapper (public0, msg0, sig0) = case validated of
CryptoFailed err ->
Left $ Failure Ty.cryptoFailureRef (errMsg err) unitValue
CryptoPassed (public, sig) ->
Right $ Ed25519.verify public msg sig
where
msg = Bytes.toArray msg0 :: ByteString
validated =
(,) <$> Ed25519.publicKey (Bytes.toArray public0 :: ByteString)
<*> Ed25519.signature (Bytes.toArray sig0 :: ByteString)
errMsg CryptoError_PublicKeySizeInvalid =
"ed25519: Public key size invalid"
errMsg CryptoError_SecretKeySizeInvalid =
"ed25519: Secret key size invalid"
errMsg CryptoError_SecretKeyStructureInvalid =
"ed25519: Secret key structure invalid"
errMsg _ = "ed25519: unexpected error"
typeReferences :: [(Reference, Word64)]
typeReferences = zip rs [1 ..]
where

View File

@ -109,7 +109,7 @@ import Unison.Runtime.Pattern
import Unison.Runtime.Serialize as SER
import Unison.Runtime.Stack
import Unison.Symbol (Symbol)
import Unison.Syntax.HashQualified qualified as HQ (toString)
import Unison.Syntax.HashQualified qualified as HQ (toText)
import Unison.Syntax.NamePrinter (prettyHashQualified)
import Unison.Syntax.TermPrinter
import Unison.Term qualified as Tm
@ -529,7 +529,7 @@ intermediateTerms ppe ctx rtms =
. splitPatterns (dspec ctx)
. addDefaultCases tmName
where
tmName = HQ.toString . termName ppe $ RF.Ref ref
tmName = HQ.toText . termName ppe $ RF.Ref ref
where
orig =
Map.fromList
@ -597,7 +597,7 @@ intermediateTerm ppe ctx tm =
case normalizeTerm ctx tm of
(ref, frem, cmbs, dcmp) -> (ref, frem, fmap f cmbs, dcmp)
where
tmName = HQ.toString . termName ppe $ RF.Ref ref
tmName = HQ.toText . termName ppe $ RF.Ref ref
f =
superNormalize
. splitPatterns (dspec ctx)

View File

@ -5,6 +5,7 @@ where
import Control.Lens
import Control.Monad.Reader (MonadReader (..))
import Data.List.NonEmpty (pattern (:|))
import Data.List.NonEmpty qualified as NonEmpty
import Data.Map qualified as Map
import Text.Megaparsec qualified as P
@ -15,14 +16,15 @@ import Unison.Name qualified as Name
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.Syntax.Lexer qualified as L
import Unison.Syntax.Name qualified as Name (toText, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toText, unsafeParseVar)
import Unison.Syntax.Parser
import Unison.Syntax.TermParser qualified as TermParser
import Unison.Syntax.TypeParser qualified as TypeParser
import Unison.Syntax.Var qualified as Var (namespaced)
import Unison.Type (Type)
import Unison.Type qualified as Type
import Unison.Var (Var)
import Unison.Var qualified as Var
import Unison.Var qualified as Var (name, named)
import Prelude hiding (readFile)
-- The parsed form of record accessors, as in:
@ -99,7 +101,7 @@ resolveUnresolvedModifier unresolvedModifier var =
resolveUniqueModifier :: (Monad m, Var v) => v -> Text -> P v m DD.Modifier
resolveUniqueModifier var guid0 = do
ParsingEnv {uniqueTypeGuid} <- ask
guid <- fromMaybe guid0 <$> lift (lift (uniqueTypeGuid (Name.unsafeFromVar var)))
guid <- fromMaybe guid0 <$> lift (lift (uniqueTypeGuid (Name.unsafeParseVar var)))
pure $ DD.Unique guid
defaultUniqueModifier :: (Monad m, Var v) => v -> P v m DD.Modifier
@ -162,7 +164,7 @@ dataDeclaration maybeUnresolvedModifier = do
ctorAnn = ann ctorName <> maybe (ann ctorName) ann (lastMay ctorArgs)
in ( ctorAnn,
( ann ctorName,
Var.namespaced [L.payload name, L.payload ctorName],
Var.namespaced (L.payload name :| [L.payload ctorName]),
Type.foralls ctorAnn typeArgVs ctorType
)
)
@ -182,7 +184,7 @@ dataDeclaration maybeUnresolvedModifier = do
)
fields <- field
closingToken <- closeBlock
let lastSegment = name <&> (\v -> Var.named (Name.toText $ Name.unqualified (Name.unsafeFromVar v)))
let lastSegment = name <&> (\v -> Var.named (Name.toText $ Name.unqualified (Name.unsafeParseVar v)))
pure ([go lastSegment (snd <$> fields)], [(name, fields)], ann closingToken)
(constructors, accessors, closingAnn) <-
msum [Left <$> record, Right <$> sepBy (reserved "|") dataConstructor] <&> \case
@ -263,7 +265,7 @@ effectDeclaration maybeUnresolvedModifier = do
<$> TypeParser.computationType
)
where
explodeToken v t = (ann v, Var.namespaced [L.payload name, L.payload v], t)
explodeToken v t = (ann v, Var.namespaced (L.payload name :| [L.payload v]), t)
-- If the effect is not syntactically present in the constructor types,
-- add them after parsing.
ensureEffect t = case t of

View File

@ -1,15 +1,12 @@
module Unison.Syntax.DeclPrinter (prettyDecl, prettyDeclW, prettyDeclHeader, prettyDeclOrBuiltinHeader, AccessorName) where
import Control.Monad.Writer (Writer, runWriter, tell)
import Data.List (isPrefixOf)
import Data.List.NonEmpty (pattern (:|))
import Data.Map qualified as Map
import Data.Text qualified as Text
import Unison.ConstructorReference (ConstructorReference, GConstructorReference (..))
import Unison.ConstructorType qualified as CT
import Unison.DataDeclaration
( DataDeclaration,
EffectDeclaration,
toDataDecl,
)
import Unison.DataDeclaration (DataDeclaration, EffectDeclaration, toDataDecl)
import Unison.DataDeclaration qualified as DD
import Unison.DataDeclaration.Dependencies qualified as DD
import Unison.HashQualified qualified as HQ
@ -21,16 +18,17 @@ import Unison.PrettyPrintEnvDecl (PrettyPrintEnvDecl (..))
import Unison.PrettyPrintEnvDecl qualified as PPED
import Unison.Reference (Reference, Reference' (DerivedId))
import Unison.Referent qualified as Referent
import Unison.Syntax.HashQualified qualified as HQ (toString, toVar, unsafeFromString)
import Unison.Syntax.HashQualified qualified as HQ (toText, toVar, unsafeParseText)
import Unison.Syntax.NamePrinter (styleHashQualified'')
import Unison.Syntax.TypePrinter (runPretty)
import Unison.Syntax.TypePrinter qualified as TypePrinter
import Unison.Syntax.Var qualified as Var (namespaced)
import Unison.Type qualified as Type
import Unison.Util.Pretty (Pretty)
import Unison.Util.Pretty qualified as P
import Unison.Util.SyntaxText qualified as S
import Unison.Var (Var)
import Unison.Var qualified as Var
import Unison.Var qualified as Var (freshenId, name, named)
type SyntaxText = S.SyntaxText' Reference
@ -83,7 +81,7 @@ prettyGADT env ctorType r name dd =
constructor (n, (_, _, t)) =
prettyPattern (PPED.unsuffixifiedPPE env) ctorType name (ConstructorReference r n)
<> fmt S.TypeAscriptionColon " :"
`P.hang` TypePrinter.prettySyntax (PPED.suffixifiedPPE env) t
`P.hang` TypePrinter.prettySyntax (PPED.suffixifiedPPE env) t
header = prettyEffectHeader name (DD.EffectDeclaration dd) <> fmt S.ControlKeyword " where"
prettyPattern ::
@ -115,9 +113,9 @@ prettyDataDecl (PrettyPrintEnvDecl unsuffixifiedPPE suffixifiedPPE) r name dd =
(header <>)
. P.sep (fmt S.DelimiterChar (" | " `P.orElse` "\n | "))
<$> constructor
`traverse` zip
[0 ..]
(DD.constructors' dd)
`traverse` zip
[0 ..]
(DD.constructors' dd)
where
constructor (n, (_, _, Type.ForallsNamed' _ t)) = constructor' n t
constructor (n, (_, _, t)) = constructor' n t
@ -136,7 +134,7 @@ prettyDataDecl (PrettyPrintEnvDecl unsuffixifiedPPE suffixifiedPPE) r name dd =
Just accessor -> HQ.NameOnly $ declName `Name.joinDot` fieldName `Name.joinDot` accessor
| HQ.NameOnly declName <- [name],
HQ.NameOnly fieldName <- fs,
accessor <- [Nothing, Just "set", Just "modify"]
accessor <- [Nothing, Just (Name.fromSegment "set"), Just (Name.fromSegment "modify")]
]
pure . P.group $
fmt S.DelimiterChar "{ "
@ -148,7 +146,7 @@ prettyDataDecl (PrettyPrintEnvDecl unsuffixifiedPPE suffixifiedPPE) r name dd =
P.group $
styleHashQualified'' (fmt (S.TypeReference r)) fname
<> fmt S.TypeAscriptionColon " :"
`P.hang` runPretty suffixifiedPPE (TypePrinter.prettyRaw Map.empty (-1) typ)
`P.hang` runPretty suffixifiedPPE (TypePrinter.prettyRaw Map.empty (-1) typ)
header = prettyDataHeader name dd <> fmt S.DelimiterChar (" = " `P.orElse` "\n = ")
-- Comes up with field names for a data declaration which has the form of a
@ -180,20 +178,26 @@ fieldNames env r name dd = do
vars = [Var.freshenId (fromIntegral n) (Var.named "_") | n <- [0 .. Type.arity typ - 1]]
hashes <- DD.hashFieldAccessors env (HQ.toVar name) vars r dd
let names =
[ (r, HQ.toString . PPE.termName env . Referent.Ref $ DerivedId r)
[ (r, HQ.toText . PPE.termName env . Referent.Ref $ DerivedId r)
| r <- (\(refId, _trm, _typ) -> refId) <$> Map.elems hashes
]
let fieldNames =
Map.fromList
[ (r, f) | (r, n) <- names, typename <- pure (HQ.toString name), typename `isPrefixOf` n, rest <- pure $ drop (length typename + 1) n, (f, rest) <- pure $ span (/= '.') rest, rest `elem` ["", ".set", ".modify"]
[ (r, f)
| (r, n) <- names,
typename <- pure (HQ.toText name),
typename `Text.isPrefixOf` n,
rest <- pure $ Text.drop (Text.length typename + 1) n,
(f, rest) <- pure $ Text.span (/= '.') rest,
rest `elem` ["", ".set", ".modify"]
]
if Map.size fieldNames == length names
then
Just
[ HQ.unsafeFromString name
[ HQ.unsafeParseText name
| v <- vars,
Just (ref, _, _) <- [Map.lookup (Var.namespaced [HQ.toVar name, v]) hashes],
Just (ref, _, _) <- [Map.lookup (Var.namespaced (HQ.toVar name :| [v])) hashes],
Just name <- [Map.lookup ref fieldNames]
]
else Nothing

View File

@ -4,14 +4,15 @@ module Unison.Syntax.FileParser
import Control.Lens
import Control.Monad.Reader (asks, local)
import Data.List.NonEmpty (pattern (:|))
import Data.Map qualified as Map
import Data.Set qualified as Set
import Data.Text qualified as Text
import Text.Megaparsec qualified as P
import Unison.ABT qualified as ABT
import Unison.DataDeclaration (DataDeclaration)
import Unison.DataDeclaration qualified as DD
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (..))
import Unison.Names qualified as Names
import Unison.Names.ResolutionResult qualified as Names
import Unison.NamesWithHistory qualified as Names
@ -20,9 +21,10 @@ import Unison.Parser.Ann qualified as Ann
import Unison.Prelude
import Unison.Syntax.DeclParser (declarations)
import Unison.Syntax.Lexer qualified as L
import Unison.Syntax.Name qualified as Name (toString, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toText, unsafeParseVar)
import Unison.Syntax.Parser
import Unison.Syntax.TermParser qualified as TermParser
import Unison.Syntax.Var qualified as Var (namespaced)
import Unison.Term (Term)
import Unison.Term qualified as Term
import Unison.UnisonFile (UnisonFile (..))
@ -51,12 +53,12 @@ file = do
Left es -> resolutionFailures (toList es)
let accessors :: [[(v, Ann, Term v Ann)]]
accessors =
[ DD.generateRecordAccessors Ann.GeneratedFrom (toPair <$> fields) (L.payload typ) r
[ DD.generateRecordAccessors Var.namespaced Ann.GeneratedFrom (toPair <$> fields) (L.payload typ) r
| (typ, fields) <- parsedAccessors,
Just (r, _) <- [Map.lookup (L.payload typ) (UF.datas env)]
]
toPair (tok, typ) = (L.payload tok, ann tok <> ann typ)
let importNames = [(Name.unsafeFromVar v, Name.unsafeFromVar v2) | (v, v2) <- imports]
let importNames = [(Name.unsafeParseVar v, Name.unsafeParseVar v2) | (v, v2) <- imports]
let locals = Names.importing importNames (UF.names env)
-- At this stage of the file parser, we've parsed all the type and ability
-- declarations. The `push locals` here has the effect
@ -97,13 +99,13 @@ file = do
-- All unique local term name suffixes - these we want to
-- avoid resolving to a term that's in the codebase
locals :: [Name.Name]
locals = (Name.unsafeFromVar <$> Map.keys canonicalVars)
locals = (Name.unsafeParseVar <$> Map.keys canonicalVars)
-- A function to replace unique local term suffixes with their
-- fully qualified name
replacements = [(v, Term.var () v2) | (v, v2) <- Map.toList canonicalVars, v /= v2]
resolveLocals = ABT.substsInheritAnnotation replacements
let bindNames = Term.bindSomeNames Name.unsafeFromVar (Set.fromList fqLocalTerms) curNames . resolveLocals
let bindNames = Term.bindSomeNames Name.unsafeParseVar (Set.fromList fqLocalTerms) curNames . resolveLocals
terms <- case List.validate (traverseOf _3 bindNames) terms of
Left es -> resolutionFailures (toList es)
Right terms -> pure terms
@ -217,14 +219,14 @@ stanza = watchExpression <|> unexpectedAction <|> binding
binding@((_, v), _) <- TermParser.binding
pure $ case doc of
Nothing -> Binding binding
Just (spanAnn, doc) -> Bindings [((spanAnn, Var.joinDot v (Var.named "doc")), doc), binding]
Just (spanAnn, doc) -> Bindings [((spanAnn, Var.namespaced (v :| [Var.named "doc"])), doc), binding]
watched :: (Monad m, Var v) => P v m (UF.WatchKind, Text, Ann)
watched = P.try do
kind <- (fmap . fmap . fmap) Name.toString (optional importWordyId)
kind <- (fmap . fmap . fmap) (Text.unpack . Name.toText) (optional importWordyId)
guid <- uniqueName 10
op <- optional (L.payload <$> P.lookAhead importSymbolyId)
guard (op == Just (Name.fromSegment (NameSegment ">")))
guard (op == Just (Name.fromSegment ">"))
tok <- anyToken
guard $ maybe True (`L.touches` tok) kind
pure (maybe UF.RegularWatch L.payload kind, guid, maybe mempty ann kind <> ann tok)

View File

@ -34,8 +34,6 @@ import Unison.HashQualified qualified as HQ
import Unison.HashQualified' qualified as HQ'
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (..))
import Unison.NameSegment qualified as NameSegment
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.NamesWithHistory qualified as Names
@ -46,7 +44,8 @@ import Unison.Prelude
import Unison.Reference (Reference)
import Unison.Referent (Referent)
import Unison.Syntax.Lexer qualified as L
import Unison.Syntax.Name qualified as Name (toText, toVar, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toText, toVar, unsafeParseVar)
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Syntax.Parser hiding (seq)
import Unison.Syntax.Parser qualified as Parser (seq, uniqueName)
import Unison.Syntax.TypeParser qualified as TypeParser
@ -106,7 +105,7 @@ rewriteBlock = do
rewriteCase = rewriteTermlike "case" DD.rewriteCase
rewriteType = do
kw <- quasikeyword "signature"
vs <- P.try (some prefixDefinitionName <* symbolyQuasikeyword ".") <|> pure []
vs <- P.try (some prefixDefinitionName <* reserved ".") <|> pure []
lhs <- TypeParser.computationType
rhs <- openBlockWith "==>" *> TypeParser.computationType <* closeBlock
pure (DD.rewriteType (ann kw <> ann rhs) (L.payload <$> vs) lhs rhs)
@ -416,15 +415,10 @@ quasikeyword kw = queryToken \case
L.WordyId (HQ'.NameOnly n) | nameIsKeyword n kw -> Just ()
_ -> Nothing
symbolyQuasikeyword :: (Ord v) => Text -> P v m (L.Token ())
symbolyQuasikeyword kw = queryToken \case
L.SymbolyId (HQ'.NameOnly n) | nameIsKeyword n kw -> Just ()
_ -> Nothing
nameIsKeyword :: Name -> Text -> Bool
nameIsKeyword name keyword =
case (Name.isRelative name, Name.reverseSegments name) of
(True, segment NonEmpty.:| []) -> NameSegment.toText segment == keyword
(True, segment NonEmpty.:| []) -> NameSegment.toEscapedText segment == keyword
_ -> False
-- If the hash qualified is name only, it is treated as a var, if it
@ -998,9 +992,9 @@ bang = P.label "bang" do
seqOp :: (Ord v) => P v m Pattern.SeqOp
seqOp =
Pattern.Snoc <$ matchToken (L.SymbolyId (HQ'.fromName (Name.fromSegment (NameSegment ":+"))))
<|> Pattern.Cons <$ matchToken (L.SymbolyId (HQ'.fromName (Name.fromSegment (NameSegment "+:"))))
<|> Pattern.Concat <$ matchToken (L.SymbolyId (HQ'.fromName (Name.fromSegment (NameSegment "++"))))
Pattern.Snoc <$ matchToken (L.SymbolyId (HQ'.fromName (Name.fromSegment ":+")))
<|> Pattern.Cons <$ matchToken (L.SymbolyId (HQ'.fromName (Name.fromSegment "+:")))
<|> Pattern.Concat <$ matchToken (L.SymbolyId (HQ'.fromName (Name.fromSegment "++")))
term4 :: (Monad m, Var v) => TermP v m
term4 = f <$> some termLeaf
@ -1030,7 +1024,7 @@ typedecl =
verifyRelativeVarName :: (Var v) => P v m (L.Token v) -> P v m (L.Token v)
verifyRelativeVarName p = do
v <- p
verifyRelativeName' (Name.unsafeFromVar <$> v)
verifyRelativeName' (Name.unsafeParseVar <$> v)
pure v
verifyRelativeName' :: (Ord v) => L.Token Name -> P v m ()
@ -1101,7 +1095,7 @@ binding = label "binding" do
-- we haven't seen a type annotation, so lookahead to '=' before commit
(lhsLoc, name, args) <- P.try (lhs <* P.lookAhead (openBlockWith "="))
(_bodySpanAnn, body) <- block "="
verifyRelativeName' (fmap Name.unsafeFromVar name)
verifyRelativeName' (fmap Name.unsafeParseVar name)
let binding = mkBinding lhsLoc args body
-- We don't actually use the span annotation from the block (yet) because it
-- may contain a bunch of white-space and comments following a top-level-definition.
@ -1109,7 +1103,7 @@ binding = label "binding" do
pure $ ((spanAnn, (L.payload name)), binding)
Just (nameT, typ) -> do
(lhsLoc, name, args) <- lhs
verifyRelativeName' (fmap Name.unsafeFromVar name)
verifyRelativeName' (fmap Name.unsafeParseVar name)
when (L.payload name /= L.payload nameT) $
customFailure $
SignatureNeedsAccompanyingBody nameT
@ -1148,7 +1142,7 @@ importp = do
-- a nicer error message if the suffixes are empty
prefix <-
optional $
fmap Right (importWordyId <|> importDotId) -- use . Nat
fmap Right importWordyId
<|> fmap Left importSymbolyId
suffixes <- optional (some (importWordyId <|> importSymbolyId))
case (prefix, suffixes) of
@ -1195,7 +1189,7 @@ substImports ns imports =
-- not in Names, but in a later term binding
[ (suffix, Type.var () full)
| (suffix, full) <- imports,
Names.hasTypeNamed Names.IncludeSuffixes (Name.unsafeFromVar full) ns
Names.hasTypeNamed Names.IncludeSuffixes (Name.unsafeParseVar full) ns
]
block' ::

View File

@ -39,7 +39,6 @@ import Unison.HashQualified' qualified as HQ'
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment)
import Unison.NameSegment qualified as NameSegment
import Unison.Pattern (Pattern)
import Unison.Pattern qualified as Pattern
import Unison.Prelude
@ -52,9 +51,10 @@ import Unison.Reference qualified as Reference
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Syntax.HashQualified qualified as HQ (unsafeFromVar)
import Unison.Syntax.Lexer (showEscapeChar, symbolyId)
import Unison.Syntax.Name qualified as Name (fromText, toString, toText, unsafeFromText)
import Unison.Syntax.Lexer (showEscapeChar)
import Unison.Syntax.Name qualified as Name (isSymboly, parseText, parseTextEither, toText, unsafeParseText)
import Unison.Syntax.NamePrinter (styleHashQualified'')
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Syntax.TypePrinter qualified as TypePrinter
import Unison.Term
import Unison.Type (Type, pattern ForallsNamed')
@ -206,7 +206,7 @@ pretty0
elideUnit = elideUnit
}
term =
specialCases term $ \case
specialCases term \case
Var' v -> pure . parenIfInfix name ic $ styleHashQualified'' (fmt S.Var) name
where
-- OK since all term vars are user specified, any freshening was just added during typechecking
@ -298,7 +298,7 @@ pretty0
`PP.hang` pb
<> PP.softbreak
<> fmt S.ControlKeyword "with"
`hangHandler` ph
`hangHandler` ph
]
Delay' x
| isLet x || p < 0 -> do
@ -1078,14 +1078,8 @@ l :: (IsString s) => String -> Pretty s
l = fromString
isSymbolic :: HQ.HashQualified Name -> Bool
isSymbolic (HQ.NameOnly name) = isSymbolic' name
isSymbolic (HQ.HashQualified name _) = isSymbolic' name
isSymbolic (HQ.HashOnly _) = False
isSymbolic' :: Name -> Bool
isSymbolic' name = case symbolyId . Name.toString $ name of
Right _ -> True
_ -> False
isSymbolic =
maybe False Name.isSymboly . HQ.toName
emptyAc :: AmbientContext
emptyAc = ac (-1) Normal Map.empty MaybeDoc
@ -1271,7 +1265,7 @@ printAnnotate n tm =
Set.fromList [n | v <- ABT.allVars tm, n <- varToName v]
usedTypeNames =
Set.fromList [n | Ann' _ ty <- ABT.subterms tm, v <- ABT.allVars ty, n <- varToName v]
varToName v = toList (Name.fromText (Var.name v))
varToName v = toList (Name.parseText (Var.name v))
go :: (Ord v) => Term2 v at ap v b -> Term2 v () () v b
go = extraMap' id (const ()) (const ())
@ -1314,11 +1308,11 @@ countName n =
{ usages =
Map.fromList do
(p, s) <- Name.splits n
pure (Name.toText s, Map.singleton (map NameSegment.toText p) 1)
pure (Name.toText s, Map.singleton (map NameSegment.toEscapedText p) 1)
}
joinName :: Prefix -> Suffix -> Name
joinName p s = Name.unsafeFromText $ dotConcat $ p ++ [s]
joinName p s = Name.unsafeParseText $ dotConcat $ p ++ [s]
dotConcat :: [Text] -> Text
dotConcat = Text.concat . intersperse "."
@ -1395,8 +1389,7 @@ calcImports im tm = (im', render $ getUses result)
|> filter
( \s ->
let (p, i) = lookupOrDie s m
in (i > 1 || isRight (symbolyId (unpack s)))
&& not (null p)
in (i > 1 || either (const False) Name.isSymboly (Name.parseTextEither s)) && not (null p)
)
|> map (\s -> (s, lookupOrDie s m))
|> Map.fromList
@ -2169,7 +2162,8 @@ avoidShadowing tm (PrettyPrintEnv terms types) =
& maybe fullName HQ'.NameOnly
in (fullName, minimallySuffixed)
tweak _ p = p
varToName v = toList (Name.fromText (Var.name v))
varToName :: Var v => v -> [Name]
varToName = toList . Name.parseText . Var.name
isLeaf :: Term2 vt at ap v a -> Bool
isLeaf (Var' {}) = True

View File

@ -12,9 +12,6 @@ import Text.Megaparsec qualified as P
import Unison.ABT qualified as ABT
import Unison.Builtin.Decls qualified as DD
import Unison.HashQualified qualified as HQ
import Unison.HashQualified' qualified as HQ'
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NamesWithHistory qualified as Names
import Unison.Parser.Ann (Ann (..))
import Unison.Prelude
@ -125,6 +122,6 @@ forall :: (Var v) => TypeP v m -> TypeP v m
forall rec = do
kw <- reserved "forall" <|> reserved ""
vars <- fmap (fmap L.payload) . some $ prefixDefinitionName
_ <- matchToken $ L.SymbolyId (HQ'.fromName (Name.fromSegment (NameSegment ".")))
_ <- reserved "."
t <- rec
pure $ Type.foralls (ann kw <> ann t) vars t

View File

@ -51,7 +51,7 @@ import Unison.Result
pattern Result,
)
import Unison.Result qualified as Result
import Unison.Syntax.Name qualified as Name (toText, unsafeFromText)
import Unison.Syntax.Name qualified as Name (toText, unsafeParseText)
import Unison.Term (Term)
import Unison.Term qualified as Term
import Unison.Type (Type)
@ -242,7 +242,7 @@ typeDirectedNameResolution ppe oldNotes oldType env = do
addTypedComponent :: Context.InfoNote v loc -> State (Env v loc) ()
addTypedComponent (Context.TopLevelComponent vtts) =
for_ vtts $ \(v, typ, _) ->
for_ (Name.suffixes . Name.unsafeFromText . Var.name $ Var.reset v) $ \suffix ->
for_ (Name.suffixes . Name.unsafeParseText . Var.name $ Var.reset v) $ \suffix ->
termsByShortname
%= Map.insertWith
(<>)
@ -278,7 +278,7 @@ typeDirectedNameResolution ppe oldNotes oldType env = do
Map.insertWith
Set.union
suggestionReplacement
(Set.singleton (Name.unsafeFromText suggestionName))
(Set.singleton (Name.unsafeParseText suggestionName))
b
)
Map.empty

View File

@ -31,8 +31,8 @@ import Unison.WatchKind qualified as WK
toNames :: (Var v) => UnisonFile v a -> Names
toNames uf = datas <> effects
where
datas = foldMap (DD.Names.dataDeclToNames' Name.unsafeFromVar) (Map.toList (UF.dataDeclarationsId uf))
effects = foldMap (DD.Names.effectDeclToNames' Name.unsafeFromVar) (Map.toList (UF.effectDeclarationsId uf))
datas = foldMap (DD.Names.dataDeclToNames' Name.unsafeParseVar) (Map.toList (UF.dataDeclarationsId uf))
effects = foldMap (DD.Names.effectDeclToNames' Name.unsafeParseVar) (Map.toList (UF.effectDeclarationsId uf))
addNamesFromUnisonFile :: (Var v) => UnisonFile v a -> Names -> Names
addNamesFromUnisonFile unisonFile names = Names.shadowing (toNames unisonFile) names
@ -42,13 +42,13 @@ typecheckedToNames uf = Names (terms <> ctors) types
where
terms =
Relation.fromList
[ (Name.unsafeFromVar v, Referent.Ref r)
[ (Name.unsafeParseVar v, Referent.Ref r)
| (v, (_a, r, wk, _, _)) <- Map.toList $ UF.hashTerms uf,
wk == Nothing || wk == Just WK.TestWatch
]
types =
Relation.fromList
[ (Name.unsafeFromVar v, r)
[ (Name.unsafeParseVar v, r)
| (v, r) <-
Map.toList $
fmap fst (UF.dataDeclarations' uf)
@ -56,7 +56,7 @@ typecheckedToNames uf = Names (terms <> ctors) types
]
ctors =
Relation.fromMap
. Map.mapKeys Name.unsafeFromVar
. Map.mapKeys Name.unsafeParseVar
. fmap (fmap Reference.DerivedId)
. UF.hashConstructors
$ uf
@ -87,8 +87,8 @@ bindNames names (UnisonFileId d e ts ws) = do
let termVars = (view _1 <$> ts) ++ (Map.elems ws >>= map (view _1))
termVarsSet = Set.fromList termVars
-- todo: can we clean up this lambda using something like `second`
ts' <- traverse (\(v, a, t) -> (v,a,) <$> Term.bindNames Name.unsafeFromVar termVarsSet names t) ts
ws' <- traverse (traverse (\(v, a, t) -> (v,a,) <$> Term.bindNames Name.unsafeFromVar termVarsSet names t)) ws
ts' <- traverse (\(v, a, t) -> (v,a,) <$> Term.bindNames Name.unsafeParseVar termVarsSet names t) ts
ws' <- traverse (traverse (\(v, a, t) -> (v,a,) <$> Term.bindNames Name.unsafeParseVar termVarsSet names t)) ws
pure $ UnisonFileId d e ts' ws'
-- | Given the set of fully-qualified variable names, this computes
@ -111,7 +111,7 @@ variableCanonicalizer :: forall v. Var v => [v] -> Map v v
variableCanonicalizer vs =
done $ List.multimap do
v <- vs
let n = Name.unsafeFromVar v
let n = Name.unsafeParseVar v
suffix <- Name.suffixes n
pure (Var.named (Name.toText suffix), v)
where
@ -134,9 +134,9 @@ environmentFor names dataDecls0 effectDecls0 = do
let locallyBoundTypes = variableCanonicalizer (Map.keys dataDecls0 <> Map.keys effectDecls0)
-- data decls and hash decls may reference each other, and thus must be hashed together
dataDecls :: Map v (DataDeclaration v a) <-
traverse (DD.Names.bindNames Name.unsafeFromVar locallyBoundTypes names) dataDecls0
traverse (DD.Names.bindNames Name.unsafeParseVar locallyBoundTypes names) dataDecls0
effectDecls :: Map v (EffectDeclaration v a) <-
traverse (DD.withEffectDeclM (DD.Names.bindNames Name.unsafeFromVar locallyBoundTypes names)) effectDecls0
traverse (DD.withEffectDeclM (DD.Names.bindNames Name.unsafeParseVar locallyBoundTypes names)) effectDecls0
let allDecls0 :: Map v (DataDeclaration v a)
allDecls0 = Map.union dataDecls (toDataDecl <$> effectDecls)
hashDecls' :: [(v, Reference.Id, DataDeclaration v a)] <- Hashing.hashDataDecls allDecls0
@ -145,8 +145,8 @@ environmentFor names dataDecls0 effectDecls0 = do
dataDecls' = Map.difference allDecls effectDecls
effectDecls' = second EffectDeclaration <$> Map.difference allDecls dataDecls
-- ctor and effect terms
ctors = foldMap (DD.Names.dataDeclToNames' Name.unsafeFromVar) (Map.toList dataDecls')
effects = foldMap (DD.Names.effectDeclToNames' Name.unsafeFromVar) (Map.toList effectDecls')
ctors = foldMap (DD.Names.dataDeclToNames' Name.unsafeParseVar) (Map.toList dataDecls')
effects = foldMap (DD.Names.effectDeclToNames' Name.unsafeParseVar) (Map.toList effectDecls')
names' = ctors <> effects
overlaps =
let w v dd (toDataDecl -> ed) = DupDataAndAbility v (DD.annotation dd) (DD.annotation ed)

View File

@ -0,0 +1,192 @@
{-# LANGUAGE RecordWildCards #-}
module Unison.Util.Star2
( Star2 (Star2),
fact,
insertD1,
insertD2,
deleteD1,
deleteD2,
deleteFact,
deletePrimaryD1,
d1,
d2,
difference,
lookupD1,
mapD2,
memberD1,
replaceFacts,
)
where
import Data.Map qualified as Map
import Data.Set qualified as Set
import Unison.Prelude
import Unison.Util.Relation (Relation)
import Unison.Util.Relation qualified as R
-- Represents a set of (fact, d1, d2, d2), but indexed using a star schema so
-- it can be efficiently queried from any of the dimensions.
data Star2 fact d1 d2 = Star2
{ fact :: Set fact,
d1 :: Relation fact d1,
d2 :: Relation fact d2
}
deriving (Eq, Ord, Show)
-- Produce the cross-product across all the dimensions
-- `difference a b` contains only the facts from `a` that are absent from `b`
-- or differ along any of the dimensions `d1..d2`.
difference ::
(Ord fact, Ord d1, Ord d2) =>
Star2 fact d1 d2 ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
difference a b = Star2 facts d1s d2s
where
d1s = R.difference (d1 a) (d1 b)
d2s = R.difference (d2 a) (d2 b)
facts = R.dom d1s <> R.dom d2s
mapD2 :: (Ord fact, Ord d2, Ord d2a) => (d2 -> d2a) -> Star2 fact d1 d2 -> Star2 fact d1 d2a
mapD2 f s = s {d2 = R.mapRan f (d2 s)}
-- Deletes tuples of the form (fact, d1, _, _).
-- If no other (fact, dk, _, _) tuples exist for any other dk, then
-- `fact` is removed from the `fact` set and from the other dimensions as well,
-- that is, (fact, d1) is treated as a primary key.
deletePrimaryD1 ::
(Ord fact, Ord d1, Ord d2) =>
(fact, d1) ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
deletePrimaryD1 (f, x) s =
let d1' = R.delete f x (d1 s)
otherX = R.lookupDom f d1'
in if Set.null otherX
then Star2 (Set.delete f (fact s)) d1' (R.deleteDom f (d2 s))
else s {d1 = d1'}
-- Deletes tuples of the form (_, d1, _, _).
deleteD1 ::
(Ord fact, Ord d1, Ord d2) =>
d1 ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
deleteD1 x s =
let d1' = R.deleteRan x (d1 s)
deadFacts = R.lookupRan x (d1 s)
newFacts = Set.difference (fact s) deadFacts
d2' = R.subtractDom deadFacts (d2 s)
in Star2
newFacts
d1'
d2'
lookupD1 :: (Ord fact, Ord d1) => d1 -> Star2 fact d1 d2 -> Set fact
lookupD1 x s = R.lookupRan x (d1 s)
insertD1 ::
(Ord fact, Ord d1) =>
(fact, d1) ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
insertD1 (f, x) s =
s
{ fact = Set.insert f (fact s),
d1 = R.insert f x (d1 s)
}
insertD2 ::
(Ord fact, Ord d2) =>
(fact, d2) ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
insertD2 (f, x) s =
s
{ fact = Set.insert f (fact s),
d2 = R.insert f x (d2 s)
}
memberD1 :: (Ord fact, Ord d1) => (fact, d1) -> Star2 fact d1 d2 -> Bool
memberD1 (f, x) s = R.member f x (d1 s)
deleteD2 ::
(Ord fact, Ord d1, Ord d2) =>
(fact, d2) ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
deleteD2 (f, x) s = garbageCollect f (Star2 (fact s) (d1 s) d2')
where
d2' = R.delete f x (d2 s)
-- | Given a possibly-invalid Star2, which may contain the given fact in its fact set that are not related to any d1,
-- d2, or d2, return a valid Star2, with this fact possibly removed.
garbageCollect :: (Ord fact) => fact -> Star2 fact d1 d2 -> Star2 fact d1 d2
garbageCollect f star =
star
{ fact =
if R.memberDom f (d1 star) || R.memberDom f (d2 star)
then fact star
else Set.delete f (fact star)
}
deleteFact ::
(Ord fact, Ord d1, Ord d2) =>
Set fact ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
deleteFact facts Star2 {..} =
Star2
(fact `Set.difference` facts)
(facts R.<|| d1)
(facts R.<|| d2)
-- Efficiently replace facts with those in the provided `Map`.
-- The `apply` function can be used to add other dimensions
-- in the same traversal. It is given `apply old new s` where
-- s is the current `Star` being accumulated.
--
-- Currently used by update propagation but likely useful for
-- other bulk rewriting of namespaces.
replaceFacts ::
(Ord fact, Ord d1, Ord d2) =>
(fact -> fact -> Star2 fact d1 d2 -> Star2 fact d1 d2) ->
Map fact fact ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
replaceFacts apply m s =
let -- the intersection of `fact` and the replacement keys is often small,
-- so we compute that first (which can happen in O(size of intersection))
-- rather than iterating over one or the other
replaceable = Map.keysSet m `Set.intersection` fact s
go s old = apply old new $ replaceFact old new s
where
new = Map.findWithDefault old old m
in foldl' go s replaceable
replaceFact ::
(Ord fact, Ord d1, Ord d2) =>
fact ->
fact ->
Star2 fact d1 d2 ->
Star2 fact d1 d2
replaceFact f f' s@Star2 {..} =
if Set.notMember f fact
then s
else
Star2
(Set.insert f' . Set.delete f $ fact)
(R.replaceDom f f' d1)
(R.replaceDom f f' d2)
instance (Ord fact, Ord d1, Ord d2) => Semigroup (Star2 fact d1 d2) where
s1 <> s2 = Star2 fact' d1' d2'
where
fact' = fact s1 <> fact s2
d1' = d1 s1 <> d1 s2
d2' = d2 s1 <> d2 s2
instance (Ord fact, Ord d1, Ord d2) => Monoid (Star2 fact d1 d2) where
mempty = Star2 mempty mempty mempty

View File

@ -1,291 +0,0 @@
{-# LANGUAGE RecordWildCards #-}
module Unison.Util.Star3 where
import Data.Map qualified as Map
import Data.Set qualified as Set
import Unison.Prelude
import Unison.Util.Relation (Relation)
import Unison.Util.Relation qualified as R
-- Represents a set of (fact, d1, d2, d3), but indexed using a star schema so
-- it can be efficiently queried from any of the dimensions.
data Star3 fact d1 d2 d3 = Star3
{ fact :: Set fact,
d1 :: Relation fact d1,
d2 :: Relation fact d2,
d3 :: Relation fact d3
}
deriving (Eq, Ord, Show)
-- Produce the cross-product across all the dimensions
toList ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
Star3 fact d1 d2 d3 ->
[(fact, d1, d2, d3)]
toList s =
[ (f, x, y, z) | f <- Set.toList (fact s), x <- Set.toList (R.lookupDom f (d1 s)), y <- Set.toList (R.lookupDom f (d2 s)), z <- Set.toList (R.lookupDom f (d3 s))
]
-- `difference a b` contains only the facts from `a` that are absent from `b`
-- or differ along any of the dimensions `d1..d3`.
difference ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
difference a b = Star3 facts d1s d2s d3s
where
d1s = R.difference (d1 a) (d1 b)
d2s = R.difference (d2 a) (d2 b)
d3s = R.difference (d3 a) (d3 b)
facts = R.dom d1s <> R.dom d2s <> R.dom d3s
d23s ::
(Ord fact, Ord d2, Ord d3) =>
Star3 fact d1 d2 d3 ->
[(fact, d2, d3)]
d23s s =
[ (f, x, y) | f <- Set.toList (fact s), x <- Set.toList (R.lookupDom f (d2 s)), y <- Set.toList (R.lookupDom f (d3 s))
]
d23s' ::
(Ord fact, Ord d2, Ord d3) =>
Star3 fact d1 d2 d3 ->
[(d2, d3)]
d23s' s =
[ (x, y) | f <- Set.toList (fact s), x <- Set.toList (R.lookupDom f (d2 s)), y <- Set.toList (R.lookupDom f (d3 s))
]
d12s ::
(Ord fact, Ord d1, Ord d2) =>
Star3 fact d1 d2 d3 ->
[(fact, d1, d2)]
d12s s =
[ (f, x, y) | f <- Set.toList (fact s), x <- Set.toList (R.lookupDom f (d1 s)), y <- Set.toList (R.lookupDom f (d2 s))
]
d13s ::
(Ord fact, Ord d1, Ord d3) =>
Star3 fact d1 d2 d3 ->
[(fact, d1, d3)]
d13s s =
[ (f, x, y) | f <- Set.toList (fact s), x <- Set.toList (R.lookupDom f (d1 s)), y <- Set.toList (R.lookupDom f (d3 s))
]
mapD1 :: (Ord fact, Ord d1, Ord d1a) => (d1 -> d1a) -> Star3 fact d1 d2 d3 -> Star3 fact d1a d2 d3
mapD1 f s = s {d1 = R.mapRan f (d1 s)}
mapD2 :: (Ord fact, Ord d2, Ord d2a) => (d2 -> d2a) -> Star3 fact d1 d2 d3 -> Star3 fact d1 d2a d3
mapD2 f s = s {d2 = R.mapRan f (d2 s)}
mapD3 :: (Ord fact, Ord d3, Ord d3a) => (d3 -> d3a) -> Star3 fact d1 d2 d3 -> Star3 fact d1 d2 d3a
mapD3 f s = s {d3 = R.mapRan f (d3 s)}
fromList ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
[(fact, d1, d2, d3)] ->
Star3 fact d1 d2 d3
fromList = foldl' (flip insert) mempty
selectFact ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
Set fact ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
selectFact fs s = Star3 fact' d1' d2' d3'
where
fact' = Set.intersection fs (fact s)
d1' = fs R.<| d1 s
d2' = fs R.<| d2 s
d3' = fs R.<| d3 s
select1D3 ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
d3 ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
select1D3 = selectD3 . Set.singleton
selectD3 ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
Set d3 ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
selectD3 d3s s = Star3 fact' d1' d2' d3'
where
fact' = Set.intersection (R.dom d3') (fact s)
d1' = R.dom d3' R.<| d1 s
d2' = R.dom d3' R.<| d2 s
d3' = d3 s R.|> d3s
-- Deletes tuples of the form (fact, d1, _, _).
-- If no other (fact, dk, _, _) tuples exist for any other dk, then
-- `fact` is removed from the `fact` set and from the other dimensions as well,
-- that is, (fact, d1) is treated as a primary key.
deletePrimaryD1 ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
(fact, d1) ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
deletePrimaryD1 (f, x) s =
let d1' = R.delete f x (d1 s)
otherX = R.lookupDom f d1'
in if Set.null otherX
then Star3 (Set.delete f (fact s)) d1' (R.deleteDom f (d2 s)) (R.deleteDom f (d3 s))
else s {d1 = d1'}
-- Deletes tuples of the form (_, d1, _, _).
deleteD1 ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
d1 ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
deleteD1 x s =
let d1' = R.deleteRan x (d1 s)
deadFacts = R.lookupRan x (d1 s)
newFacts = Set.difference (fact s) deadFacts
d2' = R.subtractDom deadFacts (d2 s)
d3' = R.subtractDom deadFacts (d3 s)
in Star3
newFacts
d1'
d2'
d3'
lookupD1 :: (Ord fact, Ord d1) => d1 -> Star3 fact d1 d2 d3 -> Set fact
lookupD1 x s = R.lookupRan x (d1 s)
insertD1 ::
(Ord fact, Ord d1) =>
(fact, d1) ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
insertD1 (f, x) s =
s
{ fact = Set.insert f (fact s),
d1 = R.insert f x (d1 s)
}
memberD1 :: (Ord fact, Ord d1) => (fact, d1) -> Star3 fact d1 d2 d3 -> Bool
memberD1 (f, x) s = R.member f x (d1 s)
memberD2 :: (Ord fact, Ord d2) => (fact, d2) -> Star3 fact d1 d2 d3 -> Bool
memberD2 (f, x) s = R.member f x (d2 s)
memberD3 :: (Ord fact, Ord d3) => (fact, d3) -> Star3 fact d1 d2 d3 -> Bool
memberD3 (f, x) s = R.member f x (d3 s)
insert ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
(fact, d1, d2, d3) ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
insert (f, d1i, d2i, d3i) s = Star3 fact' d1' d2' d3'
where
fact' = Set.insert f (fact s)
d1' = R.insert f d1i (d1 s)
d2' = R.insert f d2i (d2 s)
d3' = R.insert f d3i (d3 s)
insertD23 ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
(fact, d2, d3) ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
insertD23 (f, x, y) s = Star3 fact' (d1 s) d2' d3'
where
fact' = Set.insert f (fact s)
d2' = R.insert f x (d2 s)
d3' = R.insert f y (d3 s)
deleteD3 ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
(fact, d3) ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
deleteD3 (f, x) s = garbageCollect f (Star3 (fact s) (d1 s) (d2 s) d3')
where
d3' = R.delete f x (d3 s)
deleteD2 ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
(fact, d2) ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
deleteD2 (f, x) s = garbageCollect f (Star3 (fact s) (d1 s) d2' (d3 s))
where
d2' = R.delete f x (d2 s)
-- | Given a possibly-invalid Star3, which may contain the given fact in its fact set that are not related to any d1,
-- d2, or d3, return a valid Star3, with this fact possibly removed.
garbageCollect :: (Ord fact) => fact -> Star3 fact d1 d2 d3 -> Star3 fact d1 d2 d3
garbageCollect f star =
star
{ fact =
if R.memberDom f (d1 star) || R.memberDom f (d2 star) || R.memberDom f (d3 star)
then fact star
else Set.delete f (fact star)
}
deleteFact ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
Set fact ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
deleteFact facts Star3 {..} =
Star3
(fact `Set.difference` facts)
(facts R.<|| d1)
(facts R.<|| d2)
(facts R.<|| d3)
-- Efficiently replace facts with those in the provided `Map`.
-- The `apply` function can be used to add other dimensions
-- in the same traversal. It is given `apply old new s` where
-- s is the current `Star` being accumulated.
--
-- Currently used by update propagation but likely useful for
-- other bulk rewriting of namespaces.
replaceFacts ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
(fact -> fact -> Star3 fact d1 d2 d3 -> Star3 fact d1 d2 d3) ->
Map fact fact ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
replaceFacts apply m s =
let -- the intersection of `fact` and the replacement keys is often small,
-- so we compute that first (which can happen in O(size of intersection))
-- rather than iterating over one or the other
replaceable = Map.keysSet m `Set.intersection` fact s
go s old = apply old new $ replaceFact old new s
where
new = Map.findWithDefault old old m
in foldl' go s replaceable
replaceFact ::
(Ord fact, Ord d1, Ord d2, Ord d3) =>
fact ->
fact ->
Star3 fact d1 d2 d3 ->
Star3 fact d1 d2 d3
replaceFact f f' s@Star3 {..} =
if Set.notMember f fact
then s
else
Star3
(Set.insert f' . Set.delete f $ fact)
(R.replaceDom f f' d1)
(R.replaceDom f f' d2)
(R.replaceDom f f' d3)
instance (Ord fact, Ord d1, Ord d2, Ord d3) => Semigroup (Star3 fact d1 d2 d3) where
s1 <> s2 = Star3 fact' d1' d2' d3'
where
fact' = fact s1 <> fact s2
d1' = d1 s1 <> d1 s2
d2' = d2 s1 <> d2 s2
d3' = d3 s1 <> d3 s2
instance (Ord fact, Ord d1, Ord d2, Ord d3) => Monoid (Star3 fact d1 d2 d3) where
mempty = Star3 mempty mempty mempty mempty

View File

@ -5,7 +5,7 @@ import Data.List.NonEmpty qualified as List.NonEmpty
import Data.Set qualified as Set
import EasyTest
import Unison.Name as Name
import Unison.Syntax.Name qualified as Name (unsafeFromText)
import Unison.Syntax.Name qualified as Name (unsafeParseText)
import Unison.Util.Relation qualified as R
test :: Test ()
@ -24,25 +24,33 @@ test =
testCompareSuffix :: [Test ()]
testCompareSuffix =
[ scope "[b.c a.b.c]" (expectEqual (compareSuffix "b.c" "a.b.c") EQ),
scope "[a.b.c a.b.c]" (expectEqual (compareSuffix "a.b.c" "a.b.c") EQ),
scope "[b.c a.b.b]" (expectEqual (compareSuffix "b.c" "a.b.b") LT),
scope "[a.b.c b.c]" (expectEqual (compareSuffix "a.b.c" "b.c") LT),
scope "[b.b a.b.c]" (expectEqual (compareSuffix "b.b" "a.b.c") GT)
[ scope "[b.c a.b.c]" (expectEqual (compareSuffix (Name.unsafeParseText "b.c") (Name.unsafeParseText "a.b.c")) EQ),
scope "[a.b.c a.b.c]" (expectEqual (compareSuffix (Name.unsafeParseText "a.b.c") (Name.unsafeParseText "a.b.c")) EQ),
scope "[b.c a.b.b]" (expectEqual (compareSuffix (Name.unsafeParseText "b.c") (Name.unsafeParseText "a.b.b")) LT),
scope "[a.b.c b.c]" (expectEqual (compareSuffix (Name.unsafeParseText "a.b.c") (Name.unsafeParseText "b.c")) LT),
scope "[b.b a.b.c]" (expectEqual (compareSuffix (Name.unsafeParseText "b.b") (Name.unsafeParseText "a.b.c")) GT)
]
testEndsWithReverseSegments :: [Test ()]
testEndsWithReverseSegments =
[ scope "a.b.c ends with []" (expectEqual True (endsWithReverseSegments "a.b.c" [])),
scope "a.b.c ends with [c, b]" (expectEqual True (endsWithReverseSegments "a.b.c" ["c", "b"])),
scope "a.b.c doesn't end with [d]" (expectEqual False (endsWithReverseSegments "a.b.c" ["d"]))
[ scope "a.b.c ends with []" (expectEqual True (endsWithReverseSegments (Name.unsafeParseText "a.b.c") [])),
scope
"a.b.c ends with [c, b]"
(expectEqual True (endsWithReverseSegments (Name.unsafeParseText "a.b.c") ["c", "b"])),
scope
"a.b.c doesn't end with [d]"
(expectEqual False (endsWithReverseSegments (Name.unsafeParseText "a.b.c") ["d"]))
]
testEndsWithSegments :: [Test ()]
testEndsWithSegments =
[ scope "a.b.c ends with []" (expectEqual True (endsWithSegments "a.b.c" [])),
scope "a.b.c ends with [b, c]" (expectEqual True (endsWithSegments "a.b.c" ["b", "c"])),
scope "a.b.c doesn't end with [d]" (expectEqual False (endsWithSegments "a.b.c" ["d"]))
[ scope "a.b.c ends with []" (expectEqual True (endsWithSegments (Name.unsafeParseText "a.b.c") [])),
scope
"a.b.c ends with [b, c]"
(expectEqual True (endsWithSegments (Name.unsafeParseText "a.b.c") ["b", "c"])),
scope
"a.b.c doesn't end with [d]"
(expectEqual False (endsWithSegments (Name.unsafeParseText "a.b.c") ["d"]))
]
testSegments :: [Test ()]
@ -55,19 +63,25 @@ testSegments =
testSplitName :: [Test ()]
testSplitName =
[ scope "x" (expectEqual (splits "x") [([], "x")]),
scope "A.x" (expectEqual (splits "A.x") [([], "A.x"), (["A"], "x")]),
scope "A.B.x" (expectEqual (splits "A.B.x") [([], "A.B.x"), (["A"], "B.x"), (["A", "B"], "x")])
[ scope "x" (expectEqual (splits (Name.unsafeParseText "x")) [([], Name.unsafeParseText "x")]),
scope "A.x" (expectEqual (splits (Name.unsafeParseText "A.x")) [([], Name.unsafeParseText "A.x"), (["A"], Name.unsafeParseText "x")]),
scope
"A.B.x"
( expectEqual
(splits (Name.unsafeParseText "A.B.x"))
[ ([], Name.unsafeParseText "A.B.x"),
(["A"], Name.unsafeParseText "B.x"),
(["A", "B"], Name.unsafeParseText "x")
]
)
]
testSuffixes :: [Test ()]
testSuffixes =
[ scope "one namespace" $ expectEqual (suffixes "bar") ["bar"],
scope "two namespaces" $
expectEqual (suffixes "foo.bar") ["foo.bar", "bar"],
scope "multiple namespaces" $
expectEqual (suffixes "foo.bar.baz") ["foo.bar.baz", "bar.baz", "baz"],
scope "terms named `.`" $ expectEqual (suffixes "base..") ["base..", "."]
[ scope "one namespace" $ expectEqual (suffixes (Name.unsafeParseText "bar")) [Name.unsafeParseText "bar"],
scope "two namespaces" $ expectEqual (suffixes (Name.unsafeParseText "foo.bar")) [Name.unsafeParseText "foo.bar", Name.unsafeParseText "bar"],
scope "multiple namespaces" $ expectEqual (suffixes (Name.unsafeParseText "foo.bar.baz")) [Name.unsafeParseText "foo.bar.baz", Name.unsafeParseText "bar.baz", Name.unsafeParseText "baz"],
scope "terms named `.`" $ expectEqual (suffixes (Name.unsafeParseText "base.`.`")) [Name.unsafeParseText "base.`.`", Name.unsafeParseText "`.`"]
]
testSuffixSearch :: [Test ()]
@ -81,37 +95,23 @@ testSuffixSearch =
(n "foo.bar.baz", 3),
(n "a.b.c", 4),
(n "a1.b.c", 5),
(n "..", 6)
(n ".`.`", 6)
]
n = Name.unsafeFromText
expectEqual' ("." :| []) (Name.segments (n ".."))
expectEqual' ("." :| []) (Name.reverseSegments (n ".."))
n = Name.unsafeParseText
expectEqual' ("." :| []) (Name.reverseSegments (n ".`.`"))
expectEqual' ("." :| []) (Name.reverseSegments (n ".`.`"))
expectEqual'
(Set.fromList [1, 2])
(Name.searchBySuffix (n "map") rel)
expectEqual'
(n "List.map")
(Name.suffixifyByHash (n "base.List.map") rel)
expectEqual'
(n "Set.map")
(Name.suffixifyByHash (n "base.Set.map") rel)
expectEqual'
(n "baz")
(Name.suffixifyByHash (n "foo.bar.baz") rel)
expectEqual'
(n "a.b.c")
(Name.suffixifyByHash (n "a.b.c") rel)
expectEqual'
(n "a1.b.c")
(Name.suffixifyByHash (n "a1.b.c") rel)
note . show $ Name.reverseSegments (n ".")
note . show $ Name.reverseSegments (n "..")
expectEqual' (Set.fromList [1, 2]) (Name.searchBySuffix (n "map") rel)
expectEqual' (n "List.map") (Name.suffixifyByHash (n "base.List.map") rel)
expectEqual' (n "Set.map") (Name.suffixifyByHash (n "base.Set.map") rel)
expectEqual' (n "baz") (Name.suffixifyByHash (n "foo.bar.baz") rel)
expectEqual' (n "a.b.c") (Name.suffixifyByHash (n "a.b.c") rel)
expectEqual' (n "a1.b.c") (Name.suffixifyByHash (n "a1.b.c") rel)
note . show $ Name.reverseSegments (n "`.`")
note . show $ Name.reverseSegments (n ".`.`")
tests
[ scope "(.) shortest unique suffix" $
expectEqual' (n ".") (Name.suffixifyByHash (n "..") rel),
scope "(.) search by suffix" $
expectEqual' (Set.fromList [6]) (Name.searchBySuffix (n ".") rel)
[ scope "(.) shortest unique suffix" $ expectEqual' (n "`.`") (Name.suffixifyByHash (n ".`.`") rel),
scope "(.) search by suffix" $ expectEqual' (Set.fromList [6]) (Name.searchBySuffix (n "`.`") rel)
]
ok
]
@ -119,23 +119,23 @@ testSuffixSearch =
testUnsafeFromString :: [Test ()]
testUnsafeFromString =
[ scope "." do
expectEqual' (isAbsolute ".") False
expectEqual' (segments ".") ("." :| [])
expectEqual' (isAbsolute (Name.unsafeParseText "`.`")) False
expectEqual' (segments (Name.unsafeParseText "`.`")) ("." :| [])
ok,
scope ".." do
expectEqual' (isAbsolute "..") True
expectEqual' (segments "..") ("." :| [])
scope ".`.`" do
expectEqual' (isAbsolute (Name.unsafeParseText ".`.`")) True
expectEqual' (segments (Name.unsafeParseText ".`.`")) ("." :| [])
ok,
scope "foo.bar" do
expectEqual' (isAbsolute "foo.bar") False
expectEqual' (segments "foo.bar") ("foo" :| ["bar"])
expectEqual' (isAbsolute (Name.unsafeParseText "foo.bar")) False
expectEqual' (segments (Name.unsafeParseText "foo.bar")) ("foo" :| ["bar"])
ok,
scope ".foo.bar" do
expectEqual' (isAbsolute ".foo.bar") True
expectEqual' (segments ".foo.bar") ("foo" :| ["bar"])
expectEqual' (isAbsolute (Name.unsafeParseText ".foo.bar")) True
expectEqual' (segments (Name.unsafeParseText ".foo.bar")) ("foo" :| ["bar"])
ok,
scope "foo.." do
expectEqual' (isAbsolute "foo..") False
expectEqual' (segments "foo..") ("foo" :| ["."])
scope "foo.`.`" do
expectEqual' (isAbsolute (Name.unsafeParseText "foo.`.`")) False
expectEqual' (segments (Name.unsafeParseText "foo.`.`")) ("foo" :| ["."])
ok
]

View File

@ -4,6 +4,7 @@ module Unison.Test.Codebase.Branch
)
where
import Data.Function ((&))
import Data.Functor.Identity
import Data.Map qualified as Map
import Data.Set qualified as Set
@ -11,10 +12,11 @@ import EasyTest
import Unison.Codebase.Branch (Branch (Branch), Branch0)
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Causal qualified as Causal
import Unison.Codebase.Metadata qualified as Metadata
import Unison.Reference (Reference)
import Unison.Reference qualified as Reference
import Unison.Util.Relation qualified as Relation
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
test :: Test ()
test =
@ -31,7 +33,10 @@ branch0Tests =
b0 :: Branch0 Identity =
Branch.branch0
mempty
(Star3.fromList [(dummy, "b", dummy, (dummy, dummy))])
( mempty
& Star2.insertD1 (dummy, "b")
& Metadata.insert (dummy, dummy)
)
Map.empty
Map.empty
let -- a.b
@ -39,7 +44,10 @@ branch0Tests =
b1 :: Branch0 Identity =
Branch.branch0
mempty
(Star3.fromList [(dummy, "b", dummy, (dummy, dummy))])
( mempty
& Star2.insertD1 (dummy, "b")
& Metadata.insert (dummy, dummy)
)
(Map.singleton "a" (Branch (Causal.one b0)))
Map.empty

View File

@ -1,58 +1,30 @@
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
module Unison.Test.Codebase.Path where
import Data.Either
import Data.Maybe (fromJust)
import Data.Sequence
import Data.Text
import EasyTest
import Unison.Codebase.Path
import Unison.Codebase.Path.Parse
import Unison.Codebase.Path (Path (..), Path' (..), Relative (..))
import Unison.Codebase.Path.Parse (parseHQSplit', parseShortHashOrHQSplit')
import Unison.HashQualified' qualified as HQ'
import Unison.NameSegment
import Unison.NameSegment (NameSegment)
import Unison.Prelude
import Unison.ShortHash qualified as SH
test :: Test ()
test =
scope "path" . tests $
[ scope "parsePathImpl'" . tests $
[ let s = "foo.bar.baz.34" in scope s . expect $ parsePathImpl' s == Right (relative ["foo", "bar", "baz"], "34"),
let s = "foo.bar.baz" in scope s . expect $ parsePathImpl' s == Right (relative ["foo", "bar"], "baz"),
let s = "baz" in scope s . expect $ parsePathImpl' s == Right (relative [], "baz"),
let s = "-" in scope s . expect $ parsePathImpl' s == Right (relative [], "-"),
let s = "34" in scope s . pending . expect $ parsePathImpl' s == Right (relative [], "34"),
let s = "foo.bar.baz#a8fj" in scope s . expect $ isLeft $ parsePathImpl' s
],
scope "parseSplit'" . tests $
[ scope "wordyNameSegment" . tests $
[ let s = "foo.bar.baz"
in scope s . expect $
parseSplit' wordyNameSegment s == Right (relative ["foo", "bar"], NameSegment "baz"),
let s = "foo.bar.baz#abc" in scope s . expect $ isLeft $ parseSplit' wordyNameSegment s,
let s = "foo.bar.+"
in scope s . expect $
isLeft $
parseSplit' wordyNameSegment s
],
scope "definitionNameSegment" . tests $
[ let s = "foo.bar.+"
in scope s . expect $
parseSplit' definitionNameSegment s == Right (relative ["foo", "bar"], NameSegment "+")
]
],
scope "parseShortHashOrHQSplit'" . tests $
[ scope "parseShortHashOrHQSplit'" . tests $
[ let s = "foo.bar#34"
in scope s . expect $
parseShortHashOrHQSplit' s
== (Right . Right)
(relative ["foo"], HQ'.HashQualified (NameSegment "bar") (fromJust (SH.fromText "#34"))),
(relative ["foo"], HQ'.HashQualified "bar" (fromJust (SH.fromText "#34"))),
let s = "foo.bar.+"
in scope s . expect $
parseShortHashOrHQSplit' s
== (Right . Right)
(relative ["foo", "bar"], HQ'.NameOnly (NameSegment "+")),
(relative ["foo", "bar"], HQ'.NameOnly "+"),
let s = "#123"
in scope s . expect $
parseShortHashOrHQSplit' s
@ -61,13 +33,13 @@ test =
scope "parseHQ'Split'" . tests $
[ let s = "foo.bar#34"
in scope s . expect $
parseHQSplit' s == Right (relative ["foo"], HQ'.HashQualified (NameSegment "bar") (fromJust (SH.fromText "#34"))),
parseHQSplit' s == Right (relative ["foo"], HQ'.HashQualified "bar" (fromJust (SH.fromText "#34"))),
let s = "foo.bar.+"
in scope s . expect $
parseHQSplit' s == Right (relative ["foo", "bar"], HQ'.NameOnly (NameSegment "+")),
parseHQSplit' s == Right (relative ["foo", "bar"], HQ'.NameOnly "+"),
let s = "#123" in scope s . expect $ isLeft $ parseHQSplit' s
]
]
relative :: Seq Text -> Path'
relative = Path' . Right . Relative . Path . fmap NameSegment
relative :: Seq NameSegment -> Path'
relative = Path' . Right . Relative . Path

View File

@ -189,7 +189,7 @@ library
Unison.Util.PinBoard
Unison.Util.Pretty.MegaParsec
Unison.Util.RefPromise
Unison.Util.Star3
Unison.Util.Star2
Unison.Util.Text
Unison.Util.Text.Pattern
Unison.Util.TQueue

View File

@ -70,3 +70,5 @@ ghc-options:
# See https://github.com/haskell/haskell-language-server/issues/208
"$everything": -haddock
statistics: -fsimpl-tick-factor=10000 # statistics fails on GHC 9 without this, https://github.com/haskell/statistics/issues/173

View File

@ -402,7 +402,7 @@ popd = do
setMostRecentNamespace :: Path.Absolute -> Cli ()
setMostRecentNamespace =
runTransaction . Queries.setMostRecentNamespace . map NameSegment.toText . Path.toList . Path.unabsolute
runTransaction . Queries.setMostRecentNamespace . map NameSegment.toUnescapedText . Path.toList . Path.unabsolute
respond :: Output -> Cli ()
respond output = do

View File

@ -63,7 +63,6 @@ module Unison.Cli.MonadUtils
-- * Patches
-- ** Default patch
defaultPatchNameSegment,
defaultPatchPath,
-- ** Getting patches
@ -112,7 +111,7 @@ import Unison.Codebase.ShortCausalHash qualified as SCH
import Unison.HashQualified qualified as HQ
import Unison.HashQualified' qualified as HQ'
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment)
import Unison.NameSegment qualified as NameSegment
import Unison.Names (Names)
import Unison.Parser.Ann (Ann (..))
import Unison.Prelude
@ -498,13 +497,10 @@ getTypesAt path = do
------------------------------------------------------------------------------------------------------------------------
-- Getting patches
defaultPatchNameSegment :: NameSegment
defaultPatchNameSegment = "patch"
-- | The default patch path.
defaultPatchPath :: Path.Split'
defaultPatchPath =
(Path.RelativePath' (Path.Relative Path.empty), defaultPatchNameSegment)
(Path.RelativePath' (Path.Relative Path.empty), NameSegment.defaultPatchSegment)
-- | Get the patch at a path, or the empty patch if there's no such patch.
getPatchAt :: Path.Split' -> Cli Patch

View File

@ -17,6 +17,7 @@ module Unison.Cli.Pretty
prettyHash32,
prettyHumanReadableTime,
prettyLabeledDependencies,
prettyPath,
prettyPath',
prettyProjectAndBranchName,
prettyBranchName,
@ -159,7 +160,7 @@ prettyShareLink :: WriteShareRemoteNamespace -> Pretty
prettyShareLink WriteShareRemoteNamespace {repo, path} =
let encodedPath =
Path.toList path
& fmap (URI.encodeText . NameSegment.toText)
& fmap (URI.encodeText . NameSegment.toUnescapedText)
& Text.intercalate "/"
in P.green . P.text $ shareOrigin <> "/@" <> shareUserHandleToText repo <> "/p/code/latest/namespaces/" <> encodedPath
@ -176,6 +177,12 @@ prettyFilePath :: FilePath -> Pretty
prettyFilePath fp =
P.blue (P.string fp)
prettyPath :: Path.Path -> Pretty
prettyPath path =
if path == Path.empty
then "the current namespace"
else P.blue (P.shown path)
prettyPath' :: Path.Path' -> Pretty
prettyPath' p' =
if Path.isCurrentPath p'

View File

@ -38,6 +38,6 @@ loadUniqueTypeGuid currentPath name0 = do
-- an appropriate time, such as after the current unison file finishes parsing).
let loadBranchAtPath :: [NameSegment] -> Sqlite.Transaction (Maybe (Codebase.Branch.Branch Sqlite.Transaction))
loadBranchAtPath segments =
Operations.loadBranchAtPath Nothing (map NameSegment.toText segments)
Operations.loadBranchAtPath Nothing (map NameSegment.toUnescapedText segments)
Codebase.loadUniqueTypeGuid loadBranchAtPath (Foldable.toList @Seq branchPath) name

View File

@ -22,15 +22,15 @@ import Unison.Codebase.Editor.RemoteRepo qualified as RemoteRepo
import Unison.Codebase.Editor.UriParser qualified as UriParser
import Unison.Codebase.Path (Path' (..))
import Unison.Codebase.Path qualified as Path
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Syntax.NameSegment qualified as NameSegment
configKey :: Text -> Path.Absolute -> Text
configKey k p =
Text.intercalate "." . toList $
k
:<| fmap
NameSegment.toText
NameSegment.toEscapedText
(Path.toSeq $ Path.unabsolute p)
gitUrlKey :: Path.Absolute -> Text

View File

@ -32,6 +32,7 @@ import System.Directory (XdgDirectory (..), createDirectoryIfMissing, doesFileEx
import System.Exit (ExitCode (..))
import System.FilePath ((</>))
import System.Process (callProcess, readCreateProcessWithExitCode, shell)
import Text.Megaparsec qualified as Megaparsec
import U.Codebase.Branch.Diff qualified as V2Branch.Diff
import U.Codebase.Causal qualified as V2Causal
import U.Codebase.HashTags (CausalHash (..))
@ -178,9 +179,11 @@ import Unison.Share.Codeserver qualified as Codeserver
import Unison.ShortHash qualified as SH
import Unison.Sqlite qualified as Sqlite
import Unison.Symbol (Symbol)
import Unison.Syntax.HashQualified qualified as HQ (fromString, toString, toText, unsafeFromString)
import Unison.Syntax.HashQualified qualified as HQ (parseText, parseTextWith, toText, unsafeParseText)
import Unison.Syntax.Lexer qualified as L
import Unison.Syntax.Name qualified as Name (toString, toText, toVar, unsafeFromVar)
import Unison.Syntax.Lexer qualified as Lexer
import Unison.Syntax.Name qualified as Name (toText, toVar, unsafeParseVar)
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Syntax.Parser qualified as Parser
import Unison.Syntax.TermPrinter qualified as TP
import Unison.Term (Term)
@ -200,7 +203,7 @@ import Unison.Util.Pretty qualified as Pretty
import Unison.Util.Relation qualified as R
import Unison.Util.Relation qualified as Relation
import Unison.Util.Set qualified as Set
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
import Unison.Util.TransitiveClosure (transitiveClosure)
import Unison.Var (Var)
import Unison.Var qualified as Var
@ -801,7 +804,7 @@ loop e = do
(seg, _) <- Map.toList (Branch._edits b)
]
Cli.respond $ ListOfPatches $ Set.fromList patches
Cli.setNumberedArgs $ fmap Name.toString patches
Cli.setNumberedArgs $ fmap (Text.unpack . Name.toText) patches
FindShallowI pathArg -> do
Cli.Env {codebase} <- ask
@ -820,11 +823,11 @@ loop e = do
where
entryToHQString :: ShallowListEntry v Ann -> String
entryToHQString e =
fixup case e of
ShallowTypeEntry te -> Text.unpack $ Backend.typeEntryDisplayName te
ShallowTermEntry te -> Text.unpack $ Backend.termEntryDisplayName te
ShallowBranchEntry ns _ _ -> NameSegment.toString ns
ShallowPatchEntry ns -> NameSegment.toString ns
fixup $ Text.unpack case e of
ShallowTypeEntry te -> Backend.typeEntryDisplayName te
ShallowTermEntry te -> Backend.termEntryDisplayName te
ShallowBranchEntry ns _ _ -> NameSegment.toEscapedText ns
ShallowPatchEntry ns -> NameSegment.toEscapedText ns
where
fixup s = case pathArgStr of
"" -> s
@ -904,8 +907,8 @@ loop e = do
ambiguous t rs =
Cli.returnEarly case t of
HQ.HashOnly h -> HashAmbiguous h rs'
(Path.parseHQSplit' . HQ.toString -> Right n) -> DeleteNameAmbiguous hqLength n rs' Set.empty
_ -> BadName (HQ.toString t)
(Path.parseHQSplit' . Text.unpack . HQ.toText -> Right n) -> DeleteNameAmbiguous hqLength n rs' Set.empty
_ -> BadName (HQ.toText t)
where
rs' = Set.map Referent.Ref $ Set.fromList rs
@ -1045,9 +1048,9 @@ loop e = do
hqLength <- Cli.runTransaction Codebase.hashLength
uf <- Cli.expectLatestTypecheckedFile
let datas, effects, terms :: [(Name, Reference.Id)]
datas = [(Name.unsafeFromVar v, r) | (v, (r, _d)) <- Map.toList $ UF.dataDeclarationsId' uf]
effects = [(Name.unsafeFromVar v, r) | (v, (r, _e)) <- Map.toList $ UF.effectDeclarationsId' uf]
terms = [(Name.unsafeFromVar v, r) | (v, (_, r, _wk, _tm, _tp)) <- Map.toList $ UF.hashTermsId uf]
datas = [(Name.unsafeParseVar v, r) | (v, (r, _d)) <- Map.toList $ UF.dataDeclarationsId' uf]
effects = [(Name.unsafeParseVar v, r) | (v, (r, _e)) <- Map.toList $ UF.effectDeclarationsId' uf]
terms = [(Name.unsafeParseVar v, r) | (v, (_, r, _wk, _tm, _tp)) <- Map.toList $ UF.hashTermsId uf]
Cli.respond $ DumpUnisonFileHashes hqLength datas effects terms
DebugTabCompletionI inputs -> do
Cli.Env {authHTTPClient, codebase} <- ask
@ -1107,9 +1110,9 @@ loop e = do
Branch0 terms0 types0 children0 patches0 _ _ _ _ _ ->
let ignoreMetadata :: (Ord r, Ord n) => Metadata.Star r n -> r -> (r, Set n)
ignoreMetadata s r =
(r, R.lookupDom r $ Star3.d1 s)
terms = Map.fromList . map (ignoreMetadata terms0) . Foldable.toList $ Star3.fact terms0
types = Map.fromList . map (ignoreMetadata types0) . Foldable.toList $ Star3.fact types0
(r, R.lookupDom r $ Star2.d1 s)
terms = Map.fromList . map (ignoreMetadata terms0) . Foldable.toList $ Star2.fact terms0
types = Map.fromList . map (ignoreMetadata types0) . Foldable.toList $ Star2.fact types0
patches = fmap fst patches0
children = fmap Branch.headHash children0
in do
@ -1127,14 +1130,14 @@ loop e = do
[ Monoid.unlessM (null causalParents) $ P.lit "Causal Parents:" <> P.newline <> P.indentN 2 (P.lines (map P.shown $ Set.toList causalParents)),
Monoid.unlessM (null terms) $ P.lit "Terms:" <> P.newline <> P.indentN 2 (P.lines (map (prettyDefn Referent.toText) $ Map.toList terms)),
Monoid.unlessM (null types) $ P.lit "Types:" <> P.newline <> P.indentN 2 (P.lines (map (prettyDefn Reference.toText) $ Map.toList types)),
Monoid.unlessM (null patches) $ P.lit "Patches:" <> P.newline <> P.indentN 2 (P.column2 (map (bimap (P.text . NameSegment.toText) P.shown) $ Map.toList patches)),
Monoid.unlessM (null children) $ P.lit "Children:" <> P.newline <> P.indentN 2 (P.column2 (map (bimap (P.text . NameSegment.toText) P.shown) $ Map.toList children))
Monoid.unlessM (null patches) $ P.lit "Patches:" <> P.newline <> P.indentN 2 (P.column2 (map (bimap (P.text . NameSegment.toEscapedText) P.shown) $ Map.toList patches)),
Monoid.unlessM (null children) $ P.lit "Children:" <> P.newline <> P.indentN 2 (P.column2 (map (bimap (P.text . NameSegment.toEscapedText) P.shown) $ Map.toList children))
]
)
where
prettyRef renderR r = P.indentN 2 $ P.text (renderR r)
prettyDefn renderR (r, Foldable.toList -> names) =
P.lines (P.text . NameSegment.toText <$> if null names then [NameSegment "<unnamed>"] else names) <> P.newline <> prettyRef renderR r
P.lines (P.text <$> if null names then ["<unnamed>"] else NameSegment.toEscapedText <$> names) <> P.newline <> prettyRef renderR r
rootBranch <- Cli.getRootBranch
void . liftIO . flip State.execStateT mempty $ goCausal [getCausal rootBranch]
DebugDumpNamespaceSimpleI -> do
@ -1319,7 +1322,7 @@ inputDescription input =
scope <- p' scope0
pure ("patch " <> p <> " " <> scope)
UndoI {} -> pure "undo"
ExecuteI s args -> pure ("execute " <> Text.unwords (fmap Text.pack (s : args)))
ExecuteI s args -> pure ("execute " <> Text.unwords (s : fmap Text.pack args))
IOTestI hq -> pure ("io.test " <> HQ.toText hq)
IOTestAllI -> pure "io.test.all"
UpdateBuiltinsI -> pure "builtins.update"
@ -1327,14 +1330,14 @@ inputDescription input =
MergeIOBuiltinsI -> pure "builtins.mergeio"
MakeStandaloneI out nm -> pure ("compile " <> Text.pack out <> " " <> HQ.toText nm)
ExecuteSchemeI nm args ->
pure $ "run.native " <> Text.unwords (fmap Text.pack (nm : args))
CompileSchemeI fi nm -> pure ("compile.native " <> HQ.toText nm <> " " <> Text.pack fi)
pure $ "run.native " <> Text.unwords (nm : fmap Text.pack args)
CompileSchemeI fi nm -> pure ("compile.native " <> HQ.toText nm <> " " <> fi)
GenSchemeLibsI mdir ->
pure $
"compile.native.genlibs" <> Text.pack (maybe "" (" " ++) mdir)
FetchSchemeCompilerI name branch ->
pure ("compile.native.fetch" <> Text.pack name <> " " <> Text.pack branch)
CreateAuthorI (NameSegment id) name -> pure ("create.author " <> id <> " " <> name)
CreateAuthorI id name -> pure ("create.author " <> NameSegment.toEscapedText id <> " " <> name)
RemoveTermReplacementI src p0 -> do
p <- opatch p0
pure ("delete.term-replacement" <> HQ.toText src <> " " <> p)
@ -1348,7 +1351,6 @@ inputDescription input =
pure (Text.unwords ["diff.namespace.to-patch", branchId1, branchId2, patch])
ClearI {} -> pure "clear"
DocToMarkdownI name -> pure ("debug.doc-to-markdown " <> Name.toText name)
UpgradeI old new -> pure (Text.unwords ["upgrade", NameSegment.toText old, NameSegment.toText new])
--
ApiI -> wat
AuthLoginI {} -> wat
@ -1414,6 +1416,7 @@ inputDescription input =
TodoI {} -> wat
UiI {} -> wat
UpI {} -> wat
UpgradeI {} -> wat
VersionI -> wat
where
hp' :: Either SCH.ShortCausalHash Path' -> Cli Text
@ -1434,7 +1437,7 @@ inputDescription input =
hqs' :: Path.HQSplit' -> Cli Text
hqs' (p0, hq) = do
p <- if Path.isRoot' p0 then pure mempty else p' p0
pure (p <> "." <> HQ'.toTextWith NameSegment.toText hq)
pure (p <> "." <> HQ'.toTextWith NameSegment.toEscapedText hq)
hqs (p, hq) = hqs' (Path' . Right . Path.Relative $ p, hq)
ps' = p' . Path.unsplit'
looseCodeOrProjectToText :: Input.LooseCodeOrProject -> Cli Text
@ -1494,8 +1497,14 @@ handleFindI isVerbose fscope ws input = do
searchResultsFor names (Set.toList matches) []
-- name query
(map HQ.unsafeFromString -> qs) -> do
let srs = searchBranchScored names fuzzyNameDistance qs
qs -> do
let anythingBeforeHash :: Megaparsec.Parsec (Lexer.Token Text) [Char] Text
anythingBeforeHash = Text.pack <$> Megaparsec.takeWhileP Nothing (/= '#')
let srs =
searchBranchScored
names
Find.simpleFuzzyScore
(mapMaybe (HQ.parseTextWith anythingBeforeHash . Text.pack) qs)
pure $ uniqueBy SR.toReferent srs
let respondResults results = do
Cli.setNumberedArgs $ fmap searchResultToHQString results
@ -1507,7 +1516,7 @@ handleFindI isVerbose fscope ws input = do
Cli.respond FindNoLocalMatches
-- We've already searched everything else, so now we search JUST the
-- names in lib.
let mayOnlyLibBranch = currentBranch0 & Branch.children %%~ (\cs -> Map.singleton "lib" <$> Map.lookup "lib" cs)
let mayOnlyLibBranch = currentBranch0 & Branch.children %%~ \cs -> Map.singleton NameSegment.libSegment <$> Map.lookup NameSegment.libSegment cs
case mayOnlyLibBranch of
Nothing -> respondResults []
Just onlyLibBranch -> do
@ -1584,7 +1593,7 @@ handleDependents hq = do
r <- Set.toList dependents
Just (isTerm, hq) <- [(True,) <$> PPE.terms fqppe (Referent.Ref r), (False,) <$> PPE.types fqppe r]
fullName <- [HQ'.toName hq]
guard (not (Name.beginsWithSegment fullName Name.libSegment))
guard (not (Name.beginsWithSegment fullName NameSegment.libSegment))
Just shortName <- pure $ PPE.terms ppe (Referent.Ref r) <|> PPE.types ppe r
pure (isTerm, HQ'.toHQ shortName, r)
pure results
@ -1823,15 +1832,10 @@ confirmedCommand i = do
-- | restores the full hash to these search results, for _numberedArgs purposes
searchResultToHQString :: SearchResult -> String
searchResultToHQString = \case
SR.Tm' n r _ -> HQ.toString $ HQ.requalify n r
SR.Tp' n r _ -> HQ.toString $ HQ.requalify n (Referent.Ref r)
SR.Tm' n r _ -> Text.unpack $ HQ.toText $ HQ.requalify n r
SR.Tp' n r _ -> Text.unpack $ HQ.toText $ HQ.requalify n (Referent.Ref r)
_ -> error "impossible match failure"
-- Return a list of definitions whose names fuzzy match the given queries.
fuzzyNameDistance :: Name -> Name -> Maybe Int
fuzzyNameDistance (Name.toString -> q) (Name.toString -> n) =
Find.simpleFuzzyScore q n
-- return `name` and `name.<everything>...`
_searchBranchPrefix :: Branch m -> Name -> [SearchResult]
_searchBranchPrefix b n = case Path.unsnoc (Path.fromName n) of
@ -1866,8 +1870,8 @@ searchBranchScored ::
forall score.
(Ord score) =>
Names ->
(Name -> Name -> Maybe score) ->
[HQ.HashQualified Name] ->
(Text -> Text -> Maybe score) ->
[HQ.HashQualified Text] ->
[SearchResult]
searchBranchScored names0 score queries =
nubOrd
@ -1877,9 +1881,9 @@ searchBranchScored names0 score queries =
where
searchTermNamespace = queries >>= do1query
where
do1query :: HQ.HashQualified Name -> [(Maybe score, SearchResult)]
do1query :: HQ.HashQualified Text -> [(Maybe score, SearchResult)]
do1query q = mapMaybe (score1hq q) (R.toList . Names.terms $ names0)
score1hq :: HQ.HashQualified Name -> (Name, Referent) -> Maybe (Maybe score, SearchResult)
score1hq :: HQ.HashQualified Text -> (Name, Referent) -> Maybe (Maybe score, SearchResult)
score1hq query (name, ref) = case query of
HQ.NameOnly qn ->
pair qn
@ -1893,12 +1897,12 @@ searchBranchScored names0 score queries =
where
result = SR.termSearchResult names0 name ref
pair qn =
(\score -> (Just score, result)) <$> score qn name
(\score -> (Just score, result)) <$> score qn (Name.toText name)
searchTypeNamespace = queries >>= do1query
where
do1query :: HQ.HashQualified Name -> [(Maybe score, SearchResult)]
do1query :: HQ.HashQualified Text -> [(Maybe score, SearchResult)]
do1query q = mapMaybe (score1hq q) (R.toList . Names.types $ names0)
score1hq :: HQ.HashQualified Name -> (Name, Reference) -> Maybe (Maybe score, SearchResult)
score1hq :: HQ.HashQualified Text -> (Name, Reference) -> Maybe (Maybe score, SearchResult)
score1hq query (name, ref) = case query of
HQ.NameOnly qn ->
pair qn
@ -1912,12 +1916,12 @@ searchBranchScored names0 score queries =
where
result = SR.typeSearchResult names0 name ref
pair qn =
(\score -> (Just score, result)) <$> score qn name
(\score -> (Just score, result)) <$> score qn (Name.toText name)
compilerPath :: Path.Path'
compilerPath = Path.Path' {Path.unPath' = Left abs}
where
segs = NameSegment <$> ["unison", "internal"]
segs = ["unison", "internal"]
rootPath = Path.Path {Path.toSeq = Seq.fromList segs}
abs = Path.Absolute {Path.unabsolute = rootPath}
@ -1980,20 +1984,17 @@ doGenerateSchemeBoot force mppe mdir = do
gen ppe saveWrap cwrapf dirTm compoundWrapName
where
a = External
hq nm
| Just hqn <- HQ.fromString nm = hqn
| otherwise = error $ "internal error: cannot hash qualify: " ++ nm
sbName = hq ".unison.internal.compiler.scheme.saveBaseFile"
swName = hq ".unison.internal.compiler.scheme.saveWrapperFile"
sdName = hq ".unison.internal.compiler.scheme.saveDataInfoFile"
dinfoName = hq ".unison.internal.compiler.scheme.dataInfos"
bootName = hq ".unison.internal.compiler.scheme.bootSpec"
builtinName = hq ".unison.internal.compiler.scheme.builtinSpec"
sbName = HQ.unsafeParseText ".unison.internal.compiler.scheme.saveBaseFile"
swName = HQ.unsafeParseText ".unison.internal.compiler.scheme.saveWrapperFile"
sdName = HQ.unsafeParseText ".unison.internal.compiler.scheme.saveDataInfoFile"
dinfoName = HQ.unsafeParseText ".unison.internal.compiler.scheme.dataInfos"
bootName = HQ.unsafeParseText ".unison.internal.compiler.scheme.bootSpec"
builtinName = HQ.unsafeParseText ".unison.internal.compiler.scheme.builtinSpec"
simpleWrapName =
hq ".unison.internal.compiler.scheme.simpleWrapperSpec"
HQ.unsafeParseText ".unison.internal.compiler.scheme.simpleWrapperSpec"
compoundWrapName =
hq ".unison.internal.compiler.scheme.compoundWrapperSpec"
HQ.unsafeParseText ".unison.internal.compiler.scheme.compoundWrapperSpec"
gen ppe save file dir nm =
liftIO (doesFileExist file) >>= \b -> when (not b || force) do
@ -2015,10 +2016,10 @@ typecheckAndEval ppe tm = do
Result.Result notes Nothing -> do
currentPath <- Cli.getCurrentPath
let tes = [err | Result.TypeError err <- toList notes]
Cli.returnEarly (TypeErrors currentPath (Text.pack rendered) ppe tes)
Cli.returnEarly (TypeErrors currentPath rendered ppe tes)
where
a = External
rendered = P.toPlainUnbroken $ TP.pretty ppe tm
rendered = Text.pack (P.toPlainUnbroken $ TP.pretty ppe tm)
ensureSchemeExists :: Cli ()
ensureSchemeExists =
@ -2062,16 +2063,16 @@ runScheme file args = do
unless success $
Cli.returnEarly (PrintMessage "Scheme evaluation failed.")
buildScheme :: String -> String -> Cli ()
buildScheme :: Text -> String -> Cli ()
buildScheme main file = do
ensureSchemeExists
statDir <- getSchemeStaticLibDir
genDir <- getSchemeGenLibDir
buildRacket genDir statDir main file
buildRacket :: String -> String -> String -> String -> Cli ()
buildRacket :: String -> String -> Text -> String -> Cli ()
buildRacket genDir statDir main file =
let args = ["-l", "raco", "--", "exe", "-o", main, file]
let args = ["-l", "raco", "--", "exe", "-o", Text.unpack main, file]
opts = racketOpts genDir statDir args
in void . liftIO $
catch
@ -2095,25 +2096,25 @@ doCompile native output main = do
)
(Cli.returnEarly . EvaluationFailure)
doRunAsScheme :: String -> [String] -> Cli ()
doRunAsScheme main0 args = case HQ.fromString main0 of
doRunAsScheme :: Text -> [String] -> Cli ()
doRunAsScheme main0 args = case HQ.parseText main0 of
Just main -> do
fullpath <- generateSchemeFile True main0 main
runScheme fullpath args
Nothing -> Cli.respond $ BadName main0
doCompileScheme :: String -> HQ.HashQualified Name -> Cli ()
doCompileScheme :: Text -> HQ.HashQualified Name -> Cli ()
doCompileScheme out main =
generateSchemeFile True out main >>= buildScheme out
generateSchemeFile :: Bool -> String -> HQ.HashQualified Name -> Cli String
generateSchemeFile :: Bool -> Text -> HQ.HashQualified Name -> Cli String
generateSchemeFile exec out main = do
(comp, ppe) <- resolveMainRef main
ensureCompilerExists
doGenerateSchemeBoot False (Just ppe) Nothing
cacheDir <- getCacheDir
liftIO $ createDirectoryIfMissing True (cacheDir </> "scheme-tmp")
let scratch = out ++ ".scm"
let scratch = Text.unpack out ++ ".scm"
fullpath = cacheDir </> "scheme-tmp" </> scratch
output = Text.pack fullpath
sscm <- Term.ref a <$> resolveTermRef saveNm
@ -2128,12 +2129,9 @@ generateSchemeFile exec out main = do
pure fullpath
where
a = External
hq nm
| Just hqn <- HQ.fromString nm = hqn
| otherwise = error $ "internal error: cannot hash qualify: " ++ nm
saveNm = hq ".unison.internal.compiler.saveScheme"
filePathNm = hq "FilePath.FilePath"
saveNm = HQ.unsafeParseText ".unison.internal.compiler.saveScheme"
filePathNm = HQ.unsafeParseText "FilePath.FilePath"
delete ::
Input ->
@ -2286,7 +2284,7 @@ displayI outputLoc hq = do
let suffixifiedPPE = PPE.suffixifiedPPE pped
let bias = maybeToList $ HQ.toName hq
latestTypecheckedFile <- Cli.getLatestTypecheckedFile
case addWatch (HQ.toString hq) latestTypecheckedFile of
case addWatch (Text.unpack (HQ.toText hq)) latestTypecheckedFile of
Nothing -> do
let results = Names.lookupHQTerm Names.IncludeSuffixes hq names
ref <-
@ -2304,7 +2302,7 @@ displayI outputLoc hq = do
let suffixifiedFilePPE = PPE.biasTo bias $ PPE.suffixifiedPPE filePPED
(_, watches) <- evalUnisonFile Sandboxed suffixifiedFilePPE unisonFile []
(_, _, _, _, tm, _) <-
Map.lookup toDisplay watches & onNothing (error $ "Evaluation dropped a watch expression: " <> HQ.toString hq)
Map.lookup toDisplay watches & onNothing (error $ "Evaluation dropped a watch expression: " <> Text.unpack (HQ.toText hq))
let ns = UF.addNamesFromTypeCheckedUnisonFile unisonFile names
doDisplay outputLoc ns tm
@ -2323,7 +2321,7 @@ docsI src = do
in Name.convert hq'
dotDoc :: HQ.HashQualified Name
dotDoc = hq <&> \n -> Name.joinDot n "doc"
dotDoc = hq <&> \n -> Name.joinDot n (Name.fromSegment "doc")
findInScratchfileByName :: Cli ()
findInScratchfileByName = do
@ -2382,7 +2380,7 @@ parseType input src = do
Parsers.parseType (Text.unpack (fst lexed)) parsingEnv & onLeftM \err ->
Cli.returnEarly (TypeParseError src err)
Type.bindNames Name.unsafeFromVar mempty names (Type.generalizeLowercase mempty typ) & onLeft \errs ->
Type.bindNames Name.unsafeParseVar mempty names (Type.generalizeLowercase mempty typ) & onLeft \errs ->
Cli.returnEarly (ParseResolutionFailures src (toList errs))
-- Adds a watch expression of the given name to the file, if

View File

@ -22,6 +22,7 @@ import Unison.HashQualified qualified as HQ
import Unison.HashQualified' qualified as HQ'
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment qualified as NameSegment
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.NamesWithHistory qualified as Names
@ -76,7 +77,7 @@ handleStructuredFindI rule = do
r <- Set.toList (Relation.ran $ Names.terms names)
Just hq <- [PPE.terms fqppe r]
fullName <- [HQ'.toName hq]
guard (not (Name.beginsWithSegment fullName Name.libSegment))
guard (not (Name.beginsWithSegment fullName NameSegment.libSegment))
Referent.Ref _ <- pure r
Just shortName <- [PPE.terms (PPED.suffixifiedPPE ppe) r]
pure (HQ'.toHQ shortName, r)

View File

@ -65,7 +65,7 @@ formatFile makePPEDForFile formattingWidth currentPath inputParsedFile inputType
)
& Map.filter (\(tldAnn, _, _) -> isInFormatRange tldAnn)
& itraverse \sym (tldAnn, ref, decl) -> do
symName <- hoistMaybe (Name.fromVar sym)
symName <- hoistMaybe (Name.parseVar sym)
let declNameSegments = NEL.appendr (Path.toList (Path.unabsolute currentPath)) (Name.segments symName)
let declName = Name.fromSegments declNameSegments
let hqName = HQ.fromName symName
@ -84,7 +84,7 @@ formatFile makePPEDForFile formattingWidth currentPath inputParsedFile inputType
(FileSummary.termsBySymbol fileSummary)
& Map.filter (\(tldAnn, _, trm, _) -> shouldFormatTerm tldAnn trm)
& itraverse \sym (tldAnn, mayRefId, trm, _typ) -> do
symName <- hoistMaybe (Name.fromVar sym)
symName <- hoistMaybe (Name.parseVar sym)
let defNameSegments = NEL.appendr (Path.toList (Path.unabsolute currentPath)) (Name.segments symName)
let defName = Name.fromSegments defNameSegments
let hqName = HQ.NameOnly symName

View File

@ -22,7 +22,7 @@ import Unison.DataDeclaration qualified as DD
import Unison.LabeledDependency (LabeledDependency)
import Unison.LabeledDependency qualified as LD
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment qualified as NameSegment
import Unison.Names qualified as Names
import Unison.Prelude
import Unison.PrettyPrintEnvDecl qualified as PPED
@ -97,4 +97,4 @@ namespaceDependencies codebase branch = do
pure onlyExternalDeps
where
branchWithoutLibdeps = branch & over Branch.children (Map.delete Name.libSegment)
branchWithoutLibdeps = branch & over Branch.children (Map.delete NameSegment.libSegment)

View File

@ -23,8 +23,7 @@ import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Editor.HandleInput.Pull qualified as Pull
import Unison.Codebase.Editor.Output qualified as Output
import Unison.Codebase.Path qualified as Path
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Project (ProjectAndBranch (..), ProjectBranchName, ProjectName)
import Unison.Share.API.Hash qualified as Share.API
@ -137,12 +136,12 @@ projectCreate tryDownloadingBase maybeProjectName = do
projectBranchLibBaseObject =
over
Branch.children
(Map.insert (NameSegment "base") baseLatestReleaseBranchObject)
(Map.insert "base" baseLatestReleaseBranchObject)
Branch.empty0
projectBranchLibObject = Branch.cons projectBranchLibBaseObject Branch.empty
in over
Branch.children
(Map.insert Name.libSegment projectBranchLibObject)
(Map.insert NameSegment.libSegment projectBranchLibObject)
Branch.empty0
Cli.stepAt reflogDescription (Path.unabsolute path, const projectBranchObject)

View File

@ -51,6 +51,7 @@ import Unison.CommandLine.InputPattern qualified as InputPattern
import Unison.CommandLine.InputPatterns qualified as InputPatterns
import Unison.Core.Project (ProjectBranchName (UnsafeProjectBranchName))
import Unison.NameSegment (NameSegment (..))
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Project (ProjectAndBranch (..), ProjectBranchNameOrLatestRelease (..), ProjectName)
import Unison.Share.API.Hash (HashJWT)
@ -329,13 +330,13 @@ loadPropagateDiffDefaultPatch inputDescription maybeDest0 dest = do
Cli.respond Output.AboutToPropagatePatch
Cli.time "loadPropagateDiffDefaultPatch" do
original <- Cli.getBranch0At dest
patch <- liftIO $ Branch.getPatch Cli.defaultPatchNameSegment original
patch <- liftIO $ Branch.getPatch NameSegment.defaultPatchSegment original
patchDidChange <- propagatePatch inputDescription patch dest
when patchDidChange do
whenJust maybeDest0 \dest0 -> do
Cli.respond Output.CalculatingDiff
patched <- Cli.getBranchAt dest
let patchPath = Path.Path' (Right (Path.Relative (Path.fromList [Cli.defaultPatchNameSegment])))
let patchPath = Path.Path' (Right (Path.Relative (Path.fromList [NameSegment.defaultPatchSegment])))
(ppe, diff) <- diffHelper original (Branch.head patched)
Cli.respondNumbered (ShowDiffAfterMergePropagate dest0 dest patchPath ppe diff)

View File

@ -40,7 +40,7 @@ import Unison.UnisonFile qualified as UF
import Unison.UnisonFile.Names qualified as UF
import Unison.Var qualified as Var
handleRun :: Bool -> String -> [String] -> Cli ()
handleRun :: Bool -> Text -> [String] -> Cli ()
handleRun native main args = do
(unisonFile, mainResType) <- do
(sym, term, typ, otyp) <- getTerm main
@ -75,7 +75,7 @@ data GetTermResult
-- | Look up runnable term with the given name in the codebase or
-- latest typechecked unison file. Return its symbol, term, type, and
-- the type of the evaluated term.
getTerm :: String -> Cli (Symbol, Term Symbol Ann, Type Symbol Ann, Type Symbol Ann)
getTerm :: Text -> Cli (Symbol, Term Symbol Ann, Type Symbol Ann, Type Symbol Ann)
getTerm main =
getTerm' main >>= \case
NoTermWithThatName -> do
@ -90,7 +90,7 @@ getTerm main =
Cli.returnEarly $ Output.BadMainFunction "run" main ty suffixifiedPPE [mainType]
GetTermSuccess x -> pure x
getTerm' :: String -> Cli GetTermResult
getTerm' :: Text -> Cli GetTermResult
getTerm' mainName =
let getFromCodebase = do
Cli.Env {codebase, runtime} <- ask
@ -108,7 +108,7 @@ getTerm' mainName =
pure (GetTermSuccess (v, tm, typ, otyp))
getFromFile uf = do
let components = join $ UF.topLevelComponents uf
let mainComponent = filter ((\v -> Var.nameStr v == mainName) . view _1) components
let mainComponent = filter ((\v -> Var.name v == mainName) . view _1) components
case mainComponent of
[(v, _, tm, ty)] ->
checkType ty \otyp ->

View File

@ -31,7 +31,7 @@ import Unison.PrettyPrintEnvDecl qualified as PPED
import Unison.Reference (Reference)
import Unison.Referent (Referent, pattern Con, pattern Ref)
import Unison.Symbol (Symbol)
import Unison.Syntax.HashQualified qualified as HQ (toString)
import Unison.Syntax.HashQualified qualified as HQ (toText)
import Unison.Type (Type)
import Unison.Typechecker qualified as Typechecker
@ -118,7 +118,7 @@ resolveMainRef main = do
pped <- Cli.prettyPrintEnvDeclFromNames names
let suffixifiedPPE = PPED.suffixifiedPPE pped
let mainType = Runtime.mainType runtime
smain = HQ.toString main
smain = HQ.toText main
lookupTermRefWithType codebase main >>= \case
[(rf, ty)]
| Typechecker.fitsScheme ty mainType -> pure (rf, suffixifiedPPE)

View File

@ -134,7 +134,7 @@ handleIOTest main = do
(fails, oks) <-
refs & foldMapM \(ref, typ) -> do
when (not $ isIOTest typ) do
Cli.returnEarly (BadMainFunction "io.test" (HQ.toString main) typ suffixifiedPPE (Foldable.toList $ Runtime.ioTestTypes runtime))
Cli.returnEarly (BadMainFunction "io.test" (HQ.toText main) typ suffixifiedPPE (Foldable.toList $ Runtime.ioTestTypes runtime))
runIOTest suffixifiedPPE ref
Cli.respond $ TestResults Output.NewlyComputed suffixifiedPPE True True oks fails
@ -180,7 +180,7 @@ resolveHQNames parseNames hqNames =
getNameFromScratchFile :: HQ.HashQualified Name -> MaybeT Cli (Reference.Id, Type.Type Symbol Ann)
getNameFromScratchFile main = do
typecheckedFile <- MaybeT Cli.getLatestTypecheckedFile
mainName <- hoistMaybe $ Name.fromText (HQ.toText main)
mainName <- hoistMaybe $ Name.parseText (HQ.toText main)
(_, ref, _wk, _term, typ) <- hoistMaybe $ Map.lookup (Name.toVar mainName) (UF.hashTermsId typecheckedFile)
pure (ref, typ)

View File

@ -53,7 +53,7 @@ import Unison.Referent qualified as Referent
import Unison.Result qualified as Result
import Unison.Sqlite qualified as Sqlite
import Unison.Symbol (Symbol)
import Unison.Syntax.Name qualified as Name (toVar, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toVar, unsafeParseVar)
import Unison.Term (Term)
import Unison.Term qualified as Term
import Unison.Type (Type)
@ -90,7 +90,7 @@ handleUpdate input optionalPatch requestedNames = do
typeEdits :: [(Name, Reference, Reference)]
typeEdits = do
v <- Set.toList (SC.types (updates sr))
let n = Name.unsafeFromVar v
let n = Name.unsafeParseVar v
let oldRefs0 = Names.typesNamed currentCodebaseNames n
let newRefs = Names.typesNamed fileNames n
case (,) <$> NESet.nonEmptySet oldRefs0 <*> Set.asSingleton newRefs of
@ -105,7 +105,7 @@ handleUpdate input optionalPatch requestedNames = do
termEdits :: [(Name, Reference, Reference)]
termEdits = do
v <- Set.toList (SC.terms (updates sr))
let n = Name.unsafeFromVar v
let n = Name.unsafeParseVar v
let oldRefs0 = Names.refTermsNamed currentCodebaseNames n
let newRefs = Names.refTermsNamed fileNames n
case (,) <$> NESet.nonEmptySet oldRefs0 <*> Set.asSingleton newRefs of
@ -215,7 +215,7 @@ getSlurpResultForUpdate requestedNames slurpCheckNames = do
Set.map Name.toVar . Names.namesForReferent slurpCheckNames . Referent.fromTermReferenceId
let nameToTermRefs :: Symbol -> Set TermReference
nameToTermRefs = Names.refTermsNamed slurpCheckNames . Name.unsafeFromVar
nameToTermRefs = Names.refTermsNamed slurpCheckNames . Name.unsafeParseVar
slurp1 <- do
Cli.Env {codebase} <- ask
@ -593,10 +593,10 @@ doSlurpAdds slurp uf = Branch.batchUpdates (typeActions <> termActions)
SC.terms slurp <> UF.constructorsForDecls (SC.types slurp) uf
names = UF.typecheckedToNames uf
doTerm :: Symbol -> (Path, Branch0 m -> Branch0 m)
doTerm v = case toList (Names.termsNamed names (Name.unsafeFromVar v)) of
doTerm v = case toList (Names.termsNamed names (Name.unsafeParseVar v)) of
[] -> errorMissingVar v
[r] ->
let split = Path.splitFromName (Name.unsafeFromVar v)
let split = Path.splitFromName (Name.unsafeParseVar v)
in BranchUtil.makeAddTermName split r
wha ->
error $
@ -605,10 +605,10 @@ doSlurpAdds slurp uf = Branch.batchUpdates (typeActions <> termActions)
<> ": "
<> show wha
doType :: Symbol -> (Path, Branch0 m -> Branch0 m)
doType v = case toList (Names.typesNamed names (Name.unsafeFromVar v)) of
doType v = case toList (Names.typesNamed names (Name.unsafeParseVar v)) of
[] -> errorMissingVar v
[r] ->
let split = Path.splitFromName (Name.unsafeFromVar v)
let split = Path.splitFromName (Name.unsafeParseVar v)
in BranchUtil.makeAddTypeName split r
wha ->
error $

View File

@ -59,7 +59,8 @@ import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.Name.Forward (ForwardName (..))
import Unison.Name.Forward qualified as ForwardName
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment (NameSegment (..))
import Unison.NameSegment qualified as NameSegment
import Unison.Names (Names (Names))
import Unison.Names qualified as Names
import Unison.Parser.Ann (Ann)
@ -102,7 +103,7 @@ handleUpdate2 = do
currentPath <- Cli.getCurrentPath
currentBranch0 <- Cli.getBranch0At currentPath
let namesIncludingLibdeps = Branch.toNames currentBranch0
let namesExcludingLibdeps = Branch.toNames (currentBranch0 & over Branch.children (Map.delete Name.libSegment))
let namesExcludingLibdeps = Branch.toNames (currentBranch0 & over Branch.children (Map.delete NameSegment.libSegment))
let ctorNames = forwardCtorNames namesExcludingLibdeps
Cli.respond Output.UpdateLookingForDependents
@ -228,7 +229,7 @@ typecheckedUnisonFileToBranchUpdates abort getConstructors tuf = do
makeDeclUpdates (symbol, (typeRefId, decl)) = do
-- some decls will be deleted, we want to delete their
-- constructors as well
deleteConstructorActions <- case maybe [] (map (BranchUtil.makeAnnihilateTermName . Path.splitFromName)) <$> getConstructors (Name.unsafeFromVar symbol) of
deleteConstructorActions <- case maybe [] (map (BranchUtil.makeAnnihilateTermName . Path.splitFromName)) <$> getConstructors (Name.unsafeParseVar symbol) of
Left err -> abort err
Right actions -> pure actions
let deleteTypeAction = BranchUtil.makeAnnihilateTypeName split
@ -261,7 +262,7 @@ typecheckedUnisonFileToBranchUpdates abort getConstructors tuf = do
else []
splitVar :: Symbol -> Path.Split
splitVar = Path.splitFromName . Name.unsafeFromVar
splitVar = Path.splitFromName . Name.unsafeParseVar
-- | get references from `names` that have the same names as in `defns`
-- For constructors, we get the type reference.
@ -430,14 +431,14 @@ getTermAndDeclNames tuf =
UF.hashTermsId tuf
& Map.foldMapWithKey \var (_, _, wk, _, _) ->
if WK.watchKindShouldBeStoredInDatabase wk
then Set.singleton (Name.unsafeFromVar var)
then Set.singleton (Name.unsafeParseVar var)
else Set.empty
effects = keysToNames $ UF.effectDeclarationsId' tuf
datas = keysToNames $ UF.dataDeclarationsId' tuf
effectCtors = foldMap ctorsToNames $ fmap (Decl.toDataDecl . snd) $ UF.effectDeclarationsId' tuf
dataCtors = foldMap ctorsToNames $ fmap snd $ UF.dataDeclarationsId' tuf
keysToNames = Set.map Name.unsafeFromVar . Map.keysSet
ctorsToNames = Set.fromList . map Name.unsafeFromVar . Decl.constructorVars
keysToNames = Set.map Name.unsafeParseVar . Map.keysSet
ctorsToNames = Set.fromList . map Name.unsafeParseVar . Decl.constructorVars
-- | Given a namespace and a set of dependencies, return the subset of the namespace that consists of only the
-- (transitive) dependents of the dependencies.

View File

@ -51,12 +51,14 @@ import Unison.Reference (TermReference, TypeReference)
import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Sqlite (Transaction)
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.UnisonFile qualified as UnisonFile
import Unison.Util.Pretty qualified as Pretty
import Unison.Util.Relation (Relation)
import Unison.Util.Relation qualified as Relation
import Unison.Util.Set qualified as Set
import Witch (unsafeFrom)
import qualified Data.Char as Char
handleUpgrade :: NameSegment -> NameSegment -> Cli ()
handleUpgrade oldName newName = do
@ -68,8 +70,8 @@ handleUpgrade oldName newName = do
(projectAndBranch, _path) <- Cli.expectCurrentProjectBranch
let projectId = projectAndBranch ^. #project . #projectId
let projectPath = Cli.projectBranchPath (ProjectAndBranch projectId (projectAndBranch ^. #branch . #branchId))
let oldPath = Path.resolve projectPath (Path.Relative (Path.fromList [Name.libSegment, oldName]))
let newPath = Path.resolve projectPath (Path.Relative (Path.fromList [Name.libSegment, newName]))
let oldPath = Path.resolve projectPath (Path.Relative (Path.fromList [NameSegment.libSegment, oldName]))
let newPath = Path.resolve projectPath (Path.Relative (Path.fromList [NameSegment.libSegment, newName]))
currentNamespace <- Cli.getBranch0At projectPath
let currentNamespaceSansOld = Branch.deleteLibdep oldName currentNamespace
@ -83,7 +85,7 @@ handleUpgrade oldName newName = do
let oldLocalNamespace = Branch.deleteLibdeps oldNamespace
let oldLocalTerms = Branch.deepTerms oldLocalNamespace
let oldLocalTypes = Branch.deepTypes oldLocalNamespace
let oldNamespaceMinusLocal = maybe Branch.empty0 Branch.head (Map.lookup Name.libSegment (oldNamespace ^. Branch.children))
let oldNamespaceMinusLocal = maybe Branch.empty0 Branch.head (Map.lookup NameSegment.libSegment (oldNamespace ^. Branch.children))
let oldDeepMinusLocalTerms = Branch.deepTerms oldNamespaceMinusLocal
let oldDeepMinusLocalTypes = Branch.deepTypes oldNamespaceMinusLocal
@ -190,7 +192,7 @@ handleUpgrade oldName newName = do
where
textualDescriptionOfUpgrade :: Text
textualDescriptionOfUpgrade =
Text.unwords ["upgrade", NameSegment.toText oldName, NameSegment.toText newName]
Text.unwords ["upgrade", NameSegment.toEscapedText oldName, NameSegment.toEscapedText newName]
-- Keep only the old terms that aren't "in" new, where "in" is defined as follows:
--
@ -290,8 +292,8 @@ makeOldDepPPE oldName newName currentDeepNamesSansOld oldDeepNames oldLocalNames
}
where
-- "full" means "with lib.old.* prefix"
fullOldDeepNames = PPE.namer (Names.prefix0 (Name.fromReverseSegments (oldName :| [Name.libSegment])) oldDeepNames)
fakeLocalNames = PPE.namer (Names.prefix0 (Name.fromReverseSegments (newName :| [Name.libSegment])) oldLocalNames)
fullOldDeepNames = PPE.namer (Names.prefix0 (Name.fromReverseSegments (oldName :| [NameSegment.libSegment])) oldDeepNames)
fakeLocalNames = PPE.namer (Names.prefix0 (Name.fromReverseSegments (newName :| [NameSegment.libSegment])) oldLocalNames)
-- @findTemporaryBranchName projectId oldDepName newDepName@ finds some unused branch name in @projectId@ with a name
-- like "upgrade-<oldDepName>-to-<newDepName>".
@ -314,10 +316,11 @@ findTemporaryBranchName projectId oldDepName newDepName = do
where
preferred :: ProjectBranchName
preferred =
-- filter isAlpha just to make it more likely this is a valid project name :sweat-smile:
unsafeFrom @Text $
"upgrade-"
<> NameSegment.toText oldDepName
<> Text.filter Char.isAlpha (NameSegment.toEscapedText oldDepName)
<> "-to-"
<> NameSegment.toText newDepName
<> Text.filter Char.isAlpha (NameSegment.toEscapedText newDepName)
pure (fromJust (List.find (\name -> not (Set.member name allBranchNames)) allCandidates))

View File

@ -34,7 +34,7 @@ import Data.Text qualified as Text
import Data.These (These)
import U.Codebase.HashTags (CausalHash)
import Unison.Codebase.Branch.Merge qualified as Branch
import Unison.Codebase.Editor.RemoteRepo
import Unison.Codebase.Editor.RemoteRepo (ReadRemoteNamespace, WriteGitRepo, WriteRemoteNamespace)
import Unison.Codebase.Path (Path')
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.Path.Parse qualified as Path
@ -42,8 +42,8 @@ import Unison.Codebase.PushBehavior (PushBehavior)
import Unison.Codebase.ShortCausalHash (ShortCausalHash)
import Unison.Codebase.ShortCausalHash qualified as SCH
import Unison.Codebase.SyncMode (SyncMode)
import Unison.Codebase.Verbosity
import Unison.CommandLine.BranchRelativePath
import Unison.Codebase.Verbosity (Verbosity)
import Unison.CommandLine.BranchRelativePath (BranchRelativePath, parseBranchRelativePath)
import Unison.HashQualified qualified as HQ
import Unison.Name (Name)
import Unison.NameSegment (NameSegment)
@ -82,7 +82,7 @@ type HashOrHQSplit' = Either ShortHash Path.HQSplit'
data Insistence = Force | Try
deriving (Show, Eq)
parseBranchId :: String -> Either String BranchId
parseBranchId :: String -> Either Text BranchId
parseBranchId ('#' : s) = case SCH.fromText (Text.pack s) of
Nothing -> Left "Invalid hash, expected a base32hex string."
Just h -> pure $ Left h
@ -172,7 +172,7 @@ data Input
-- Second `Maybe Int` is cap on diff elements shown, if any
HistoryI (Maybe Int) (Maybe Int) BranchId
| -- execute an IO thunk with args
ExecuteI String [String]
ExecuteI Text [String]
| -- save the result of a previous Execute
SaveExecuteResultI Name
| -- execute an IO [Result]
@ -182,9 +182,9 @@ data Input
| -- make a standalone binary file
MakeStandaloneI String (HQ.HashQualified Name)
| -- execute an IO thunk using scheme
ExecuteSchemeI String [String]
ExecuteSchemeI Text [String]
| -- compile to a scheme file
CompileSchemeI String (HQ.HashQualified Name)
CompileSchemeI Text (HQ.HashQualified Name)
| -- generate scheme libraries, optional target directory
GenSchemeLibsI (Maybe String)
| -- fetch scheme compiler from a given username and branch

View File

@ -154,13 +154,13 @@ data Output
| InvalidSourceName String
| SourceLoadFailed String
| -- No main function, the [Type v Ann] are the allowed types
NoMainFunction String PPE.PrettyPrintEnv [Type Symbol Ann]
NoMainFunction Text PPE.PrettyPrintEnv [Type Symbol Ann]
| -- | Function found, but has improper type
-- Note: the constructor name is misleading here; we weren't necessarily looking for a "main".
BadMainFunction
String
Text
-- ^ what we were trying to do (e.g. "run", "io.test")
String
Text
-- ^ name of function
(Type Symbol Ann)
-- ^ bad type of function
@ -306,7 +306,7 @@ data Output
| DumpNumberedArgs NumberedArgs
| DumpBitBooster CausalHash (Map CausalHash [CausalHash])
| DumpUnisonFileHashes Int [(Name, Reference.Id)] [(Name, Reference.Id)] [(Name, Reference.Id)]
| BadName String
| BadName Text
| CouldntLoadBranch CausalHash
| HelpMessage Input.InputPattern
| NamespaceEmpty (NonEmpty AbsBranchId)

View File

@ -39,6 +39,7 @@ import Unison.Hashing.V2.Convert qualified as Hashing
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment)
import Unison.NameSegment qualified as NameSegment
import Unison.Names (Names)
import Unison.Names qualified as Names
import Unison.Parser.Ann (Ann (..))
@ -60,7 +61,7 @@ import Unison.UnisonFile qualified as UF
import Unison.Util.Monoid (foldMapM)
import Unison.Util.Relation qualified as R
import Unison.Util.Set qualified as Set
import Unison.Util.Star3 qualified as Star3
import Unison.Util.Star2 qualified as Star2
import Unison.Util.TransitiveClosure (transitiveClosure)
import Unison.Var (Var)
import Unison.WatchKind (WatchKind)
@ -596,64 +597,61 @@ applyDeprecations patch =
deleteDeprecatedTypes ::
Set Reference -> Branch0 m -> Branch0 m
deleteDeprecatedTerms rs =
over Branch.terms (Star3.deleteFact (Set.map Referent.Ref rs))
deleteDeprecatedTypes rs = over Branch.types (Star3.deleteFact rs)
over Branch.terms (Star2.deleteFact (Set.map Referent.Ref rs))
deleteDeprecatedTypes rs = over Branch.types (Star2.deleteFact rs)
-- | Things in the patch are not marked as propagated changes, but every other
-- definition that is created by the `Edits` which is passed in is marked as
-- a propagated change.
applyPropagate :: forall m. (Applicative m) => Patch -> Edits Symbol -> Branch0 m -> Branch0 m
applyPropagate patch Edits {newTerms, termReplacements, typeReplacements, constructorReplacements} = do
let termTypes = Map.map (Hashing.typeToReference . snd) newTerms
applyPropagate patch Edits {termReplacements, typeReplacements, constructorReplacements} = do
-- recursively update names and delete deprecated definitions
stepEverywhereButLib (updateLevel termReplacements typeReplacements termTypes)
stepEverywhereButLib (updateLevel termReplacements typeReplacements)
where
-- Like Branch.stepEverywhere, but don't step the child named "lib"
stepEverywhereButLib :: (Branch0 m -> Branch0 m) -> (Branch0 m -> Branch0 m)
stepEverywhereButLib f branch =
let children =
Map.mapWithKey
(\name child -> if name == "lib" then child else Branch.step (Branch.stepEverywhere f) child)
(\name child -> if name == NameSegment.libSegment then child else Branch.step (Branch.stepEverywhere f) child)
(branch ^. Branch.children)
in f (Branch.branch0 (branch ^. Branch.terms) (branch ^. Branch.types) children (branch ^. Branch.edits))
isPropagated r = Set.notMember r allPatchTargets
allPatchTargets = Patch.allReferenceTargets patch
propagatedMd :: forall r. r -> (r, Metadata.Type, Metadata.Value)
propagatedMd r = (r, IOSource.isPropagatedReference, IOSource.isPropagatedValue)
propagatedMd :: forall r. r -> (r, Metadata.Value)
propagatedMd r = (r, IOSource.isPropagatedValue)
updateLevel ::
Map Referent Referent ->
Map Reference Reference ->
Map Reference Reference ->
Branch0 m ->
Branch0 m
updateLevel termEdits typeEdits termTypes Branch0 {..} =
updateLevel termEdits typeEdits Branch0 {..} =
Branch.branch0 terms types _children _edits
where
isPropagatedReferent (Referent.Con _ _) = True
isPropagatedReferent (Referent.Ref r) = isPropagated r
terms0 :: Metadata.Star Referent NameSegment
terms0 = Star3.replaceFacts replaceConstructor constructorReplacements _terms
terms0 = Star2.replaceFacts replaceConstructor constructorReplacements _terms
terms :: Branch.Star Referent NameSegment
terms =
updateMetadatas $
Star3.replaceFacts replaceTerm termEdits terms0
Star2.replaceFacts replaceTerm termEdits terms0
types :: Branch.Star Reference NameSegment
types =
updateMetadatas $
Star3.replaceFacts replaceType typeEdits _types
Star2.replaceFacts replaceType typeEdits _types
updateMetadatas ::
(Ord r) =>
Star3.Star3 r NameSegment Metadata.Type (Metadata.Type, Metadata.Value) ->
Star3.Star3 r NameSegment Metadata.Type (Metadata.Type, Metadata.Value)
updateMetadatas s = Star3.mapD3 go s
Metadata.Star r NameSegment ->
Metadata.Star r NameSegment
updateMetadatas s = Star2.mapD2 go s
where
go (tp, v) = case Map.lookup (Referent.Ref v) termEdits of
Just (Referent.Ref r) -> (typeOf r tp, r)
_ -> (tp, v)
typeOf r t = fromMaybe t $ Map.lookup r termTypes
go v = case Map.lookup (Referent.Ref v) termEdits of
Just (Referent.Ref r) -> r
_ -> v
replaceTerm :: Referent -> Referent -> Metadata.Star Referent NameSegment -> Metadata.Star Referent NameSegment
replaceTerm _r r' s =
@ -710,4 +708,4 @@ computeDirty getDependents patch shouldUpdate =
nameNotInLibNamespace :: Name -> Bool
nameNotInLibNamespace name =
not (Name.beginsWithSegment name "lib")
not (Name.beginsWithSegment name NameSegment.libSegment)

View File

@ -23,7 +23,7 @@ import Unison.Referent (Referent)
import Unison.Referent qualified as Referent
import Unison.Referent' qualified as Referent
import Unison.Symbol (Symbol)
import Unison.Syntax.Name qualified as Name (toText, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toText, unsafeParseVar)
import Unison.UnisonFile qualified as UF
import Unison.UnisonFile.Names qualified as UF
import Unison.Util.Map qualified as Map
@ -159,7 +159,7 @@ computeNamesWithDeprecations uf unalteredCodebaseNames involvedVars = \case
& filter (\(typeV, _) -> Set.member (TypeVar typeV) involvedVars)
& concatMap (\(_typeV, (_refId, decl)) -> DD.constructors' decl)
& fmap
( \(_ann, v, _typ) -> Name.unsafeFromVar v
( \(_ann, v, _typ) -> Name.unsafeParseVar v
)
& Set.fromList
@ -170,7 +170,7 @@ computeNamesWithDeprecations uf unalteredCodebaseNames involvedVars = \case
let effectNames = Map.keys (UF.effectDeclarationsId' uf)
typeName <- declNames <> effectNames
when (not . null $ involvedVars) (guard (TypeVar typeName `Set.member` involvedVars))
pure $ Names.typesNamed unalteredCodebaseNames (Name.unsafeFromVar typeName)
pure $ Names.typesNamed unalteredCodebaseNames (Name.unsafeParseVar typeName)
existingConstructorsFromEditedTypes = Set.fromList $ do
-- List Monad
ref <- Set.toList oldRefsForEditedTypes
@ -194,8 +194,8 @@ computeSelfStatuses vars varReferences codebaseNames =
Just r -> r
Nothing -> error $ "Expected LabeledDependency in map for var: " <> show tv
v = untagged tv
existingTypesAtName = Names.typesNamed codebaseNames (Name.unsafeFromVar v)
existingTermsOrCtorsAtName = Names.termsNamed codebaseNames (Name.unsafeFromVar v)
existingTypesAtName = Names.typesNamed codebaseNames (Name.unsafeParseVar v)
existingTermsOrCtorsAtName = Names.termsNamed codebaseNames (Name.unsafeParseVar v)
in case ld of
LD.TypeReference _typeRef ->
case Set.toList existingTypesAtName of

View File

@ -35,6 +35,7 @@ import Unison.NameSegment (NameSegment (..))
import Unison.Prelude
import Unison.Project (ProjectBranchName, ProjectBranchSpecifier (..), ProjectName, projectAndBranchNamesParser)
import Unison.Syntax.Lexer qualified
import Unison.Syntax.NameSegment qualified as NameSegment
import Unison.Util.Pretty qualified as P
import Unison.Util.Pretty.MegaParsec qualified as P
@ -378,7 +379,7 @@ absolutePath = do
nameSegment :: P NameSegment
nameSegment =
NameSegment . Text.pack
NameSegment.unsafeParseText . Text.pack
<$> ( (:)
<$> P.satisfy Unison.Syntax.Lexer.wordyIdStartChar
<*> P.many (P.satisfy Unison.Syntax.Lexer.wordyIdChar)

View File

@ -210,8 +210,8 @@ incrementalBranchRelativePathParser =
Left err -> failureAt offset err
Right x -> pure x
failureAt :: forall a. Int -> String -> Megaparsec.Parsec Void Text a
failureAt offset str = Megaparsec.parseError (Megaparsec.FancyError offset (Set.singleton (Megaparsec.ErrorFail str)))
failureAt :: forall a. Int -> Text -> Megaparsec.Parsec Void Text a
failureAt offset str = Megaparsec.parseError (Megaparsec.FancyError offset (Set.singleton (Megaparsec.ErrorFail (Text.unpack str))))
parseThese ::
forall a b.

View File

@ -27,6 +27,7 @@ import Data.Aeson qualified as Aeson
import Data.List (isPrefixOf)
import Data.List qualified as List
import Data.List.Extra (nubOrdOn)
import Data.List.NonEmpty qualified as List.NonEmpty
import Data.List.NonEmpty qualified as NE
import Data.Map qualified as Map
import Data.Set.NonEmpty (NESet)
@ -37,6 +38,7 @@ import Network.URI qualified as URI
import System.Console.Haskeline qualified as Line
import System.Console.Haskeline.Completion (Completion)
import System.Console.Haskeline.Completion qualified as Haskeline
import Text.Megaparsec qualified as P
import U.Codebase.Branch qualified as V2Branch
import U.Codebase.Causal qualified as V2Causal
import U.Codebase.Reference qualified as Reference
@ -45,11 +47,12 @@ import Unison.Auth.HTTPClient (AuthenticatedHttpClient (..))
import Unison.Codebase (Codebase)
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.Path.Parse qualified as Path
import Unison.Codebase.SqliteCodebase.Conversions qualified as Cv
import Unison.CommandLine.InputPattern qualified as IP
import Unison.HashQualified' qualified as HQ'
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment qualified as NameSegment
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (..))
import Unison.Prelude
import Unison.Server.Local.Endpoints.NamespaceListing (NamespaceListing (NamespaceListing))
import Unison.Server.Local.Endpoints.NamespaceListing qualified as Server
@ -57,6 +60,8 @@ import Unison.Server.Types qualified as Server
import Unison.Share.Codeserver qualified as Codeserver
import Unison.Share.Types qualified as Share
import Unison.Sqlite qualified as Sqlite
import Unison.Syntax.Name qualified as Name
import Unison.Syntax.NameSegment qualified as NameSegment
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Pretty qualified as P
import UnliftIO qualified
@ -144,7 +149,12 @@ completeWithinNamespace compTypes query currentPath = do
currentBranchSuggestions <- do
nib <- namesInBranch shortHashLen b
nib
& fmap (\(isFinished, match) -> (isFinished, Text.unpack . Path.toText' $ queryPathPrefix Lens.:> NameSegment.NameSegment match))
& fmap
( \(ty, isFinished, match) ->
( isFinished,
Text.unpack (dotifyNamespace ty (Path.toText' (queryPathPrefix Lens.:> NameSegment match)))
)
)
& filter (\(_isFinished, match) -> List.isPrefixOf query match)
& fmap (\(isFinished, match) -> prettyCompletionWithQueryPrefix isFinished query match)
& pure
@ -156,42 +166,55 @@ completeWithinNamespace compTypes query currentPath = do
pure . nubOrdOn Haskeline.replacement . List.sortOn Haskeline.replacement $ allSuggestions
where
queryPathPrefix :: Path.Path'
querySuffix :: NameSegment.NameSegment
querySuffix :: Text
(queryPathPrefix, querySuffix) = parseLaxPath'Query (Text.pack query)
absQueryPath :: Path.Absolute
absQueryPath = Path.resolve currentPath queryPathPrefix
getChildSuggestions :: Int -> V2Branch.Branch Sqlite.Transaction -> Sqlite.Transaction [Completion]
getChildSuggestions shortHashLen b = do
nonEmptyChildren <- V2Branch.nonEmptyChildren b
case querySuffix of
"" -> pure []
suffix -> do
case Map.lookup suffix nonEmptyChildren of
Nothing -> pure []
Just childCausal -> do
childBranch <- V2Causal.value childCausal
nib <- namesInBranch shortHashLen childBranch
nib
& fmap
( \(isFinished, match) -> (isFinished, Text.unpack . Path.toText' $ queryPathPrefix Lens.:> suffix Lens.:> NameSegment.NameSegment match)
)
& filter (\(_isFinished, match) -> List.isPrefixOf query match)
& fmap (\(isFinished, match) -> prettyCompletionWithQueryPrefix isFinished query match)
& pure
namesInBranch :: Int -> V2Branch.Branch Sqlite.Transaction -> Sqlite.Transaction [(Bool, Text)]
getChildSuggestions shortHashLen b
| Text.null querySuffix = pure []
| otherwise =
case NameSegment.parseText querySuffix of
Left _ -> pure []
Right suffix -> do
nonEmptyChildren <- V2Branch.nonEmptyChildren b
case Map.lookup suffix nonEmptyChildren of
Nothing -> pure []
Just childCausal -> do
childBranch <- V2Causal.value childCausal
nib <- namesInBranch shortHashLen childBranch
nib
& fmap
( \(ty, isFinished, match) ->
( isFinished,
Text.unpack (dotifyNamespace ty (Path.toText' (queryPathPrefix Lens.:> suffix Lens.:> NameSegment match)))
)
)
& filter (\(_isFinished, match) -> List.isPrefixOf query match)
& fmap (\(isFinished, match) -> prettyCompletionWithQueryPrefix isFinished query match)
& pure
namesInBranch :: Int -> V2Branch.Branch Sqlite.Transaction -> Sqlite.Transaction [(CompletionType, Bool, Text)]
namesInBranch hashLen b = do
nonEmptyChildren <- V2Branch.nonEmptyChildren b
let textifyHQ :: (NameSegment -> r -> HQ'.HashQualified NameSegment) -> Map NameSegment (Map r metadata) -> [(Bool, Text)]
textifyHQ f xs =
xs
& hashQualifyCompletions f
& fmap (HQ'.toTextWith NameSegment.toText)
& fmap (HQ'.toTextWith NameSegment.toEscapedText)
& fmap (True,)
pure $
((False,) <$> dotifyNamespaces (fmap NameSegment.toText . Map.keys $ nonEmptyChildren))
<> Monoid.whenM (NESet.member TermCompletion compTypes) (textifyHQ (hqFromNamedV2Referent hashLen) $ V2Branch.terms b)
<> Monoid.whenM (NESet.member TypeCompletion compTypes) (textifyHQ (hqFromNamedV2Reference hashLen) $ V2Branch.types b)
<> Monoid.whenM (NESet.member PatchCompletion compTypes) (fmap ((True,) . NameSegment.toText) . Map.keys $ V2Branch.patches b)
concat
[ (NamespaceCompletion,False,) <$> (fmap NameSegment.toEscapedText . Map.keys $ nonEmptyChildren),
Monoid.whenM
(NESet.member TermCompletion compTypes)
(map (\(x, y) -> (TermCompletion, x, y)) (textifyHQ (hqFromNamedV2Referent hashLen) $ V2Branch.terms b)),
Monoid.whenM
(NESet.member TypeCompletion compTypes)
(map (\(x, y) -> (TypeCompletion, x, y)) (textifyHQ (hqFromNamedV2Reference hashLen) $ V2Branch.types b)),
Monoid.whenM
(NESet.member PatchCompletion compTypes)
(fmap ((PatchCompletion,True,) . NameSegment.toEscapedText) . Map.keys $ V2Branch.patches b)
]
-- Regrettably there'shqFromNamedV2Referencenot a great spot to combinators for V2 references and shorthashes right now.
hqFromNamedV2Referent :: Int -> NameSegment -> Referent.Referent -> HQ'.HashQualified NameSegment
@ -205,16 +228,14 @@ completeWithinNamespace compTypes query currentPath = do
-- completions.
qualifyRefs :: NameSegment -> Map r metadata -> [HQ'.HashQualified NameSegment]
qualifyRefs n refs
| ((Text.isInfixOf "#" . NameSegment.toText) querySuffix) || length refs > 1 = refs & Map.keys <&> qualify n
| Text.isInfixOf "#" querySuffix || length refs > 1 = refs & Map.keys <&> qualify n
| otherwise = [HQ'.NameOnly n]
-- If we're not completing namespaces, then all namespace completions should automatically
-- drill-down by adding a trailing '.'
dotifyNamespaces :: [Text] -> [Text]
dotifyNamespaces namespaces =
if not (NESet.member NamespaceCompletion compTypes)
then fmap (<> ".") namespaces
else namespaces
dotifyNamespace :: CompletionType -> Text -> Text
dotifyNamespace NamespaceCompletion | not (NESet.member NamespaceCompletion compTypes) = (<> ".")
dotifyNamespace _ = id
-- | A path parser which which is more lax with respect to well formed paths,
-- specifically we can determine a valid path prefix with a (possibly empty) suffix query.
@ -241,22 +262,14 @@ completeWithinNamespace compTypes query currentPath = do
--
-- >>> parseLaxPath'Query "base.List"
-- (base,"List")
parseLaxPath'Query :: Text -> (Path.Path', NameSegment)
parseLaxPath'Query :: Text -> (Path.Path', Text)
parseLaxPath'Query txt =
case unsnoc (Text.splitOn "." txt) of
-- This case is impossible due to the behaviour of 'splitOn'
Nothing ->
(Path.relativeEmpty', NameSegment "")
-- ".base."
-- ".base.List"
Just ("" : pathPrefix, querySegment) -> (Path.AbsolutePath' . Path.Absolute . Path.fromList . fmap NameSegment $ pathPrefix, NameSegment querySegment)
-- ""
-- "base"
-- "base.List"
Just (pathPrefix, querySegment) ->
( Path.RelativePath' . Path.Relative . Path.fromList . fmap NameSegment $ pathPrefix,
NameSegment querySegment
)
case P.runParser ((,) <$> Path.splitP' <*> P.takeRest) "" (Text.unpack txt) of
Left _err -> (Path.relativeEmpty', txt)
Right ((path, segment), rest) ->
if take 1 rest == "."
then (Path.unsplit' (path, segment), Text.empty)
else (path, NameSegment.toEscapedText segment)
-- | Completes a namespace argument by prefix-matching against the query.
prefixCompleteNamespace ::
@ -350,19 +363,21 @@ shareCompletion ::
m [Completion]
shareCompletion completionTypes authHTTPClient str =
fromMaybe [] <$> runMaybeT do
case Text.splitOn "." (Text.pack str) of
[] -> empty
[userPrefix] -> do
userHandles <- searchUsers authHTTPClient userPrefix
case Path.toList <$> Path.parsePath str of
Left _err -> empty
Right [] -> empty
Right [userPrefix] -> do
userHandles <- searchUsers authHTTPClient (NameSegment.toEscapedText userPrefix)
pure $
userHandles
& filter (userPrefix `Text.isPrefixOf`)
<&> \handle -> prettyCompletionWithQueryPrefix False (Text.unpack userPrefix) (Text.unpack handle)
userHandle : path -> do
(userHandle, path, pathSuffix) <- case unsnoc path of
Just (path, pathSuffix) -> pure (userHandle, Path.fromList (NameSegment <$> path), pathSuffix)
Nothing -> pure (userHandle, Path.empty, "")
NamespaceListing {namespaceListingChildren} <- MaybeT $ fetchShareNamespaceInfo authHTTPClient userHandle path
& filter (\userHandle -> NameSegment.toEscapedText userPrefix `Text.isPrefixOf` userHandle)
<&> \handle -> prettyCompletionWithQueryPrefix False (Text.unpack (NameSegment.toEscapedText userPrefix)) (Text.unpack handle)
Right (userHandle : path0) -> do
let (path, pathSuffix) =
case unsnoc path0 of
Just (path, pathSuffix) -> (Path.fromList path, NameSegment.toEscapedText pathSuffix)
Nothing -> (Path.empty, "")
NamespaceListing {namespaceListingChildren} <- MaybeT $ fetchShareNamespaceInfo authHTTPClient (NameSegment.toEscapedText userHandle) path
namespaceListingChildren
& fmap
( \case
@ -370,10 +385,10 @@ shareCompletion completionTypes authHTTPClient str =
let name = Server.namespaceName nn
in (NamespaceCompletion, name)
Server.TermObject nt ->
let name = HQ'.toTextWith NameSegment.toText $ Server.termName nt
let name = HQ'.toTextWith Name.toText $ Server.termName nt
in (NamespaceCompletion, name)
Server.TypeObject nt ->
let name = HQ'.toTextWith NameSegment.toText $ Server.typeName nt
let name = HQ'.toTextWith Name.toText $ Server.typeName nt
in (TermCompletion, name)
Server.PatchObject np ->
let name = Server.patchName np
@ -382,8 +397,13 @@ shareCompletion completionTypes authHTTPClient str =
& filter (\(typ, name) -> typ `NESet.member` completionTypes && pathSuffix `Text.isPrefixOf` name)
& fmap
( \(_, name) ->
let queryPath = userHandle : coerce (Path.toList path)
result = Text.unpack $ Text.intercalate "." (queryPath <> [name])
let queryPath = userHandle : Path.toList path
result =
(queryPath ++ [NameSegment.unsafeParseText name])
& List.NonEmpty.fromList
& Name.fromSegments
& Name.toText
& Text.unpack
in prettyCompletionWithQueryPrefix False str result
)
& pure

View File

@ -45,6 +45,7 @@ import Unison.Prelude
import Unison.Project.Util (ProjectContext (..))
import Unison.Symbol (Symbol)
import Unison.Syntax.HashQualified qualified as HQ (toText)
import Unison.Syntax.NameSegment qualified as NameSegment
import Unison.Util.Monoid (foldMapM)
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Relation qualified as Relation
@ -104,10 +105,10 @@ namespaceOptions _codebase _projCtx searchBranch0 = do
projectDependencyOptions :: OptionFetcher
projectDependencyOptions _codebase _projCtx searchBranch0 = do
searchBranch0
& Branch.getAt0 (Path.singleton Name.libSegment)
& Branch.getAt0 (Path.singleton NameSegment.libSegment)
& Branch.nonEmptyChildren
& Map.keys
& fmap NameSegment.toText
& fmap NameSegment.toEscapedText
& pure
-- | Select a namespace from the given branch.

View File

@ -20,6 +20,7 @@ import System.Console.Haskeline.Completion (Completion (Completion))
import System.Console.Haskeline.Completion qualified as Haskeline
import System.Console.Haskeline.Completion qualified as Line
import Text.Megaparsec qualified as Megaparsec
import Text.Megaparsec.Internal qualified as Megaparsec (withParsecT)
import U.Codebase.Sqlite.DbId (ProjectBranchId, ProjectId)
import U.Codebase.Sqlite.Project qualified as Sqlite
import U.Codebase.Sqlite.Queries qualified as Queries
@ -28,7 +29,6 @@ import Unison.Cli.Pretty (prettyProjectAndBranchName, prettyProjectName, prettyP
import Unison.Cli.ProjectUtils qualified as ProjectUtils
import Unison.Codebase (Codebase)
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Branch qualified as Branch
import Unison.Codebase.Branch.Merge qualified as Branch
import Unison.Codebase.Editor.Input (DeleteOutput (..), DeleteTarget (..), Input)
import Unison.Codebase.Editor.Input qualified as Input
@ -60,8 +60,9 @@ import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Project (ProjectAndBranch (..), ProjectAndBranchNames (..), ProjectBranchName, ProjectBranchNameOrLatestRelease (..), ProjectBranchSpecifier (..), ProjectName, Semver)
import Unison.Project.Util (ProjectContext (..), projectContextFromPath)
import Unison.Syntax.HashQualified qualified as HQ (fromString)
import Unison.Syntax.Name qualified as Name (fromText, unsafeFromString)
import Unison.Syntax.HashQualified qualified as HQ (parseText)
import Unison.Syntax.Name qualified as Name (parseText, unsafeParseText)
import Unison.Syntax.NameSegment qualified as NameSegment (renderParseErr, segmentP)
import Unison.Util.ColorText qualified as CT
import Unison.Util.Monoid (intercalateMap)
import Unison.Util.Pretty qualified as P
@ -153,8 +154,8 @@ todo =
]
)
( \case
patchStr : ws -> mapLeft (warn . fromString) $ do
patch <- Path.parseSplit' Path.definitionNameSegment patchStr
patchStr : ws -> mapLeft (warn . P.text) $ do
patch <- Path.parseSplit' patchStr
branch <- case ws of
[] -> pure Path.relativeEmpty'
[pathStr] -> Path.parsePath' pathStr
@ -213,7 +214,7 @@ add =
( "`add` adds to the codebase all the definitions from the most recently "
<> "typechecked file."
)
$ \ws -> pure $ Input.AddI (Set.fromList $ map Name.unsafeFromString ws)
\ws -> pure $ Input.AddI (Set.fromList $ map (Name.unsafeParseText . Text.pack) ws)
previewAdd :: InputPattern
previewAdd =
@ -227,7 +228,7 @@ previewAdd =
<> "results. Use `load` to reparse & typecheck the file if the context "
<> "has changed."
)
$ \ws -> pure $ Input.PreviewAddI (Set.fromList $ map Name.unsafeFromString ws)
\ws -> pure $ Input.PreviewAddI (Set.fromList $ map (Name.unsafeParseText . Text.pack) ws)
update :: InputPattern
update =
@ -279,7 +280,7 @@ updateOldNoPatch =
pure $
Input.UpdateI
Input.NoPatch
(Set.fromList $ map Name.unsafeFromString ws)
(Set.fromList $ map (Name.unsafeParseText . Text.pack) ws)
)
updateOld :: InputPattern
@ -316,13 +317,11 @@ updateOld =
)
\case
patchStr : ws -> do
patch <-
first fromString $
Path.parseSplit' Path.definitionNameSegment patchStr
patch <- first P.text $ Path.parseSplit' patchStr
pure $
Input.UpdateI
(Input.UsePatch patch)
(Set.fromList $ map Name.unsafeFromString ws)
(Set.fromList $ map (Name.unsafeParseText . Text.pack) ws)
[] -> Right $ Input.UpdateI Input.DefaultPatch mempty
previewUpdate :: InputPattern
@ -337,7 +336,7 @@ previewUpdate =
<> "typechecking results. Use `load` to reparse & typecheck the file if "
<> "the context has changed."
)
\ws -> pure $ Input.PreviewUpdateI (Set.fromList $ map Name.unsafeFromString ws)
\ws -> pure $ Input.PreviewUpdateI (Set.fromList $ map (Name.unsafeParseText . Text.pack) ws)
patch :: InputPattern
patch =
@ -366,8 +365,8 @@ patch =
]
)
\case
patchStr : ws -> first fromString $ do
patch <- Path.parseSplit' Path.definitionNameSegment patchStr
patchStr : ws -> first P.text do
patch <- Path.parseSplit' patchStr
branch <- case ws of
[pathStr] -> Path.parsePath' pathStr
_ -> pure Path.relativeEmpty'
@ -474,10 +473,10 @@ docs =
]
)
( \case
(x : xs) ->
x : xs ->
(x NE.:| xs)
& traverse Path.parseHQSplit'
& bimap fromString Input.DocsI
& bimap P.text Input.DocsI
_ -> Left (I.help docs)
)
@ -501,7 +500,7 @@ ui =
help = P.wrap "`ui` opens the Local UI in the default browser.",
parse = \case
[] -> pure $ Input.UiI Path.relativeEmpty'
[path] -> first fromString $ do
[path] -> first P.text $ do
p <- Path.parsePath' path
pure $ Input.UiI p
_ -> Left (I.help ui)
@ -642,7 +641,7 @@ findShallow =
)
( \case
[] -> pure $ Input.FindShallowI Path.relativeEmpty'
[path] -> first fromString $ do
[path] -> first P.text $ do
p <- Path.parsePath' path
pure $ Input.FindShallowI p
_ -> Left (I.help findShallow)
@ -695,9 +694,9 @@ renameTerm =
]
"`move.term foo bar` renames `foo` to `bar`."
( \case
[oldName, newName] -> first fromString $ do
[oldName, newName] -> first P.text do
src <- Path.parseHQSplit' oldName
target <- Path.parseSplit' Path.definitionNameSegment newName
target <- Path.parseSplit' newName
pure $ Input.MoveTermI src target
_ ->
Left . P.warnCallout $
@ -716,7 +715,7 @@ moveAll =
]
"`move foo bar` renames the term, type, and namespace foo to bar."
( \case
[oldName, newName] -> first fromString $ do
[oldName, newName] -> first P.text $ do
src <- Path.parsePath' oldName
target <- Path.parsePath' newName
pure $ Input.MoveAllI src target
@ -737,9 +736,9 @@ renameType =
]
"`move.type foo bar` renames `foo` to `bar`."
( \case
[oldName, newName] -> first fromString $ do
[oldName, newName] -> first P.text do
src <- Path.parseHQSplit' oldName
target <- Path.parseSplit' Path.definitionNameSegment newName
target <- Path.parseSplit' newName
pure $ Input.MoveTypeI src target
_ ->
Left . P.warnCallout $
@ -786,7 +785,7 @@ deleteGen suffix queryCompletionArg target mkTarget =
info
( \case
[] -> Left . P.warnCallout $ P.wrap warn
queries -> first fromString $ do
queries -> first P.text do
paths <- traverse Path.parseHQSplit' queries
pure $ Input.DeleteI (mkTarget paths)
)
@ -834,10 +833,7 @@ deleteReplacement isTerm =
)
( \case
query : patch -> do
patch <-
first fromString
. traverse (Path.parseSplit' Path.definitionNameSegment)
$ listToMaybe patch
patch <- first P.text . traverse Path.parseSplit' $ listToMaybe patch
q <- parseHashQualifiedName query
pure $ input q patch
_ ->
@ -919,16 +915,15 @@ aliasTerm =
I.Visible
[("term to alias", Required, exactDefinitionTermQueryArg), ("alias name", Required, newNameArg)]
"`alias.term foo bar` introduces `bar` with the same definition as `foo`."
( \case
[oldName, newName] -> first fromString $ do
source <- Path.parseShortHashOrHQSplit' oldName
target <- Path.parseSplit' Path.definitionNameSegment newName
pure $ Input.AliasTermI source target
_ ->
Left . warn $
P.wrap
"`alias.term` takes two arguments, like `alias.term oldname newname`."
)
\case
[oldName, newName] -> first P.text do
source <- Path.parseShortHashOrHQSplit' oldName
target <- Path.parseSplit' newName
pure $ Input.AliasTermI source target
_ ->
Left . warn $
P.wrap
"`alias.term` takes two arguments, like `alias.term oldname newname`."
aliasType :: InputPattern
aliasType =
@ -938,16 +933,15 @@ aliasType =
I.Visible
[("type to alias", Required, exactDefinitionTypeQueryArg), ("alias name", Required, newNameArg)]
"`alias.type Foo Bar` introduces `Bar` with the same definition as `Foo`."
( \case
[oldName, newName] -> first fromString $ do
source <- Path.parseShortHashOrHQSplit' oldName
target <- Path.parseSplit' Path.definitionNameSegment newName
pure $ Input.AliasTypeI source target
_ ->
Left . warn $
P.wrap
"`alias.type` takes two arguments, like `alias.type oldname newname`."
)
\case
[oldName, newName] -> first P.text do
source <- Path.parseShortHashOrHQSplit' oldName
target <- Path.parseSplit' newName
pure $ Input.AliasTypeI source target
_ ->
Left . warn $
P.wrap
"`alias.type` takes two arguments, like `alias.type oldname newname`."
aliasMany :: InputPattern
aliasMany =
@ -965,13 +959,12 @@ aliasMany =
<> "creates aliases `.quux.foo.foo` and `.quux.bar.bar`."
]
)
( \case
srcs@(_ : _) Cons.:> dest -> first fromString $ do
sourceDefinitions <- traverse Path.parseHQSplit srcs
destNamespace <- Path.parsePath' dest
pure $ Input.AliasManyI sourceDefinitions destNamespace
_ -> Left (I.help aliasMany)
)
\case
srcs@(_ : _) Cons.:> dest -> first P.text do
sourceDefinitions <- traverse Path.parseHQSplit srcs
destNamespace <- Path.parsePath' dest
pure $ Input.AliasManyI sourceDefinitions destNamespace
_ -> Left (I.help aliasMany)
up :: InputPattern
up =
@ -1012,13 +1005,12 @@ cd =
]
]
)
( \case
[".."] -> Right Input.UpI
[p] -> first fromString $ do
p <- Path.parsePath' p
pure . Input.SwitchBranchI $ p
_ -> Left (I.help cd)
)
\case
[".."] -> Right Input.UpI
[p] -> first P.text do
p <- Path.parsePath' p
pure . Input.SwitchBranchI $ p
_ -> Left (I.help cd)
back :: InputPattern
back =
@ -1033,10 +1025,9 @@ back =
)
]
)
( \case
[] -> pure Input.PopBranchI
_ -> Left (I.help cd)
)
\case
[] -> pure Input.PopBranchI
_ -> Left (I.help cd)
deleteNamespace :: InputPattern
deleteNamespace =
@ -1061,17 +1052,15 @@ deleteNamespaceForce =
(deleteNamespaceParser (I.help deleteNamespaceForce) Input.Force)
deleteNamespaceParser :: P.Pretty CT.ColorText -> Input.Insistence -> [String] -> Either (P.Pretty CT.ColorText) Input
deleteNamespaceParser helpText insistence =
( \case
["."] ->
first fromString
. pure
$ Input.DeleteI (DeleteTarget'Namespace insistence Nothing)
[p] -> first fromString $ do
p <- Path.parseSplit' Path.definitionNameSegment p
pure $ Input.DeleteI (DeleteTarget'Namespace insistence (Just p))
_ -> Left helpText
)
deleteNamespaceParser helpText insistence = \case
["."] ->
first fromString
. pure
$ Input.DeleteI (DeleteTarget'Namespace insistence Nothing)
[p] -> first P.text do
p <- Path.parseSplit' p
pure $ Input.DeleteI (DeleteTarget'Namespace insistence (Just p))
_ -> Left helpText
deletePatch :: InputPattern
deletePatch =
@ -1081,23 +1070,22 @@ deletePatch =
I.Visible
[("patch to delete", Required, patchArg)]
"`delete.patch <foo>` deletes the patch `foo`"
( \case
[p] -> first fromString $ do
p <- Path.parseSplit' Path.definitionNameSegment p
pure . Input.DeleteI $ DeleteTarget'Patch p
_ -> Left (I.help deletePatch)
)
\case
[p] -> first P.text do
p <- Path.parseSplit' p
pure . Input.DeleteI $ DeleteTarget'Patch p
_ -> Left (I.help deletePatch)
movePatch :: String -> String -> Either (P.Pretty CT.ColorText) Input
movePatch src dest = first fromString $ do
src <- Path.parseSplit' Path.definitionNameSegment src
dest <- Path.parseSplit' Path.definitionNameSegment dest
movePatch src dest = first P.text do
src <- Path.parseSplit' src
dest <- Path.parseSplit' dest
pure $ Input.MovePatchI src dest
copyPatch' :: String -> String -> Either (P.Pretty CT.ColorText) Input
copyPatch' src dest = first fromString $ do
src <- Path.parseSplit' Path.definitionNameSegment src
dest <- Path.parseSplit' Path.definitionNameSegment dest
copyPatch' src dest = first P.text do
src <- Path.parseSplit' src
dest <- Path.parseSplit' dest
pure $ Input.CopyPatchI src dest
copyPatch :: InputPattern
@ -1108,10 +1096,9 @@ copyPatch =
I.Visible
[("patch to copy", Required, patchArg), ("copy destination", Required, newNameArg)]
"`copy.patch foo bar` copies the patch `foo` to `bar`."
( \case
[src, dest] -> copyPatch' src dest
_ -> Left (I.help copyPatch)
)
\case
[src, dest] -> copyPatch' src dest
_ -> Left (I.help copyPatch)
renamePatch :: InputPattern
renamePatch =
@ -1121,10 +1108,9 @@ renamePatch =
I.Visible
[("patch", Required, patchArg), ("new location", Required, newNameArg)]
"`move.patch foo bar` renames the patch `foo` to `bar`."
( \case
[src, dest] -> movePatch src dest
_ -> Left (I.help renamePatch)
)
\case
[src, dest] -> movePatch src dest
_ -> Left (I.help renamePatch)
renameBranch :: InputPattern
renameBranch =
@ -1134,13 +1120,12 @@ renameBranch =
I.Visible
[("namespace to move", Required, namespaceArg), ("new location", Required, newNameArg)]
"`move.namespace foo bar` renames the path `foo` to `bar`."
( \case
[src, dest] -> first fromString $ do
src <- Path.parsePath' src
dest <- Path.parsePath' dest
pure $ Input.MoveBranchI src dest
_ -> Left (I.help renameBranch)
)
\case
[src, dest] -> first P.text do
src <- Path.parsePath' src
dest <- Path.parsePath' dest
pure $ Input.MoveBranchI src dest
_ -> Left (I.help renameBranch)
history :: InputPattern
history =
@ -1158,13 +1143,12 @@ history =
)
]
)
( \case
[src] -> first fromString $ do
p <- Input.parseBranchId src
pure $ Input.HistoryI (Just 10) (Just 10) p
[] -> pure $ Input.HistoryI (Just 10) (Just 10) (Right Path.currentPath)
_ -> Left (I.help history)
)
\case
[src] -> first P.text do
p <- Input.parseBranchId src
pure $ Input.HistoryI (Just 10) (Just 10) p
[] -> pure $ Input.HistoryI (Just 10) (Just 10) (Right Path.currentPath)
_ -> Left (I.help history)
forkLocal :: InputPattern
forkLocal =
@ -1187,13 +1171,12 @@ forkLocal =
)
]
)
( \case
[src, dest] -> do
src <- Input.parseBranchId2 src
dest <- parseBranchRelativePath dest
pure $ Input.ForkLocalBranchI src dest
_ -> Left (I.help forkLocal)
)
\case
[src, dest] -> do
src <- Input.parseBranchId2 src
dest <- parseBranchRelativePath dest
pure $ Input.ForkLocalBranchI src dest
_ -> Left (I.help forkLocal)
reset :: InputPattern
reset =
@ -1262,12 +1245,11 @@ resetRoot =
)
]
)
( \case
[src] -> first fromString $ do
src <- Input.parseBranchId src
pure $ Input.ResetRootI src
_ -> Left (I.help resetRoot)
)
\case
[src] -> first P.text $ do
src <- Input.parseBranchId src
pure $ Input.ResetRootI src
_ -> Left (I.help resetRoot)
pull :: InputPattern
pull =
@ -1425,11 +1407,10 @@ debugFuzzyOptions =
P.wrap $ "or `debug.fuzzy-options merge - _`"
]
)
( \case
(cmd : args) ->
Right $ Input.DebugFuzzyOptionsI cmd args
_ -> Left (I.help debugFuzzyOptions)
)
\case
(cmd : args) ->
Right $ Input.DebugFuzzyOptionsI cmd args
_ -> Left (I.help debugFuzzyOptions)
debugFormat :: InputPattern
debugFormat =
@ -1750,11 +1731,11 @@ diffNamespace =
]
)
( \case
[before, after] -> first fromString $ do
[before, after] -> first P.text do
before <- Input.parseBranchId before
after <- Input.parseBranchId after
pure $ Input.DiffNamespaceI before after
[before] -> first fromString $ do
[before] -> first P.text do
before <- Input.parseBranchId before
pure $ Input.DiffNamespaceI before (Right Path.currentPath)
_ -> Left $ I.help diffNamespace
@ -1830,10 +1811,7 @@ replaceEdit f = self
)
( \case
source : target : patch -> do
patch <-
first fromString
<$> traverse (Path.parseSplit' Path.definitionNameSegment)
$ listToMaybe patch
patch <- first P.text <$> traverse Path.parseSplit' $ listToMaybe patch
sourcehq <- parseHashQualifiedName source
targethq <- parseHashQualifiedName target
pure $ f sourcehq targethq patch
@ -1892,7 +1870,7 @@ editNamespace =
[ "`edit.namespace` will load all terms and types contained within the current namespace into your scratch file. This includes definitions in namespaces, but excludes libraries.",
"`edit.namespace ns1 ns2 ...` loads the terms and types contained within the provided namespaces."
],
parse = Right . Input.EditNamespaceI . fmap (Path.fromText . Text.pack)
parse = Right . Input.EditNamespaceI . fmap (Path.unsafeParseText . Text.pack)
}
topicNameArg :: ArgumentType
@ -2103,33 +2081,32 @@ help =
I.Visible
[("command", Optional, commandNameArg)]
"`help` shows general help and `help <cmd>` shows help for one command."
( \case
[] ->
Left $
intercalateMap
"\n\n"
showPatternHelp
visibleInputs
[cmd] ->
case (Map.lookup cmd commandsByName, isHelp cmd) of
(Nothing, Just msg) -> Left msg
(Nothing, Nothing) -> Left . warn $ "I don't know of that command. Try `help`."
(Just pat, Nothing) -> Left $ showPatternHelp pat
-- If we have a command and a help topic with the same name (like "projects"), then append a tip to the
-- command's help that suggests running `help-topic command`
(Just pat, Just _) ->
Left $
showPatternHelp pat
<> P.newline
<> P.newline
<> ( tip $
"To read more about"
<> P.group (P.string cmd <> ",")
<> "use"
<> makeExample helpTopics [P.string cmd]
)
_ -> Left $ warn "Use `help <cmd>` or `help`."
)
\case
[] ->
Left $
intercalateMap
"\n\n"
showPatternHelp
visibleInputs
[cmd] ->
case (Map.lookup cmd commandsByName, isHelp cmd) of
(Nothing, Just msg) -> Left msg
(Nothing, Nothing) -> Left . warn $ "I don't know of that command. Try `help`."
(Just pat, Nothing) -> Left $ showPatternHelp pat
-- If we have a command and a help topic with the same name (like "projects"), then append a tip to the
-- command's help that suggests running `help-topic command`
(Just pat, Just _) ->
Left $
showPatternHelp pat
<> P.newline
<> P.newline
<> ( tip $
"To read more about"
<> P.group (P.string cmd <> ",")
<> "use"
<> makeExample helpTopics [P.string cmd]
)
_ -> Left $ warn "Use `help <cmd>` or `help`."
where
commandsByName =
Map.fromList $ do
@ -2146,10 +2123,9 @@ quit =
I.Visible
[]
"Exits the Unison command line interface."
( \case
[] -> pure Input.QuitI
_ -> Left "Use `quit`, `exit`, or <Ctrl-D> to quit."
)
\case
[] -> pure Input.QuitI
_ -> Left "Use `quit`, `exit`, or <Ctrl-D> to quit."
viewPatch :: InputPattern
viewPatch =
@ -2167,13 +2143,12 @@ viewPatch =
)
]
)
( \case
[] -> Right $ Input.ListEditsI Nothing
[patchStr] -> mapLeft fromString $ do
patch <- Path.parseSplit' Path.definitionNameSegment patchStr
Right $ Input.ListEditsI (Just patch)
_ -> Left $ warn "`view.patch` takes a patch and that's it."
)
\case
[] -> Right $ Input.ListEditsI Nothing
[patchStr] -> mapLeft P.text do
patch <- Path.parseSplit' patchStr
Right $ Input.ListEditsI (Just patch)
_ -> Left $ warn "`view.patch` takes a patch and that's it."
names :: Input.IsGlobal -> InputPattern
names isGlobal =
@ -2183,15 +2158,14 @@ names isGlobal =
I.Visible
[("name or hash", Required, definitionQueryArg)]
(P.wrap $ makeExample (names isGlobal) ["foo"] <> " shows the hash and all known names for `foo`.")
( \case
[thing] -> case HQ.fromString thing of
Just hq -> Right $ Input.NamesI isGlobal hq
Nothing ->
Left $
"I was looking for one of these forms: "
<> P.blue "foo .foo.bar foo#abc #abcde .foo.bar#asdf"
_ -> Left (I.help (names isGlobal))
)
\case
[thing] -> case HQ.parseText (Text.pack thing) of
Just hq -> Right $ Input.NamesI isGlobal hq
Nothing ->
Left $
"I was looking for one of these forms: "
<> P.blue "foo .foo.bar foo#abc #abcde .foo.bar#asdf"
_ -> Left (I.help (names isGlobal))
where
cmdName = if isGlobal then "names.global" else "names"
@ -2203,10 +2177,9 @@ dependents =
I.Visible
[("definition", Required, definitionQueryArg)]
"List the named dependents of the specified definition."
( \case
[thing] -> fmap Input.ListDependentsI $ parseHashQualifiedName thing
_ -> Left (I.help dependents)
)
\case
[thing] -> fmap Input.ListDependentsI $ parseHashQualifiedName thing
_ -> Left (I.help dependents)
dependencies =
InputPattern
"dependencies"
@ -2214,10 +2187,9 @@ dependencies =
I.Visible
[("definition", Required, definitionQueryArg)]
"List the dependencies of the specified definition."
( \case
[thing] -> fmap Input.ListDependenciesI $ parseHashQualifiedName thing
_ -> Left (I.help dependencies)
)
\case
[thing] -> fmap Input.ListDependenciesI $ parseHashQualifiedName thing
_ -> Left (I.help dependencies)
namespaceDependencies :: InputPattern
namespaceDependencies =
@ -2227,13 +2199,12 @@ namespaceDependencies =
I.Visible
[("namespace", Optional, namespaceArg)]
"List the external dependencies of the specified namespace."
( \case
[p] -> first fromString $ do
p <- Path.parsePath' p
pure $ Input.NamespaceDependenciesI (Just p)
[] -> pure (Input.NamespaceDependenciesI Nothing)
_ -> Left (I.help namespaceDependencies)
)
\case
[p] -> first P.text do
p <- Path.parsePath' p
pure $ Input.NamespaceDependenciesI (Just p)
[] -> pure (Input.NamespaceDependenciesI Nothing)
_ -> Left (I.help namespaceDependencies)
debugNumberedArgs :: InputPattern
debugNumberedArgs =
@ -2416,12 +2387,11 @@ docsToHtml =
)
]
)
( \case
[namespacePath, destinationFilePath] -> first fromString $ do
np <- Path.parsePath' namespacePath
pure $ Input.DocsToHtmlI np destinationFilePath
_ -> Left $ showPatternHelp docsToHtml
)
\case
[namespacePath, destinationFilePath] -> first P.text do
np <- Path.parsePath' namespacePath
pure $ Input.DocsToHtmlI np destinationFilePath
_ -> Left $ showPatternHelp docsToHtml
docToMarkdown :: InputPattern
docToMarkdown =
@ -2436,12 +2406,11 @@ docToMarkdown =
)
]
)
( \case
[docNameText] -> first fromString $ do
docName <- maybeToEither "Invalid name" . Name.fromText . Text.pack $ docNameText
pure $ Input.DocToMarkdownI docName
_ -> Left $ showPatternHelp docToMarkdown
)
\case
[docNameText] -> first fromString $ do
docName <- maybeToEither "Invalid name" . Name.parseText . Text.pack $ docNameText
pure $ Input.DocToMarkdownI docName
_ -> Left $ showPatternHelp docToMarkdown
execute :: InputPattern
execute =
@ -2459,11 +2428,10 @@ execute =
)
]
)
( \case
[w] -> pure $ Input.ExecuteI w []
(w : ws) -> pure $ Input.ExecuteI w ws
_ -> Left $ showPatternHelp execute
)
\case
[w] -> pure $ Input.ExecuteI (Text.pack w) []
w : ws -> pure $ Input.ExecuteI (Text.pack w) ws
_ -> Left $ showPatternHelp execute
saveExecuteResult :: InputPattern
saveExecuteResult =
@ -2475,10 +2443,9 @@ saveExecuteResult =
( "`add.run name` adds to the codebase the result of the most recent `run` command"
<> "as `name`."
)
( \case
[w] -> pure $ Input.SaveExecuteResultI (Name.unsafeFromString w)
_ -> Left $ showPatternHelp saveExecuteResult
)
\case
[w] -> pure $ Input.SaveExecuteResultI (Name.unsafeParseText (Text.pack w))
_ -> Left $ showPatternHelp saveExecuteResult
ioTest :: InputPattern
ioTest =
@ -2531,11 +2498,10 @@ makeStandalone =
)
]
)
( \case
[main, file] ->
Input.MakeStandaloneI file <$> parseHashQualifiedName main
_ -> Left $ showPatternHelp makeStandalone
)
\case
[main, file] ->
Input.MakeStandaloneI file <$> parseHashQualifiedName main
_ -> Left $ showPatternHelp makeStandalone
runScheme :: InputPattern
runScheme =
@ -2550,10 +2516,9 @@ runScheme =
)
]
)
( \case
(main : args) -> Right $ Input.ExecuteSchemeI main args
_ -> Left $ showPatternHelp runScheme
)
\case
main : args -> Right $ Input.ExecuteSchemeI (Text.pack main) args
_ -> Left $ showPatternHelp runScheme
compileScheme :: InputPattern
compileScheme =
@ -2570,11 +2535,10 @@ compileScheme =
)
]
)
( \case
[main, file] ->
Input.CompileSchemeI file <$> parseHashQualifiedName main
_ -> Left $ showPatternHelp compileScheme
)
\case
[main, file] ->
Input.CompileSchemeI (Text.pack file) <$> parseHashQualifiedName main
_ -> Left $ showPatternHelp compileScheme
schemeLibgen :: InputPattern
schemeLibgen =
@ -2597,11 +2561,10 @@ schemeLibgen =
)
]
)
( \case
[] -> pure $ Input.GenSchemeLibsI Nothing
[dir] -> pure . Input.GenSchemeLibsI $ Just dir
_ -> Left $ showPatternHelp schemeLibgen
)
\case
[] -> pure $ Input.GenSchemeLibsI Nothing
[dir] -> pure . Input.GenSchemeLibsI $ Just dir
_ -> Left $ showPatternHelp schemeLibgen
fetchScheme :: InputPattern
fetchScheme =
@ -2634,16 +2597,15 @@ fetchScheme =
)
]
)
( \case
[] -> pure (Input.FetchSchemeCompilerI "unison" JitInfo.currentRelease)
[name] -> pure (Input.FetchSchemeCompilerI name branch)
where
branch
| name == "unison" = JitInfo.currentRelease
| otherwise = "main"
[name, branch] -> pure (Input.FetchSchemeCompilerI name branch)
_ -> Left $ showPatternHelp fetchScheme
)
\case
[] -> pure (Input.FetchSchemeCompilerI "unison" JitInfo.currentRelease)
[name] -> pure (Input.FetchSchemeCompilerI name branch)
where
branch
| name == "unison" = JitInfo.currentRelease
| otherwise = "main"
[name, branch] -> pure (Input.FetchSchemeCompilerI name branch)
_ -> Left $ showPatternHelp fetchScheme
createAuthor :: InputPattern
createAuthor =
@ -2664,8 +2626,10 @@ createAuthor =
)
)
( \case
symbolStr : authorStr@(_ : _) -> first fromString $ do
symbol <- Path.definitionNameSegment symbolStr
symbolStr : authorStr@(_ : _) -> first P.text do
symbol <-
Megaparsec.runParser (Megaparsec.withParsecT (fmap NameSegment.renderParseErr) NameSegment.segmentP <* Megaparsec.eof) "" symbolStr
& mapLeft (Text.pack . Megaparsec.errorBundlePretty)
-- let's have a real parser in not too long
let author :: Text
author = Text.pack $ case (unwords authorStr) of
@ -2745,10 +2709,10 @@ diffNamespaceToPatch =
help = P.wrap "Create a patch from a namespace diff.",
parse = \case
[branchId1, branchId2, patch] ->
mapLeft fromString do
mapLeft P.text do
branchId1 <- Input.parseBranchId branchId1
branchId2 <- Input.parseBranchId branchId2
patch <- Path.parseSplit' Path.definitionNameSegment patch
patch <- Path.parseSplit' patch
pure (Input.DiffNamespaceToPatchI Input.DiffNamespaceToPatchInput {branchId1, branchId2, patch})
_ -> Left (showPatternHelp diffNamespaceToPatch)
}
@ -3020,7 +2984,7 @@ upgrade =
where
parseRelativeNameSegment :: String -> Maybe NameSegment
parseRelativeNameSegment string = do
name <- Name.fromText (Text.pack string)
name <- Name.parseText (Text.pack string)
guard (Name.isRelative name)
segment NE.:| [] <- Just (Name.reverseSegments name)
Just segment
@ -3274,14 +3238,10 @@ dependencyArg =
ArgumentType
{ typeName = "project dependency",
suggestions = \q cb _http p -> Codebase.runTransaction cb do
prefixCompleteNamespace q (p Path.:> Name.libSegment),
prefixCompleteNamespace q (p Path.:> NameSegment.libSegment),
fzfResolver = Just Resolvers.projectDependencyResolver
}
-- | Names of child branches of the branch, only gives options for one 'layer' deeper at a time.
childNamespaceNames :: Branch.Branch0 m -> [Text]
childNamespaceNames b = NameSegment.toText <$> Map.keys (Branch.nonEmptyChildren b)
newNameArg :: ArgumentType
newNameArg =
ArgumentType
@ -3338,8 +3298,7 @@ remoteNamespaceArg =
"ghs" -> complete "git(git@github.com:"
"gls" -> complete "git(git@gitlab.com:"
"bbs" -> complete "git(git@bitbucket.com:"
_ -> do
sharePathCompletion http input,
_ -> sharePathCompletion http input,
fzfResolver = Nothing
}
@ -3819,7 +3778,7 @@ parseHashQualifiedName s =
<> "I expected something like `foo`, `#abc123`, or `foo#abc123`."
)
Right
$ HQ.fromString s
$ HQ.parseText (Text.pack s)
parseWriteGitRepo :: String -> String -> Either (P.Pretty P.ColorText) WriteGitRepo
parseWriteGitRepo label input = do

View File

@ -130,8 +130,8 @@ import Unison.Share.Sync.Types (CodeserverTransportError (..))
import Unison.ShortHash qualified as ShortHash
import Unison.Sync.Types qualified as Share
import Unison.Syntax.DeclPrinter qualified as DeclPrinter
import Unison.Syntax.HashQualified qualified as HQ (toString, toText, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toString, toText)
import Unison.Syntax.HashQualified qualified as HQ (toText, unsafeFromVar)
import Unison.Syntax.Name qualified as Name (toText)
import Unison.Syntax.NamePrinter
( prettyHashQualified,
prettyHashQualified',
@ -143,6 +143,7 @@ import Unison.Syntax.NamePrinter
prettyShortHash,
styleHashQualified,
)
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Syntax.TermPrinter qualified as TermPrinter
import Unison.Syntax.TypePrinter qualified as TypePrinter
import Unison.Term (Term)
@ -305,7 +306,7 @@ notifyNumbered = \case
"",
tip $
"Add"
<> prettyName "License"
<> prettyName (Name.fromSegment "License")
<> "values for"
<> prettyName (Name.fromSegment authorNS)
<> "under"
@ -492,7 +493,7 @@ notifyNumbered = \case
E.AmbiguousReset'Hash -> \xs -> xs
E.AmbiguousReset'Target -> \xs -> "<some hash>" : xs
reset = IP.makeExample IP.reset
relPath0 = prettyPath' (Path.toPath' path)
relPath0 = prettyPath path
absPath0 = review ProjectUtils.projectBranchPathPrism (ProjectAndBranch (pn0 ^. #projectId) (bn0 ^. #branchId), path)
ListNamespaceDependencies _ppe _path Empty -> ("This namespace has no external dependencies.", mempty)
ListNamespaceDependencies ppe path' externalDependencies ->
@ -514,12 +515,13 @@ notifyNumbered = \case
newNextNum = nextNum + length unnumberedNames
in ( newNextNum,
( nameToNum <> (Map.fromList (zip unnumberedNames [nextNum ..])),
args <> fmap Name.toString unnumberedNames
args <> fmap Name.toText unnumberedNames
)
)
)
(1, (mempty, mempty))
& snd
& over (_2 . mapped) Text.unpack
externalDepsTable :: Map LabeledDependency (Set Name) -> [(P.Pretty P.ColorText, P.Pretty P.ColorText)]
externalDepsTable = ifoldMap $ \ld dependents ->
[(prettyLD ld, prettyDependents dependents)]
@ -610,7 +612,7 @@ showListEdits patch ppe =
TermEdit.Replace rhsRef _typing -> do
n2 <- gets snd <* modify (second succ)
let rhsTermName = PPE.termName ppe (Referent.Ref rhsRef)
lift $ tell ([lhsHash], [HQ.toString rhsTermName])
lift $ tell ([lhsHash], [Text.unpack (HQ.toText rhsTermName)])
pure
( showNum n1 <> (P.syntaxToColor . prettyHashQualified $ lhsTermName),
"-> " <> showNum n2 <> (P.syntaxToColor . prettyHashQualified $ rhsTermName)
@ -635,7 +637,7 @@ showListEdits patch ppe =
TypeEdit.Replace rhsRef -> do
n2 <- gets snd <* modify (second succ)
let rhsTypeName = PPE.typeName ppe rhsRef
lift $ tell ([lhsHash], [HQ.toString rhsTypeName])
lift $ tell ([lhsHash], [Text.unpack (HQ.toText rhsTypeName)])
pure
( showNum n1 <> (P.syntaxToColor . prettyHashQualified $ lhsTypeName),
"-> " <> showNum n2 <> (P.syntaxToColor . prettyHashQualified $ rhsTypeName)
@ -648,7 +650,7 @@ notifyUser dir = \case
. P.warnCallout
. P.wrap
$ "Cannot save the last run result into"
<> P.backticked (P.string (Name.toString name))
<> P.backticked (P.text (Name.toText name))
<> "because that name conflicts with a name in the scratch file."
NoLastRunResult ->
pure
@ -747,7 +749,7 @@ notifyUser dir = \case
"Use"
<> IP.makeExample
IP.todo
[ prettyPath' (snoc mergedPath "patch"),
[ prettyPath' (snoc mergedPath NameSegment.defaultPatchSegment),
prettyPath' mergedPath
]
<> "to see what work is remaining for the merge.",
@ -886,21 +888,21 @@ notifyUser dir = \case
P.lines
[ P.wrap $
"I looked for a function"
<> P.backticked (P.string main)
<> P.backticked (P.text main)
<> "in the most recently typechecked file and codebase but couldn't find one. It has to have the type:",
"",
P.indentN 2 $ P.lines [P.string main <> " : " <> TypePrinter.pretty ppe t | t <- ts]
P.indentN 2 $ P.lines [P.text main <> " : " <> TypePrinter.pretty ppe t | t <- ts]
]
BadMainFunction what main ty ppe ts ->
pure . P.callout "😶" $
P.lines
[ P.string "I found this function:",
"",
P.indentN 2 $ P.string main <> " : " <> TypePrinter.pretty ppe ty,
P.indentN 2 $ P.text main <> " : " <> TypePrinter.pretty ppe ty,
"",
P.wrap $ P.string "but in order for me to" <> P.backticked (P.string what) <> "it needs to be a subtype of:",
P.wrap $ P.string "but in order for me to" <> P.backticked (P.text what) <> "it needs to be a subtype of:",
"",
P.indentN 2 $ P.lines [P.string main <> " : " <> TypePrinter.pretty ppe t | t <- ts]
P.indentN 2 $ P.lines [P.text main <> " : " <> TypePrinter.pretty ppe t | t <- ts]
]
NoUnisonFile -> do
dir' <- canonicalizePath dir
@ -1073,11 +1075,11 @@ notifyUser dir = \case
formatEntry :: (Var v) => PPE.PrettyPrintEnv -> ShallowListEntry v a -> (Pretty, Pretty)
formatEntry ppe = \case
ShallowTermEntry termEntry ->
( P.syntaxToColor . prettyHashQualified' . fmap Name.fromSegment . Backend.termEntryHQName $ termEntry,
( P.syntaxToColor . prettyHashQualified' . Backend.termEntryHQName $ termEntry,
P.lit "(" <> maybe "type missing" (TypePrinter.pretty ppe) (Backend.termEntryType termEntry) <> P.lit ")"
)
ShallowTypeEntry typeEntry ->
( P.syntaxToColor . prettyHashQualified' . fmap Name.fromSegment . Backend.typeEntryHQName $ typeEntry,
( P.syntaxToColor . prettyHashQualified' . Backend.typeEntryHQName $ typeEntry,
isBuiltin (typeEntryReference typeEntry)
)
ShallowBranchEntry ns _ (NamespaceStats {numContainedTerms, numContainedTypes}) ->
@ -1549,8 +1551,7 @@ notifyUser dir = \case
"",
P.wrap "Try again with a few more hash characters to disambiguate."
]
BadName n ->
pure . P.wrap $ P.string n <> " is not a kind of name I understand."
BadName n -> pure . P.wrap $ P.text n <> " is not a kind of name I understand."
TermNotFound' sh ->
pure $
"I could't find a term with hash "
@ -1864,9 +1865,7 @@ notifyUser dir = \case
( "Use"
<> IP.makeExample IP.mergeLocal [prettySlashProjectBranchName (UnsafeProjectBranchName "somebranch")]
<> "or"
<> IP.makeExample
IP.mergeLocal
[prettyAbsolute (Path.Absolute (Path.fromList ["path", "to", "code"]))]
<> IP.makeExample IP.mergeLocal [prettyAbsolute (Path.Absolute (Path.fromList ["path", "to", "code"]))]
<> "to initialize this branch."
)
CreatedProjectBranchFrom'OtherBranch (ProjectAndBranch otherProject otherBranch) ->
@ -2211,19 +2210,19 @@ notifyUser dir = \case
UpgradeFailure path old new ->
pure . P.wrap $
"I couldn't automatically upgrade"
<> P.text (NameSegment.toText old)
<> P.text (NameSegment.toEscapedText old)
<> "to"
<> P.group (P.text (NameSegment.toText new) <> ".")
<> P.group (P.text (NameSegment.toEscapedText new) <> ".")
<> "However, I've added the definitions that need attention to the top of"
<> P.group (prettyFilePath path <> ".")
UpgradeSuccess old new ->
pure . P.wrap $
"I upgraded"
<> P.text (NameSegment.toText old)
<> P.text (NameSegment.toEscapedText old)
<> "to"
<> P.group (P.text (NameSegment.toText new) <> ",")
<> P.group (P.text (NameSegment.toEscapedText new) <> ",")
<> "and removed"
<> P.group (P.text (NameSegment.toText old) <> ".")
<> P.group (P.text (NameSegment.toEscapedText old) <> ".")
where
_nameChange _cmd _pastTenseCmd _oldName _newName _r = error "todo"
@ -2266,7 +2265,7 @@ prettyDownloadEntitiesError = \case
Share.DownloadEntitiesInvalidRepoInfo err repoInfo -> invalidRepoInfo err repoInfo
Share.DownloadEntitiesUserNotFound userHandle -> shareUserNotFound (Share.RepoInfo userHandle)
Share.DownloadEntitiesProjectNotFound project -> shareProjectNotFound project
Share.DownloadEntitiesEntityValidationFailure err -> prettyEntityValidationError err
Share.DownloadEntitiesEntityValidationFailure err -> prettyEntityValidationFailure err
prettyFastForwardPathError :: Share.Path -> Share.FastForwardPathError -> Pretty
prettyFastForwardPathError path = \case
@ -2319,7 +2318,7 @@ prettyUpdatePathError repoInfo = \case
prettyUploadEntitiesError :: Share.UploadEntitiesError -> Pretty
prettyUploadEntitiesError = \case
Share.UploadEntitiesError'EntityValidationFailure validationFailureErr -> prettyValidationFailure validationFailureErr
Share.UploadEntitiesError'EntityValidationFailure validationFailureErr -> prettyEntityValidationFailure validationFailureErr
Share.UploadEntitiesError'HashMismatchForEntity (Share.HashMismatchForEntity {supplied, computed}) ->
hashMismatchFromShare supplied computed
Share.UploadEntitiesError'InvalidRepoInfo err repoInfo -> invalidRepoInfo err repoInfo
@ -2328,14 +2327,16 @@ prettyUploadEntitiesError = \case
Share.UploadEntitiesError'ProjectNotFound project -> shareProjectNotFound project
Share.UploadEntitiesError'UserNotFound userHandle -> shareUserNotFound (Share.RepoInfo userHandle)
prettyValidationFailure :: Share.EntityValidationError -> Pretty
prettyValidationFailure = \case
prettyEntityValidationFailure :: Share.EntityValidationError -> Pretty
prettyEntityValidationFailure = \case
Share.EntityHashMismatch entityType (Share.HashMismatchForEntity {supplied, computed}) ->
P.lines
[ P.wrap $ "The hash associated with the given " <> prettyEntityType entityType <> " entity is incorrect.",
"",
P.wrap $ "The associated hash is: " <> prettyHash32 supplied,
P.wrap $ "The computed hash is: " <> prettyHash32 computed
P.wrap $ "The computed hash is: " <> prettyHash32 computed,
"",
"Please create an issue and report this to the Unison team."
]
Share.UnsupportedEntityType hash32 entityType ->
P.lines
@ -2350,6 +2351,7 @@ prettyValidationFailure = \case
P.wrap $ "The error was: " <> P.text msg
]
Share.HashResolutionFailure hash32 ->
-- See https://github.com/unisonweb/unison/pull/4381#discussion_r1452652087 for discussion.
P.lines
[ P.wrap $ "Failed to resolve a referenced hash when validating the hash for " <> prettyHash32 hash32 <> ".",
"Please create an issue and report this to the Unison team"
@ -2402,34 +2404,6 @@ prettyTransportError = \case
responseRequestId =
fmap Text.decodeUtf8 . List.lookup "X-RequestId" . Foldable.toList @Seq . Servant.responseHeaders
prettyEntityValidationError :: Share.EntityValidationError -> Pretty
prettyEntityValidationError = \case
Share.EntityHashMismatch typ (Share.HashMismatchForEntity {supplied, computed}) ->
P.lines
[ P.wrap $ "The hash associated with the given " <> prettyEntityType typ <> " entity is incorrect.",
"",
P.wrap $ "The associated hash is: " <> prettyHash32 supplied,
P.wrap $ "The computed hash is: " <> prettyHash32 computed
]
Share.UnsupportedEntityType hash typ ->
P.lines
[ P.wrap $ "The entity with hash " <> prettyHash32 hash <> " of type " <> prettyEntityType typ <> " is not supported by your version of ucm.",
P.wrap $ "Try upgrading to the latest version of ucm."
]
Share.InvalidByteEncoding hash typ err ->
P.lines
[ P.wrap $ "Failed to decode a " <> prettyEntityType typ <> " entity with the hash " <> prettyHash32 hash <> ".",
"Please create an issue and report this to the Unison team",
"",
P.wrap $ "The error was: " <> P.text err
]
Share.HashResolutionFailure hash ->
-- See https://github.com/unisonweb/unison/pull/4381#discussion_r1452652087 for discussion.
P.lines
[ P.wrap $ "Failed to resolve data when hashing " <> prettyHash32 hash <> ".",
"Please create an issue and report this to the Unison team"
]
prettyEntityType :: Share.EntityType -> Pretty
prettyEntityType = \case
Share.TermComponentType -> "term component"
@ -2735,7 +2709,7 @@ renderNameConflicts ppe conflictedNames = do
P.lines <$> do
for (Map.toList conflictedNames) $ \(name, hashes) -> do
prettyConflicts <- for hashes \hash -> do
n <- addNumberedArg (HQ.toString hash)
n <- addNumberedArg (Text.unpack (HQ.toText hash))
pure $ formatNum n <> (P.blue . P.syntaxToColor . prettyHashQualified $ hash)
pure . P.wrap $
( "The "
@ -2767,7 +2741,7 @@ renderEditConflicts ppe Patch {..} = do
<> (fmap Right . Map.toList . R.toMultimap . R.filterManyDom $ _termEdits)
numberedHQName :: HQ.HashQualified Name -> Numbered Pretty
numberedHQName hqName = do
n <- addNumberedArg (HQ.toString hqName)
n <- addNumberedArg (Text.unpack (HQ.toText hqName))
pure $ formatNum n <> styleHashQualified P.bold hqName
formatTypeEdits ::
(Reference, Set TypeEdit.TypeEdit) ->
@ -2880,11 +2854,11 @@ todoOutput ppe todo = runNumbered do
todoEdits :: Numbered Pretty
todoEdits = do
numberedTypes <- for (unscore <$> dirtyTypes) \(ref, displayObj) -> do
n <- addNumberedArg (HQ.toString $ PPE.typeName ppeu ref)
n <- addNumberedArg (Text.unpack (HQ.toText $ PPE.typeName ppeu ref))
pure $ formatNum n <> prettyDeclPair ppeu (ref, displayObj)
let filteredTerms = goodTerms (unscore <$> dirtyTerms)
termNumbers <- for filteredTerms \(ref, _, _) -> do
n <- addNumberedArg (HQ.toString $ PPE.termName ppeu ref)
n <- addNumberedArg (Text.unpack (HQ.toText $ PPE.termName ppeu ref))
pure $ formatNum n
let formattedTerms = TypePrinter.prettySignaturesCT ppes filteredTerms
numberedTerms = zipWith (<>) termNumbers formattedTerms
@ -3300,8 +3274,8 @@ showDiffNamespace sn ppe oldPath newPath OBD.BranchDiffOutput {..} =
-- prefixBranchId ".base" "List.map" -> ".base.List.map"
prefixBranchId :: Input.AbsBranchId -> Name -> String
prefixBranchId branchId name = case branchId of
Left sch -> "#" <> SCH.toString sch <> ":" <> Name.toString (Name.makeAbsolute name)
Right pathPrefix -> Name.toString (Name.makeAbsolute . Path.prefixName pathPrefix $ name)
Left sch -> "#" <> SCH.toString sch <> ":" <> Text.unpack (Name.toText (Name.makeAbsolute name))
Right pathPrefix -> Text.unpack (Name.toText (Name.makeAbsolute . Path.prefixName pathPrefix $ name))
addNumberedArg' :: String -> Numbered Pretty
addNumberedArg' s = case sn of
@ -3558,7 +3532,7 @@ numberedArgsForEndangerments (PPED.unsuffixifiedPPE -> ppe) m =
m
& Map.elems
& concatMap toList
& fmap (HQ.toString . PPE.labeledRefName ppe)
& fmap (Text.unpack . HQ.toText . PPE.labeledRefName ppe)
-- | Format and render all dependents which are endangered by references going extinct.
endangeredDependentsTable ::

View File

@ -10,6 +10,7 @@ import Control.Lens hiding (List, (:<))
import Control.Monad.Reader
import Data.Aeson qualified as Aeson
import Data.Aeson.Types qualified as Aeson
import Data.Foldable qualified as Foldable
import Data.List.Extra (nubOrdOn)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Map qualified as Map
@ -18,6 +19,7 @@ import Data.Text qualified as Text
import Language.LSP.Protocol.Lens
import Language.LSP.Protocol.Message qualified as Msg
import Language.LSP.Protocol.Types
import Text.Megaparsec qualified as Megaparsec
import Unison.Codebase.Path (Path)
import Unison.Codebase.Path qualified as Path
import Unison.HashQualified qualified as HQ
@ -41,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 (fromText, toText)
import Unison.Syntax.Name qualified as Name (parseText, nameP, toText)
import Unison.Syntax.TypePrinter qualified as TypePrinter
import Unison.Util.Monoid qualified as Monoid
import Unison.Util.Pretty qualified as Pretty
@ -190,7 +192,7 @@ namesToCompletionTree Names {terms, types} =
-- Special docs like "README" will still appear since they're not named 'doc'
isDefinitionDoc name =
case Name.reverseSegments name of
("doc" :| _) -> True
((NameSegment.toUnescapedText -> "doc") :| _) -> True
_ -> False
nameToCompletionTree :: Name -> LabeledDependency -> CompletionTree
@ -228,27 +230,25 @@ nameToCompletionTree name ref =
-- @@
matchCompletions :: CompletionTree -> Text -> [(Path, Name, LabeledDependency)]
matchCompletions (CompletionTree tree) txt =
matchSegments segments (Set.toList <$> tree)
case Megaparsec.runParser (Name.nameP <* Megaparsec.eof) "" (Text.unpack txt) of
Left _ -> []
Right name -> matchSegments (Foldable.toList @NonEmpty (Name.segments name)) (Set.toList <$> tree)
where
segments :: [Text]
segments =
Text.splitOn "." txt
& filter (not . Text.null)
matchSegments :: [Text] -> Cofree (Map NameSegment) [(Name, LabeledDependency)] -> [(Path, Name, LabeledDependency)]
matchSegments :: [NameSegment] -> Cofree (Map NameSegment) [(Name, LabeledDependency)] -> [(Path, Name, LabeledDependency)]
matchSegments xs (currentMatches :< subtreeMap) =
case xs of
[] ->
let current = currentMatches <&> (\(name, def) -> (Path.empty, name, def))
in (current <> mkDefMatches subtreeMap)
[prefix] ->
Map.dropWhileAntitone ((< prefix) . NameSegment.toText) subtreeMap
& Map.takeWhileAntitone (Text.isPrefixOf prefix . NameSegment.toText)
Map.dropWhileAntitone (< prefix) subtreeMap
& Map.takeWhileAntitone (NameSegment.isPrefixOf prefix)
& \matchingSubtrees ->
let subMatches = ifoldMap (\ns subTree -> matchSegments [] subTree & consPathPrefix ns) matchingSubtrees
in subMatches
(ns : rest) ->
foldMap (matchSegments rest) (Map.lookup (NameSegment ns) subtreeMap)
& consPathPrefix (NameSegment ns)
foldMap (matchSegments rest) (Map.lookup ns subtreeMap)
& consPathPrefix ns
consPathPrefix :: NameSegment -> ([(Path, Name, LabeledDependency)]) -> [(Path, Name, LabeledDependency)]
consPathPrefix ns = over (mapped . _1) (Path.cons ns)
mkDefMatches :: Map NameSegment (Cofree (Map NameSegment) [(Name, LabeledDependency)]) -> [(Path, Name, LabeledDependency)]
@ -340,8 +340,8 @@ instance Aeson.ToJSON CompletionItemDetails where
instance Aeson.FromJSON CompletionItemDetails where
parseJSON = Aeson.withObject "CompletionItemDetails" \obj -> do
dep <- ((obj Aeson..: "dep") >>= ldParser)
relativeName <- (obj Aeson..: "relativeName" >>= maybe (fail "Invalid name in CompletionItemDetails") pure . Name.fromText)
fullyQualifiedName <- (obj Aeson..: "fullyQualifiedName" >>= maybe (fail "Invalid name in CompletionItemDetails") pure . Name.fromText)
relativeName <- (obj Aeson..: "relativeName" >>= maybe (fail "Invalid name in CompletionItemDetails") pure . Name.parseText)
fullyQualifiedName <- (obj Aeson..: "fullyQualifiedName" >>= maybe (fail "Invalid name in CompletionItemDetails") pure . Name.parseText)
fileUri <- obj Aeson..: "fileUri"
pure $ CompletionItemDetails {..}
where

View File

@ -458,7 +458,7 @@ mkTypeSignatureHints parsedFile typecheckedFile = do
& Zip.zip symbolsWithoutTypeSigs
& imapMaybe
( \v (ann, (_ann, ref, _wk, _trm, typ)) -> do
name <- Name.fromText (Var.name v)
name <- Name.parseText (Var.name v)
range <- annToRange ann
let newRangeEnd =
range ^. LSPTypes.start

View File

@ -94,7 +94,7 @@ hoverInfo uri pos =
LD.TypeReference (Reference.Builtin {}) -> do
pure (symAtCursor <> " : <builtin>")
LD.TypeReference ref@(Reference.DerivedId refId) -> do
nameAtCursor <- MaybeT . pure $ Name.fromText symAtCursor
nameAtCursor <- MaybeT . pure $ Name.parseText symAtCursor
decl <- LSPQ.getTypeDeclaration uri refId
let typ = Text.pack . Pretty.toPlain prettyWidth . Pretty.syntaxToColor $ DeclPrinter.prettyDecl pped ref (HQ.NameOnly nameAtCursor) decl
pure typ

View File

@ -0,0 +1,687 @@
-- | Unfortunately, due to bugs in previous versions of UCM there are some entities whose
-- hashes are not what they should be, but have propagated widely into end-user's codebases.
-- This is a map from the nominal hash to the actual hash of the component of components which
-- are known to have widely available incorrect hashes.
--
-- Keeping this table allows us to allow UCM to validate the hashes of new terms which are
-- received from remote sources, but allows a bit of lee-way for these known exceptions.
--
-- While we certainly don't want to make this a common occurence, it's safe as long as we
-- are specific about both the provided and actual hashes.
module Unison.Share.ExpectedHashMismatches (expectedComponentHashMismatches, expectedCausalHashMismatches) where
import Data.Map qualified as Map
import U.Util.Base32Hex qualified as Base32Hex
import Unison.Hash32 (Hash32 (..))
import Unison.Prelude
expectedComponentHashMismatches :: Map Hash32 Hash32
expectedComponentHashMismatches =
Map.fromList . map (\(nominalComponentHash, actualComponentHash) -> (UnsafeFromBase32Hex . Base32Hex.UnsafeFromText $ nominalComponentHash, UnsafeFromBase32Hex . Base32Hex.UnsafeFromText $ actualComponentHash)) $
[ ("92lrlhpjro7f3ljk2fvaepus1bd75abshm90hjciuq90v7suiihms6h1poig89duobul5o817475mr5453dj57rob67d866tf43sooo", "8o4a84k6b0s9gmrrb7c2ps3qmn2c75jj2tpt2rbhrgbo08f6kctb19agvbsqpma0oh1a9e4tngclnb6ign191pb014811b08nvhlo30"),
("bpt1vj3hv98hki99br4mndipbnd5ubnj4ikd4s359bj5uket9125a9g8s3a39ra7mffbq70c2gpbigtdods5n7i500giqrhslemck80", "7b7vu3vlbtsucd2bcidccjoeru6er14sdj7mjqf4h081jqqk02t5d6md3ag1qkl8dbg7310r1cpjrr8eaqg3tgsuvpn59nvkjrdou0g"),
("dhr9g21r1nop0imppadgpf4meomuv2nm9fkmomrs672h4l1epntcqg0jh0uitqftc30e0fa08qhogotdhv9ei2du2k01irkh4jo7avo", "607m7vvhrglru5bhpjvqp2oij7hm2bc20lgn00ce6slk8chokm980ma0s27glkhtrfkgncshfhtog7u8ovdr47vq17e7m53ra1n1hh8"),
("f3rq379n5jobdo9f1cn44o1iq92cvi6kg81n0obku35oop1ihb2fqn3r9mccoida87spg5ltpbpknbvgceeu84lk2p3rbgsqbu2dbq0", "rndmus44tpc0e8n47811apk0porkq21bemhp8757dmdjhvf4rc2f7lst8r8ehd9klk1bi2r3uvf0kd3279bpbmkr6iq29j9kkuaotf8"),
("fovehf5jh4oki32asgujmp3toq87fm09fjo4p7e90173ajiq0l23s3bv4kmgphu85f3rn0222irmgi2lcbklso47cbmpr0r6jthc9go", "daoq65eapb7bfbh1apcimmjm589ujcunuiel8pbrimo3djkq5gdii3uk0282grobf14tvt5i1agbigptjnlg0l0h92if61s7cfik3kg"),
("g2abvlgb173sstq1m7i08ne0a4mpm13deh9is58l3mk2ruqjuko7b0b7legjqv7shf956o7rnssup6t7a92bhah307faimau7piuc48", "q817is6du9lv6t9k99lkt3ao2grim2f0srk621ralfntvmcdi23du1baonp2ph2o7iv5m9l67eoehveric8qehm0anukpa3mpaiu6f8"),
("hflvc8hf7pkc85ueapi3b1lshspfk8ui1ud5895hojtc0fj85nl2mur6pngo81i215q9v2snv3mar826hu2t8rkra3a1k94to3ba3jo", "vl4q6rfu6buq7icleha1l05jvr4srkhocu6ffhmm44la2c72tk02o3ahjj4cio8ra39d7tudcfeobjj4vjqlf1ujrf8kvore98h44t8"),
("ia1rqqv36qltembs4opn77djv9hhmeki962lcr0rec5tmla73t421lhqt8r5d5o3cnf8e0gi78m8sbicor2vhlseimaqfntdlp947mo", "sqe133m72nf32mbp2tau3g5bih8phrqqh6eushlbcnftaj2stk1pfqpmdakr24va6h5sp22drm6bnkbbs70dvls5veoeqr69mstpboo"),
("iffbns77p3m0f9vrn0i6jhomijoiond6o1as88a70ouvts1531l64iuop8vru70gl7hursub85ga4eivkgm0sk502qmjj4c9jd5nndg", "6r3stegrgqbtffj3fnjsecusvbv1gg0cmj2hhg24fciv56lo843dupnkt48rip75dop1226a9nskraiug2l2h7q5rbepgnmh4gjkms8"),
("m18cqudc5vjobuu2lasig2ok9k4io4l0qnmdo239a6qol2f1g49g63gvot4u9hlbse2mbdc2scet49vi9e8iu9kkjvcfo3f4uqt27d0", "bg1njbqsc66f2krtti5bsrreh4osqhuq3stee4f5ij4v32k42k88mraiqv85v8jj33ab07ul92ii3nvn254v3p8isbaor25a69u5r98"),
("mtogtbq9est6bc7aqq62auo37dso54oncgj5jgrhnd1h00b6e970s3h9uerq4v1emmr33vgrdlfaokf6mt51c2duasmrhg22g5mauro", "7pb4sehbpqo4fkdlhvem1vv96g6l2opk4j5cdb38p4s7hi1avj109u6j06au4kopdsf5fjf03kmgook7s9v68a0s169uaquoes20io0"),
("n11m3pvh74mjtvoc9rkhqie17mg75gtdihjvshl2u2foeqo9905ds7jsjav20u1jn5vft29cquedjjtdbi06mv5n3r2nel3hnnii9r0", "8ptrsajcjki99r59laq39ouds9l753kkd34poa56pd1oqk8jm92alpoveguaq7esjihti5l36746pg34uqje104aeuk271jtkvce3rg"),
("n4qoc7gmbs93c8ho8cl5km3oc44jiu5de877ggvul5le8uoq6vvo3qgo5flvk9jstdn674u7kb3utihl7rhkpkqas9vlocosvpgo6f0", "b7hijoeef7ftr0hsf6ovo65l1fpfkcli5g9cfpflphkgqu4bsp4qr0cgqj5guv6c7pp0rt68s8rka9kb5rvccutu49p92k3onnhen6o"),
("omd4b25k692lk2rd6uan5t6d9g5o6rmmdligal4c82dkjvf9tsp1t5nat9j210fhr8ubojul2k94gf2qs7b4eo9em75tk049vvddtvo", "pjj63f0l25muajj60qnvvsd6vi1fcjrq0tuk70kuusbqe5iuv4a11gd8kqgg9236qeu0cqi6cljn2rukou93ad1udku1rlinbs89r1g"),
("pk2u5cm639krojutestidqh8quam72h1cac76hivq3bj5vap7cejmuucv965c101nfgd4272iegcb74eld8e3bavs0grit3i53f3rj0", "q49hpmb3pcffmfer1746968145uvskfi3lqh0bvoajr4u6tcrpk5mc1708rimdr4cemfec4s4ci4fl7dqbssd4rhm7jtje0ffq5kf10"),
("q4bi57ku4agrgulkiqmfdh8cpa81o3db2n8te68vdrcvmqnu7a1vi5coovnmju0t2f32pk8v7tc61g423bjqi90n40i9d181ndmjlh8", "r2mk6ikg0kmgmlne6jnmvvm1i29o41ej8fg2epd56ul2m3p9r2t9vl4d89k0ohj13ejn1qq399nn567q2mjfu2hl085ongd3n35g3tg"),
("qdrga4tb3t6ler1scpm0qdfkdplc9skf4sunvj9bo5um7sa5q7lilmik3cvbjo7dsu4o4gmvlq3fp1lmrps627e2ttophh56vqhlnr8", "160s1hvc8jfd4c8lcfhr8e9s697a93qjtd3bsud1iquj9l8bdco7da2pn77baq6h3l2itcg8tepa99v88tlrqfaao8c9pajcvtv9v98"),
("spaaj7f3or3jtd4flmk9o3932ieourarbetnhnsjfgbs7gihatmguthg7umphvegdnfitrks08r3g1brp5ksp6049cec7aoofc70qqo", "2sllqejg089b74id2ou1krr4lm1ka70hltltn1nn8vbrje4hnvdho9tc2erq7ild6ah1nqail4v8tci3ko7s3p91ahlv1hbs9j6g25o"),
("sros4nt55is5pjko2ktf3tr8994f46mis9v08pbq3jrc29img09vqm20tjhf921vefialo111a5h9gv129uf9k971uf9n3m98jjq358", "fbi23ca6fu8b1jc844g1vjmdj557vl0rt93tqkrn59tfjti62981s7sgirmhnhd4faipp3hcaaa0d398stbc5d4samk6bapss6ihtvg"),
("t3r6mj586o22l0rrf020id7tg2pdd2akoo7cmdl6f24bp2qfl8rn4roo4jkvjj0b6eeesfun32a1pgqu4jfs71bo3bdl5p2prtt3gt0", "qa9ibjdi8cdh89c6pajmf0b17jg4gb26qi0o1qmfb0kr5cru88j3b0cbh53q9db4vgogv642q9rccv60brbnd31qpg8kju2o7mlbfl0"),
("tdtiedpmlmt933l78s4ce26eilajfbtri44amjrbbhg8amlo9l6psgec96vlfuv17of2bds398hkg4jp82vht98vdef4hnflc1c20po", "dvvj64d9seq1t0sn70n2h117docigoc4cr7llrc354r04j4fmoc3ica7q4ooq72sfkn92oooibivs8of22etn2qaj51g8ieluarh5dg"),
("ufm68453ujd177hbr0v5qgljmj5d3jjh6l1i0kjpol1gdva69apne5tj49pft97bnhdkiaicic1gnh3374m092r7tog4thlgro9etn8", "isdi2qe63pi7qrc9ecs6hdlona9e3kimughgh04d6kkn4o3gcutvci2ullpp1l77bq85sdfri4ilahalssvj3nnh58vq1jfqq9rrgk0"),
("v4q0jv19b7o2iukcd8or71537d3jqg78m7oddr9tao1t8318gfmn2fb6fsjq55kirc5jg575pmh5mkhu9jmuj2j4k1uoga10ap0luv0", "jliprhj9h6e86n4paqeinof4e2b6roklobakmdpn8r4cs0km7tpm79no3nfbaubk0rjj8o2e2snk7g4cooklut44abbhdq6trt4l1b0"),
("c71vkf3hg8der3l5rrorp7srcll0pu27b1t7an34u15e47fac0jrki8jt667452ffjmjoekfjtgei667hmndvvlngmrla34hqjvig20", "7inqv5ibqvevperl08jlf7s8rhds79inonjhfv2lfjou2o6ap91nm9seq2ut96pocs1m271q3kib40i15cufd86ku808oamq8igak5g"),
("chf6psj1cunsrm5gmmd7kumkv3b1qoqle7kkbr9toeq32qf9qv52ntqlv6fth7jc71phbee9r4q66egl17ji72u9ubomcjtvcpttl38", "ghtjsdlainihh2cb1s8s9j4j94bmkuif8acp0b0dmh69a40roih8ib9db7gkcg9kc87fc3fcmcll76ucvgdjffuksiid1flciteecf0"),
("co9ub9ihv2u8ghdqfjfn25nld9cto1fo90udb33enib4ccbasicurrnp2ksobekcadv029c5hmhe0odchgulkicun5c8f7t5h35qbf8", "r1uiqbcg74qgv3dub003em6cp7du2re72psfsk4bhl12ornl2ncftepel5rogkrbijv80sdm14qo84benrl7i1u9l48r0cnjl31rnr0"),
("cprcjp97keb3atbp5ue12sdivl6di6lcgb3oclr39o90t8qsv4ip4s58t5hhfhfk9gutv8cmp7gkhatn0p7rjlmnuqf3t3r9m2q58qg", "kc3f310diq6qp5agnoopefshqernbivf34isa7k0d28o6uiaj9h3lveod2bi9fo7j9efc1cikv93b4mt5rkt841q1rhddh38fm2eb2g"),
("cq5rh7rmsabr3l90bp04ec5u2mgqn53ro85scahvtvu0unbskgj3c84adq5c3sd7d3of4u7rhmlqfgj8j19offsrtpb5c43cd1go5q8", "keoli8tb577smc65a157uedqrq4l6kov169q99shn15gfbghgo3ht7vkdvbsbf2pu4jkbov1evs5d7vemr8ldocv582lidlunhtp8ao"),
("csntdmdefs254nfghmks16goqnvc8g6h293p7skvi3qeuvph67spnd7c3hqa10up7h5qs7jbdfktaoflpfh5gdiohmi6v8mq7k5t23g", "e1b8q8c8p7i3le9d8hnvecj0pa39pp4r1dhvhjptgtoelvcst2lutudf151591nli327q07vkva79cr1nbpr7u26bia5g9n8eno0c08"),
("dbccms8ebpvuved57apvuop3ejid5lhhjjojbh0l3big4an8kutsk8q2fptju1k1uq4b8qg2p7vr075nr42unffe31gqb1p3idbelc0", "j7rmkb9csti3v0924sdt912p2rutnmaln2f5a61757fcbu4v9m0vc7rhkvu0rh1e5n033b3737t236v5vov0ovcb3h3f1hfhpij0m9g"),
("djufse22a0p7qjuaethqjh69k0oogau7mvg9chv8e3lsje792s4e4uvdoo2nmqsagq61pabpp24lg5mpqpfq9762hv5v69ujigatb70", "kr40jbjq6n27l9s0egh1t1c8ruo1qiqdfgof2nrk96it8jtdt4hadv4tsg3ve31f4k2almgga83e1l4jsthqlt8qicubtffap9i968g"),
("dkeg2trsiss15us8qlqcb5hlfrfi2kg0hsqgnp7it9ctajq4pvg08u0utm69i8cp2t1gsanpnf95u6jghmh3s3cg1defsubqom3m0m8", "eu65vokntm1bvtma706aj1g82e0ct24ivqo8v2ehghk2kdp6h5thcjfrdipb5qo87s3qebnm0qnp9a2gj9gssmni6iubcas48l39ig8"),
("dvv41gnnuaskqbsn08iqno38id3i4al18q0ut59dajupova58sh5iv0kko1bs4h9t1us41slg9nlfu607e44dd1ig0qaja6pjq718b0", "uknirvj9tl9jgf54ch54sht66qfjtpo506tsfapepfjio0t6ta9hmvjg0br5dg6l5alc7ttmnnl8ffi9m7asabv0p74vv0s5af87rd0"),
("eunn44e14h0ntksvft7stfhoiscs4fuvs8mud5m0e3utl06re47p47nrl920b9at4svof5159jqjikak956qkjgcbpmbh1i7i8kokh0", "i6muddf8faoanpftog2uijtv4rab3pdqaehvkmunvh8ranes8p5g36beglj7na23rqh4c46gevvmuatcmdpd8dp5l42u3k034bhdda8"),
("0gcd6a6jkqm4soutdlh907vj5r1b0lkvda6vb00l9244akuj3g0qqtojecshjeoa4odp00gn5rc5i81aumefahjc4seijmrf236lv9o", "b9l25c9g3pggj2bvnlk79dr08tthc46degf55d9q0p096od7bs3g89r6enb966oikr0samagfai319o08suenvmsku2jc5452sdff9o"),
("gqcsh2a38l7edurtcb8pf7h5m03n584oguvj1jk1e437careac2jvpiblbrskqe2rbf369is7185anqm6ueruq28ah1q24c9p1jmtbo", "8kgo4gkfc9psgocfricug281faavd0kdjm3th1cc9mrkicip04kjpi7tgoeap1dear00l63raor0uilejf9dk3d7kn7hluas6h1lnj8"),
("i17ru9nbgurqrmilruj45kimnv6mu7nr4vf9pk0bqn18r174qftiq6ljr1c17tsorakl0odet25fk0rdbsk9cs6vfcbkenbs9uvr2fg", "4ulcd1nci9304qtrrrf24ctbqe76djbsnqoth72014g2fudmuqled0stgnk29aij5tuifj33dtj7hjfd9prpp8kh7du2apdmhlksllg"),
("lhvr87o1gv55ntaihk7slpeurtl39inh0jnpekbt9f907f2p8e08a2tk13m0ldnr9ih65hrs643959gh0m1gmb1lmjq756ms4tau2s0", "gg3f1gbpqb1jr63ubiae63focrktimnakf4u38vpk004ps7s9ami8ju8dllcm2bebsiv1evb3vvgeanrgv4h0c8kukjlcs2s6qlrgu8"),
("p1r5fnchfmuj2f6r77ehk4bmasts4at1o9p0j4sa9gebo1cd1pp8vjdt073975a561tds00f6bii1spgioca2ea72fccn56e0ul9uoo", "5lnvbp42ut2vl53ea1hae6tndir1fibb7lptvssictuhq8pmbl6c6ggc50nf8ei0n0e4md1k1h85c5b1phqma96qmimm31htcru9928"),
("1d0v1dffgdqmg13uj21o6718loj5126bt2c4m4rq42n5ei7atk2h93e2q3l4fled2vn9s32spqn8b7c8domb5s15g9b8c7f29o8hebo", "anjq7jpp1ec41rk9p5p2o1r89ev73vpgmaesbbrnm831djpkqp52nv6dj5uu7vlc1h5lds9qu195p041te04fjddclj5dnh4jiok7i8"),
("1dejs8bgrmndvtqd9lvuik7oppp2n3n1lhta8f64gv1d6ono55ipqqhrg7q8u9k003fe05fbm2tmf8759ugn069p14fksltsi7sga48", "dmgjut2ia253e8asos7snlc123bafq5h605o170b90kohh17mn55jge209rmi8q8fa915f99t50s84dopi4si54okut52vqudlrhtr8"),
("1mqe3jf9omkhusgm4sd443fm8odvuik484md3g9nnum5o3bdprl1fit7apdathrjige7goer71r3e538j867lahmm7g3g86sg0bdpo8", "gk2i9tpmt6i1bhjkdideipnb1p9jtsj82j382tnill4gg9180htl4hmrpm4eb5qineuumcbltam4iqolh5m2u54o937cn839rr7hf10"),
("1sc1q065sfdmugvarnsj3o75v9a0vqa1njilvii9pqps73vgb7temttoccrm4vgq07bh3o4tdsglua76j7n9svctjl69agfs1sohp3o", "l46su4nef4jngbpelk3r1b04qrnvnhmgn822k4mv65343s2dv8nl6m4s4bsbkd78vc39guig9kgbfi3au3j7t296lui709pjfbglrtg"),
("24kfkp0ljjgna46dta212jse3os9j6ku00617n4klemmc6rn3jk6n3ak16avdt2uubl5auait60vm1ql2vrlpas16n7r0ejuvos8vag", "rc8t7nkba3n842q0mv52mfuejb9c4fcck7dtg1bsj6p3rs11r6qh4dptefotm6v7q52no7qbt72e18cskt0oh5lm05rhv6m2pf28ij0"),
("2jbc89an99f36tnrg5vat3e1uhpsa0ielajflo2dcqqurjilk3hev00aa7gh890rr0f6btuvcddkpg3quks4btjchjpalnco5buhph8", "jges28gjkskmjluui5tkk2o168348rm2trfjp843s0obh00ig4vauqf3aglvps5ll3a1e1t9aluf3blp8iojf2g0ea1t96e5tp1aeeg"),
("2l8tfpk28bpl6qr2an4nm8q5o11fvl1l4skiu9vsm9p797h1h33jv5pa18a8bltd3dl4n007mutm5dfrk0fpl4oi16cgvdpc3onpd98", "31mmde0d6r25gpjljif1a3hsff8oaolgfpt302hepts42s43u45ppv2amr7m993uvff4l7i5ln8i28ip8mrl58mld4g2le3135dmq7g"),
("39voi8cnmvafn4h48615ff57r7qn6peo45k4kkedvsdunh83n9f7eekk6qhc7cot6e46d8nre42ssku318bj0d20fhf4o6i4ni0oh58", "7a7cipfu0hg2u9judj1kcjvv2usc4tpmblp4dgq35lmnvjrobdsdnjafr32s8g0jebphf9o69vqvqrmpke4unogb1dv1912gclei3f0"),
("3bvi7bjc6auf64v5ecoibtvdj35ssd9mt843tvm8p3n5dvucihtciu9a03havg5dg3sq4d7m4b6nou1vvrvkosvruq0d6nqmoa6l1i8", "q7r360kuu32te39ube1fjvh5qbed04p8iolf9oiqml9ejji1hkn1j1l9b3b6g71i9ug73ifj5f92eospqr9v36mo77vtbvvqsi48pvo"),
("3kp4vjlmbv0mh4hsptbjottvrlrtaus52fufvjv1o3e9gkarputqtvamc3pku574247vqq3sjlb7qj202e7ftr206u080m6ha32ghf0", "jqf58u94qqjcsso0e1qfvn3dlbgn0vpt943v5v27t9q2llaov9s5qtkavjfuckdt07vu8srjik79bmt2jpmhufi52uuom9bmao5ch18"),
("3rp7mihl0l0m6hddofjggr4goqng7jv3dq8uh7sbrduvnt4gbchg1p1gfug02qi1dq7o9rn9hpos0s580381os0605e7n4kl2ko314g", "kopnl7e4vd3efsicnr7qflqmld15nb0kqearjsjer12lnfkdu02ujb68lco405jlbntee1hum104gvnc3oo1b4k39ofcdf8v6s3770g"),
("41691c2ot5kgnpbrbqthjfkc1pdja8hls5ouujsojc8vfb9gqdtot5ocdl720r350pkfrkdnnh07on47ggade5rqtnmh95aah3h8o9o", "i23bk4fpivpom0jk1l5v5togc32ge54p97s78u1r1raank5cpdkocahnfge0p0rsl0vpgaek5e5tsonlj6j4th46gc5pksiiuskide8"),
("4nnhm70eu4u5eps52us5b151gimi85p21ro0tq6nvfu0v6i8ft0o5d0freiofh6biv7c54moq47pesaa9qot7ao00isaskosqdk4roo", "p90adcm8g7qgp8j8h3d21lsjgkf4diq9mt39lajjuq8a63dt9gfd5kjmntl27c05d9t8mi7kr20uopt42j60blfqf54irnqn2pq5ru0"),
("5kc4kicfsi3v3eghjhe5hsos33a70797cs8qmq0r57ueasrsls8mu39uck0bicil3ib1qcd4i2udtlksoatr6bl940p04b7kttjj3ro", "rbjag2oapa1ok6rjq1i7pt424nlejean9hqu3h5mk6pvindh8sb9ri8f1jqcude1ggnnrkq2emhu45ic983dqkh5ibjhqfdrsd39uvg"),
("5p2kpi0gsn1foqhggq5ap874kcpj2jhpogvcn8hb44grbqf0p6imueojhkln2aspsbckf07gfd0bsp8q7lp1sne0lj1uckl16iuosao", "c3vf9cqbb165ai5dgscbcai9tkrpj3im1biv81st652kvbbimc7j0n5ni3dhor31ic46rqm1op0kkddb52elf69uqcv4h2evocdomgg"),
("5tgdlqhefmrv4vi9mqa6pqtqajmk3dpl0gsit1rv6fli0pfi63jo3tbebbl87f5tavcistv9n07urpld00ss0u1b2u2e1qvik9rfsn0", "cdc9mfct4tfahv0k0fg9b4i47ra26hegolmfjvcb7qmlogelqc7tsv6400me4idpj29362c5e2fgsd5up5ni8ptcn320vslcb7r46q0"),
("64f4nfplcp4dkntuteuvrnlrh15f7tmrpa9ei0o8fefaqng6agsq5a7jnv276lvut307jl4kirs8mqcb3agccro6sdftfv91ifuads0", "tpps1f9ssvrhooapkuevgcd7obcfsaijgtdod7jinrp5dvp2m2i37pospuirjv48nhn2ndvghs4r76vr79i9gcuka0i5kbbujsv29n8"),
("6dr3op5agul6kops005e18drjhtro7ts0bcjdc9gcmathnij23d88mhcrduuoe5kolk55khdvjpn2nvpvlkm6aqsdirdsppr9fokud8", "vibpu8mb5hivekju546gbp8lj5642rj3k2n90v1up8ehd7ta277nnbgujfl14k3ldsgrhikilg3dht5s64ekuvl00cj13p4ptnf81go"),
("748ekftnqapn7r71ljpm4r8prn6hlas0niq3q3i57h4gi1v2bhv341ljkciniv0dc984lrkh0vhmdnesrqk8o8gh309h5sm29jvb6kg", "b1l448psh74fid29ci41monj7huk3amdorfkl5bfj7ngah950ovi0bqc2hdkek7mtsfa4gscg90d5ljmvgr5539c5vlo5smh86d06qg"),
("83906tuspe76kipk6kgbfp1ejgf7s4j6hvg3snonmhom94l5jv406g4lualc3rfqnfp12rqnr3r0e6d2ajdf4k2vb42vvht0id1c908", "e773cuqfr6ebdren27olt6oqenrb144p4cg6a29580tmce8iiouc4dip7eueej5qubesqbtu9dfgq824e712dp9ql7j4pegc6p2eq2g"),
("8rhn8grcdbhrov0da959g8e4m7ue4vufet5c6k6t526lhq2b7g7b89rpisj7av8gl8e7vt8qkpev86ipe4k76vvmf2if7evl29q4b18", "2jd77kkn1nv14fjpu9j0lqcp8d8a27pvvhp8gheg1sqrkgl4pn0haic0ld5tg4eljgttolednqjdr79bk4m6p19g3532r2nksrgj7t0"),
("a056049l4gpqphi6tqusgui66ccleh2fivuhf58g4qavoedpk7lp5ssa8cs2gmdo49tveuif7ivmharr4o66vjlvj75lnnjjulg36d0", "d0aava23hmoj62h5b61722ugk3a8i0heuhhkeime97i48ldgquenm718f80kgc9137ngd35s6li9n1a974v46dop8gd8slsafh87t88"),
("a9jot0bkuq5d7rt0fa7hvd7d5ilfd7cheqscc5s4cn569diirkb933hl381fa495d39nlp8odspj4u4eb0qgbcl9pa2u4honkp9t840", "k71lvt49qq6opa9np4grpnil8pomjrno8q5i9p43h10vvgjv6okec3oqotq2958afv6k17udj3h1jsdmqh8tfrtms95mb4eeu36csl0"),
("alq45lfgg3ldnpcae0tecvcp2lnrhfse7o39311mchlld7mttqsap52cna1sd8hg5ahlqmhqegvc9a07e847oo760vc0n1qs00s04v0", "2779bchdmpcj6626hp27olunip1lvkda3v7dqsb88opbh0vgmibn6e54opsu6jsctk3a49jatu9lf6kggr3un2a7gd9uopq801ts2lo"),
("arb7haeh021msd03lrsm300tkftggmgdd4gv7to7iua2ftl2ino2f29elbmitsnkqr785r3drmvte2l59bb2cuoc5olt6op27nbudk0", "lrnhqtkkg6nbuv749dd7am8qaapn06p95lvqt3en29li3cps94ldv8elmuk50meecplvm3ojirtbj0d3j71j1hdatv6nunkm85cusqg"),
("bcaalsrvhs8b203v82p824bq5ae0ple01mkhgjbv3utn1qoic6dpag8b5qfc2jeou600v7u1psgenha018d1oj4tppk5q0gi1ssocn0", "omf85hee48sottmvr2f6rc5ip7eld4gse6n7isu5bscu8cucfd3r7e97pej95er52gpi254ing71e7n68herjophhtp3k7mk5fniq30"),
("bt5l8e2lln0i700npr6eok7h68lmvph5vk39joo12vmhsigj73nftvgbsegva7oim59i4dn8mbv9tbl12jgb2qm52u6c4s7j31nti58", "fb4j37ur8msqj8egvlrhou16fu4fhtmd8ud0qqpeo6u65d1t1d5h4utrflranig1d191lcrbunbkc531v3lb02svm9p4g0ge3c3kkl8"),
("btpmcih6qbvmqtk64ji06fmcoea608r6nvcgfk4m49oj9jd00j0ni3i0ek4dtcdq8962fd0tq1i4kg36pn6e7veltqjgvl2j2vsvno8", "k7siegjcjj1l5g5lvli5m30qth0j1ltce3969to38mju7boti0o9makaho342hql88sngfbqcadk9rcmrli916u937uk6et4ij47u70"),
("c64aliaa5i3l52jeaqq55dg60jio6k7ot0n668mou3153te1t2h4in6l4p8uj228lhlmr8tik2a8rcjcfm35ehlsqte39frv67mmsco", "dl8tbhj9o1opm8jq7hfhoj8a24gqkaa21rng78bdejpnahbq9pjqdmqb9gmtlnsmdsg9bqta6rllr7b39er2cn6ninms1tjgj69n63o"),
("912ukcib346qpv8b5cugn4v37kl546rpgp8sjk4rio0qmim6tsiucm987qa2u02bkgeki2ll7kjj785i91kp40f345nbdbmkp8p5o4o", "63csvqr59quqrcii9m6pivd4us2p95nvlqqgfvr9eo5vsdjh4cu6mjdjhqh975f5cl2jhj4vffcok1daee9iks3j9p2v6o9u38vdnjo"),
("k2mqq3b0lpoudqleaad9kkg7qr0gjtekev6c6mbuilndibtksu1pb7cg85u9ch5d76ovejsq683i8l8ce1n5vv8aakkl3umvp0rb4a8", "01795et8mueeqp8l96i4n8imtm8oqle16td2abvqegqc3j0v7u8oqett6e50i474vl4esddsc8mqcifpddfc1dcpjibtcgld3nhrffg"),
("194n7on91hmoafovmlkq83vcq3lcuohrmmtar2bip76misam9i6rhse9f6ijnotmj5t9ce0qstkbi9sq8g12sgqge1efb4h870i2vdo", "03qnlf7gei9pjgia94bghuhd27pn9jca00dn6qujtmaes5bj8add491l25joe26hfaatjdrk4chocl9vso0uondbv7d7cl1dbji3ke8"),
("ulbuequ0irre818c9hujrq6rd65cih74ie9v1p6m70h8egl7uaalj1mqshjoo435qijmrnh89g7m72o6dat0lhrunm1fbnfh4dv0lug", "06e54ggbcmkc4f2n21leomdm6q0h5qkq650b11ou5n8jq7um60s1k4hce5fei9t3m6ikrtckg15dbk87r1dqgrlbmvo68g861v9a20o"),
("o369aaf0at417k2s52o1p8qh35bt5l6fiai6u329gssjambn4akoserfa2a7qi0vs8t1p9ckuha2nbl8nfnasttn9i8rt8p0a2j36pg", "0d1b539fcpj9e07brv9al5c5qjqsl580haggil7p76cf3ea234mp6tccvq0jouj0u1u7riktsjb6k12dsu424c01bokl60som761i2g"),
("h0sohgmnootjl5kg0cbth9ojr0hsafqng76mebhkigtpsr4pk477o9g59g2de7al09d98rldsuf0ukv10ku3q1gq72tg77l3qrlk39o", "0fap27479vb5jqo8ndmn79b1007s5jo5e6d51r3bqv6q4em4isfpme62ojstrbc44k1agcmlgnp9fu4rqc2m9f0bndr99hek9noud9g"),
("meo2q4qpk5gksfgvfe2pmjteg3h0bnorqaiiedkm1i30rlvi0eanjkhsffi9ecajtushab0p7ee8s0nug7po7msrig05c00kgtm7h1o", "0fdsboocpbcenotqbeidkqofuv4u5i18l92cbd9tt4q0k4ot8dg1ov2dvqvb3ibsnnrpkemhl31u02f100dck6ilgkkl3s2voidm9a8"),
("h2kqofk7elvm0huqsbokhslv6g8futraap7qb36pe239o9lkdmb3u4h1ed8c6oph219t1e2djnedn0bqfm9m1m4t8po4gnea2a30b8g", "0fdsboocpbcenotqbeidkqofuv4u5i18l92cbd9tt4q0k4ot8dg1ov2dvqvb3ibsnnrpkemhl31u02f100dck6ilgkkl3s2voidm9a8"),
("i3qru6q4i81tgdr68400sfv64dskk3n356vt5ognv76b9scimcv70qosjuucde1rrtdue5ab2r26kdftna819e429sn6a64e0haj0a8", "0ngjp6m2qb9c2a7bsrac90231p7fl2rneshabnih52us7rhn5mc2r1p1jgm3hdm99gq3ggjloi425b70eq32llbj6torhmfkc3b7d3g"),
("a2ter3pknp5hoh230e07fp44fhsqvis8dugt7ff9j3tqtvimr2nt1b1oi63dcn3bj90oi4c04dp2iulv3hqlbj8fh03d6irvojeos3g", "0nkjuo7c0l5dgsad0tpkh2jp91cnt1svmp5s3l6gqoe85bjo2vhp6q4fg57eurpkv7jcb7atcek1vl8pgcdl3semkfid3c4520brueo"),
("3kdh01gckoujqja0rflj5e9346ijsp3gcomi16n6r9919p33382oe7gerh2apk6590smjkg34dqim09mefoh8uniibrcu6lrc8v09ug", "0nqng9eh3hppfrg3k837qvuu636k2jfa2s76nj8ao1l62qoglh8ftv7d9l8f2c70tssrumre8kp6brgj9kepaugrhf4rl7vdjoe4m20"),
("ikr17h9av978atvsuh9iqrih3gniudi7344kct7ltv0e49alcs3lajel6p58f9i32qq2h5rcmm61govn16pephjst7p55fktrfrcsb0", "0o5t8h2jsekjr5iq17rsq3aiqpdbtul1l936kj07rtahamqm41eah77h1ojlvd1gbp93n3nl6qlrcbojqot3atpq66v7qil931u0qr0"),
("02dkoqlap8k8g19990t2ttr1p30jfl0kqi65e1lmaq3qic406d8t2l9o2equ20e45kh4v1792oidtio5f940hka0hpk2eajosli9k18", "121urdhevdnisjsckhgsb9opgk5qtqosm4s0fl5hc8rj4ks677oprdi361o0gscp1cllhome8dcu2vh9auuk4p788linmnt1nhvd4qo"),
("msb9bc7jrahn5n1cdpg3kkr2otocv6v19lgfdc2romnpenu195vuncpl3mu2mk4ij7jeb5mj4i9tke169cbgt1rvmmbrvttvpr5kieg", "126val3c9tp44cbvn0uspnpnn60kqkcfjbofl9bbkd2o429keqndfeep62gnapout6823s0ictdpe6hh0deinadtb6v1368tk1ovjn0"),
("6ck2tmgu9mekjfhqlsajosng5skmkmeno308arpbqu4dih8uo56ajkj90mug31dnk6i2v9pppk9lira0b4eg5ptopg1mv5ikmohp2r0", "13ttbm3vgfga9f0k08vhqv87nvitkl52gvqss17ldet8oc8qf17q4fhgh32drqhs30rs9hnpmn2s8lotfets418ttk43tb2qk30m9io"),
("5v05r1kqp7p7p69477e6g6is04c7bkljp1ca5lurqit8ii72u2ptf7a7bakptremucf32h3s0o7fvt45th1g6np5lqhqs8j6nsresbo", "18huli46ulo0bai3q4cn4b93o5f0fa8pt0lteudgkj7uoo18jhknhapbso3sffmme8ntthuomo6l89tnc7493gqughcap8lus4h2500"),
("uu1c87ciugc99dh2cuikn678ta2h5fnqfgeo0ib7tcf6feqffpcr4ba6mlevobg5m49d25lqpbgc5ind6o0hgd6u3qjo400dad2t0cg", "1bfdpb773lv1rof8e1utj32g1utl25958fv8i7r4g719k84pq5p1emgf9s8a75ahl8q399j9g5gjp7mkkv1hf4t9mhk96nnk4tj5doo"),
("k2mv220b28stuktljr62eq0tn7hv5rap2g7tdkrumhjjebt6d1jjdn5t2eo83dascufdlc1gnhitmqf2l2jj55qtm5evoue4vmksgjo", "1boeoej4ui7li3nguifqr4afb8l7u0s7n5sitcidtf6oinjltm1o0t3rnf8vfh6csenmh3gctb6nbf4gq31p89pngr0ummb9umisrno"),
("2pse0jamijm0jk91vfq90ggc5olnab2n4nqmct18flkbj3sioonghn4pchc95knub4m4o7qrjofomc2bflf4pf2o7dlbh3i3044r4r0", "1ekp7066uokir456gpt1nqdv9kihcqrqlq0oq72d2sdv27v7aku9joh90rsmlgbp90mf85o8drdjmlp9otb3r6e0qna8kbfbnu75ft8"),
("jg4brj6um9ienp4dcme38omssr83a82jmm949pr5qea6r90qgccvgfbchcclqskk7fbq7s9gk7cef1kih34u18lh2rsqc4mnjf04tb8", "1g3cscno561j8jjf1l57i2hmigorbdt8i33ge7tde88a61m3roq5v0q7uala87dua0rn07139gkb6au5cnprugqp5jl1299t0hk3t8g"),
("1j5s6tomsgaqot0v3atj498jkkg293ugc554u8ert8bvrlvp9sqjbovjqjsieljbvcm35ft2qv6vo8hpiknqstprgscko156dhjteq0", "1hts8e49tpho8jc9f5o9dr43ct6pjq94c07hdi0nv4tp6of8vikme733rl2dk0li9ild338q0bh18m366kvd33ops4psnp4a0n6euco"),
("q7dmi14sgenlm0ogvmfb389jh5d0vdbkl33momrvocinho1pbiuckrjja8rnel2stbkqei5t6op4ftu8d4fe1hbuobn61ij1koicqvo", "1to15kbo46l68jq7vcb0rqijvfjggm3k5knr6vchsaiujqd22a1cgbt75mv4ua00sjtqdlljs510242c7shvi8vqo0b51foujqbjoq0"),
("u05cmh543v6593hdqs1ei61s12ndfo5p16e03ehjp3pvvlqo8da8o04tod7k0uln0v7bc4tu9g58a2395vlfk2027ak7fbtrakk5nn8", "1vju7i3u9vruoc6urm9eph2sslul47fh68q77rrddovqq6cvfhggn92co4eshf781k2skkem1sm8fb7ksm5fnss9slsvlnfee47e4oo"),
("trvn6psgol3qlfnfg63qf5ps9h3fq7mgs3tgj47f5tkhfbfvvccka2dalm434d0t9aob8fbqe3h6avp2bgdohqvg9vkh5u6aen4qjao", "25cf974o9l71cu0nu3efi2gdviqm9b5b08st3i7cj5fac8ui1rrr4vk4bh23st4ssvsljvhait5l1cmfh93kn06i2k4m5b2gi3pe9mg"),
("3klftek74k8alu5ncl63771imrpsks7vka6ifldq6skaadrgbcdet70bsqrbqlboo00el7r8p6t7785dod978kgfu85m71o37ob6f5g", "25il2hdbb0pud847ep3fq6907nee3utikm58utq2usuao6q3m43p6cd4puv7jn6useb8bt1a1fuunfuqd3a76prf943jqos7feiara0"),
("2oouj8u8bd77fo2is4bsb5rlpbb42o806qsvr2f4uduq2b9tur34qiu3hv0n3oklchgdn37ev61cq3kv3rmvh1q00m8q0kpusksj2ko", "26mq3cbq3rj5vn7pjq71l8cr7l389n81ns5q26c4142huv62jhlrp8qkip0u6a0ek2mcglht7tlbe1g39et5djl76f1kl72sgcvrqm8"),
("8l0vho5jma82lfrmqi7o6sjnquhflb58gepnt6ai30g48ntoa0gj26pc4gu3ppfthu3q8a74p9b3ebrf6b5091r9n317eg1bslb4gpg", "26t3s8mvtr74mc4blhq0tfcgqb5e9hp6cvflh8gvuh2olgnku1ida5ddt56h2qgck7fu3tpb30n2eed5u2sdf1ce3mijaptojntrudo"),
("eqahcfr9kvifrgb2htt98sal852c0kdd131hmg225cmnreo4pcafrukak7d1dhhbs7rioer6jkl0kkarenhie7p0d76020c9v141bm8", "26upkog73615rh0gt7u6rurb4ip5lsm5cuo3t0thqkfdq88htpt4kn15h4h97trvv5ritbm5902lrr3uin7hrodkn7emle6h5gv825o"),
("g9jeeb0qecp60l9t3bqtjgi249sphacbam461pt8h8u0ha2o7tn4vsml56t8oitvi9k28njltib50f96kh0mid2v09qob1smutc6hv8", "29gr5c3lc3hgaa0qo0k4m3pp5j0b1rqlc87aha3jvfiddhdeo01td8kd2t4uqqg44435obehm0g14brd7oeq53jvp1heb4meinbuem8"),
("9n4tev6pmn6bk7f9i4kga1tc6rdl4cir8u31ldrmkbjfi77pb2hao4qc0oldtnmh36sg0g7qfp4ki6ono5t6srfdnk4j3qh2hvk1ug0", "2jrgfjipijvp1552phjh0rvvnus2m7bl03a9sg1phupbiesc58tqo04d9lhil2vk1rim46ddqdgcksb9o61u8gpmvoe0srenge9hj78"),
("ggvp21a35k83s49qs2bdt981c45am96gnpaca0d0ac5ah1e5cn4cr1nqoans381g3n9qu2q10tgkglr5jntmm80e8qk6rn6cmaesfho", "2n239cunfb688ptt398911meaium8bl2e75s923dt81n2j7p77hrelot56b2emp2m6hcuohdd8u5lic4muunqld7ho29mqgcq8vo7pg"),
("72bb8lglg9mmkkudbm8d3nooiafc16ae0dfcs2qhs7a78baon6easb7lp3vt5eirmapsuodf55vbpt22j2q048dj5fud8uv6cabcij0", "2oqrh1kjk0vlq8ncfmnd71ru4ncm7hvkdtoakpmfm1tjqnq3nnb94h803tk0uej51crsdohira8mpvsc3nmaq4if2d3bkpukq2bhip8"),
("rahvpefju8tkt4c0o3ierkp5glr8583fm3ponfnaa9a899rhrrup5oh94jibm7ok1t2v63cid295pq9brnm9ag9rfhu2j2rfo4knmi0", "2p1mjv6jm7ber70u2i2t7jleuv2t3r80i84vdus5slrn71nlhgj78bljvs42bivgcekn94umqbpcv766tovm65evcsv40jrjqf0ksq0"),
("ekpl4o0i21ji1oo2utqdflmpa2f1s3na605n0p1dgke9lct6h7h5e2k2uhqtsi6mq3t98p73mlivi73ao27of7lmvph3mdda9t78sbg", "2p1mjv6jm7ber70u2i2t7jleuv2t3r80i84vdus5slrn71nlhgj78bljvs42bivgcekn94umqbpcv766tovm65evcsv40jrjqf0ksq0"),
("eivqnp5t5lsm4f1knliqlrgm5pad9vr2vvn1luko9vl964qnnds4hd7o2klb22fm2nmsutm306o1s1582r6n5n6ggo2utkq3hnrnmdg", "2pjkc5au4tl88j5m8fho52tmimdmff1gbbn5ocvm39a43cessohsuosou25ujoo4mj8ng52ss45hnmm2sdaapaflepuifugl88i7tt0"),
("3rit16j4u43o0gmb54rdmjq0civ0d12nveki4r8vmq8hki12t0tgubskgq1flaftqjc4ml19rfjn1acdb6vq4j0uhag1ojud10ucgeg", "2pn21pec5ncmqnpsk9c6j71cc33nraq66n1q4l9ditfs4jf1sgve8rfacam3no47opb7911o2td4q1vfcrt8bnae2a3f8na2th15070"),
("ipmhapa091v68nhj2mj8ng4o8cc3imh68b80lkvtk5g80fihr5jmq7i11059f9rkjal4ad2qnhmf0gol1vqcnu1v1j2m7flno67kodg", "2qs0iinvh1hthfffocslhpb73p4nhbnj283tbsj1i758p436bfo1nbv3qrlcvmprglar4esblbtqinms8ntis9a8b293sv1rn22lup0"),
("jm1104tgp5hsgvv2k6o8iid9uv7nje6aqq8nme1hdc7hnb6r7m1q87ridv3pe6t61r2vabd1bsng32v4jr3vtn5r582f7l0acdtf7ug", "2sa9nofd3u19j6qca4amo9eovbocurr1hu2ms2p300jvm4m78mr1p7n39u5d0j1h687gnldra3uvrh4gsvmc4hegbosio19a1004mr8"),
("sbv4itejos2c4llpcfj3rpa0unl7hf7i93tjn379n21cpo7vme8g990ojcp8hm2fmsf703ah468v71cgcq0bgccd4s13l5lu4s5bhto", "30eh38hbbet06eb7tkl9991glo5lrahb2vrnbkp8425ddgpo3hb0f7o13h04e8k8638qo17i1jmeiumifp9fd0ikt7khq50opc9sfi8"),
("ntuv09i4g96kg6dv1q600g6j4jl5q61edrlbl49nbuec0vqu6187j00icpnqv7asb57di7vu224qlis2vr3s3jpldgg4eiuugf15suo", "30kg7rtbqupahi6bruv7hn0h01n3p2ddtja8nnpoej07him1r1c5su6ndbpf1257suk0htcf7ioqedkuphdd3ok4rgc1v4n8ibf1ni0"),
("n7eetribjrctm7kc78c0uh0pkdfjvnabsl80tjhbnudqp3oj57fvptk20fmhtfp79br7krarc18aj50k4a8j6so4gp7mc39o61ec0a0", "36kl3d5fv8uieb022ho9gsavag2i9f3ousu6pmsspgkab94ttpn0oehsaekt6vsf224jchilsopntqsdja3kegifh388s6sn777q278"),
("mihfbc82p5jqba41k5k70q975orc1f9te55c0g0r8alqv442ah3502jftn3svjaqk6mv4vueo0keuj5godhqkt76knmble71v81fqno", "36o617j7io7r7gfc5f0asjf2ii9fpek1l3p89n3jpjd0b8462p55bha9tkabc8l7sq11h4sl4cn9lcbf9ouqpdj8kvsjmanqutbc3h8"),
("8oatjteifebbluo4sb571h6mh3svva3ao4nnboiarcsbgfcn0jc860tiucbb08gl636p69285ujmpel90qik3kgj8ajh1hjdkhochj8", "37sqd9kq92q83rg1qeik5eq1fps9e4q36fn033t3312jmg0jiemc7b714q7hnn2dkh7ubi27b0ik2f243eq0uqc5gia6b614jn81t0o"),
("2abhqosrutbf5tdbd23k9m7qeelgcmmb7vseebfru66nhg27c3c9urcv2lr8sfd3iift7d97fpiisko8v6u0u8vab3oj32ma20amoa0", "38tj1jgk62d5qap98gkc862ujl681d1tn9ps4h3d3e6np0dj1mq61gl6jl07i3vu8vfma1kob863ia09rpjghl5mvqf5lke585punf0"),
("c40ehdt3k9ei49qbn0i3v3jc12blp8a50qsqjppso0j5uh78hu2tqej5lal6cr7ce6mq1fr0ikmhvbms3b2vehnu2tv42jg8m8behfg", "39pmv9t5k085iied4nsp4ldfo9moc95jms7cvh8577roa0u6sghobif4e8modmsnu439lt1nftsphapj33d65gp9eun76cnq5b63rbo"),
("5tpmv7htqsagapk59dqgtsv2rkh4h48qu09tiaqnguqqsbrrce08ues9i5cval4tgvk5lu31bdrr923hgtncrvte26vg3e3ps5dhreo", "3dt7sgi70qv4fqt9gg2k58kofeof5jr85kvtga6813omj3qo45gmgnmt1glfiss31ufdet2l0uu38mth45fljgtmsgiug6qik029rv0"),
("gll8aovd1bf977hqer7ej5ectjkn0kj9d73csnlcqg05rpi3skoo1j5e58orarlv9fmlaiintp30sdt882m47u1eb7vbn2qt4gjq4l0", "3eh0f9kq2fnkhq1t8ld3226sa1iqvv6ibtadgv3abbs8m94h2rkdc3vss1lkn8898ibnj9dtulss0b38i1tg9v6c7vd4r1vts8pcv6o"),
("201uo29c20crkq9cdl0e79q39idgsoscpacmffje27s95e2i72j68neincbk7bntfd8mgvoanfc0lgth95fga0achkbu09jk1g8p3c8", "3eh0f9kq2fnkhq1t8ld3226sa1iqvv6ibtadgv3abbs8m94h2rkdc3vss1lkn8898ibnj9dtulss0b38i1tg9v6c7vd4r1vts8pcv6o"),
("gp8umgugq27e7c4m7ueqttr1dkp5st1fq4r0j6qj6e8esl5poojanr92udtusrkb98pgbqltpil25ht3amh2jq5u2j8um0voskgvr60", "3fbjd043v9jobbufdtde2s2ihokj8lfm3acd12k9nv44sil16j1m1hbji0i90dih6c81ef788ur1me4f5rnnsbjs324n3ncom3f2mn8"),
("j8ncvs8q6nn9vdmjuhhhffha69jth75astb404fn2g37tr9p8kfoklvei47uqaib1804uo8jhs5018hv55uov3hnr9fbs4u7e1cti2g", "3fddtoiquq9136djff7003d7v77r5ld9uguko5gp8ru5q4v59q9lga2jhhditalg1kj6eb1oviqe1p7v28iv78e926ocnilq44hmluo"),
("e1c07c3fnr6r0p9v6uf9r1h9d2dkpk7455haa5pk0dgcsm5kqkfigud7c89p2o4dmdsl70kfjdg8vrf46h7jio7f62iiud3p14fdm0g", "3injtqp7qbpgu8m7s9vgv2sb56a41o1edp70gkr0ht7nsimv1ofb11oirjq592t2raumf6lcmpj25gnvnq6jnui5f8dcm8802n81ncg"),
("1bm1s6ruimq4rffbvmrv6a28mfo1di4s4amb2i07kmcito4on1sqesaqnberbe35ftec5q7atq9710db12bfovuj8kh11n5vuu6dds8", "3jcq42s8uq4ndb1i58pfsu44kdin8cn8nlc35a0nf1mei2enr9heffjacfbcb4m51msfl8o27mka6f9hlr26id0cqkknraghbp13bu8"),
("6130shl68e1im8b1paf1adcqn1utpsi9df77qcfuiaflvvk705s88lnaq2s3f9vpbhp41q7psd4paeai2pjoqm7ni4eq037sf32qdkg", "3jtpeuk1fj7frbfq6tvd2hnn8mctf8otlvqpkmei5qbk3uid1pmjccgc1547n8b3dos5lbv8fm24vbtv4aofnp4j0tg10m4acbv92hg"),
("j9v1vp8b2oha5ujeugbk1bttjv2qhafbjdng37akal5nrtecvq7fsbob8ttb3iqbahrm3u3oa8g64cu1sa299sk4qdbiu4hgivsu8fo", "3lmukrmur1g34ihtlp8641vgu4tapg80ep2giq1fmahdiqg5dep50hssf9umvpn0jt936sbp5holp2k4k3r767ji8h4bmc6nff6rab0"),
("add45psr08kjs0e6tk135r6ms6q7sssrcd0n8b50kmppkn7f89vkvmveovkgtrujq3harfgc52pdguktkjrvuv6612iapbqjokhg71g", "3m3nfchsl5a9313hk6dr7thmgdqtekf4s6edvdibo31dtqkpbkgc2jg2o8c22jd7hb74egj55ih2675ivl837700nl0uslhpfrgt7f8"),
("qsfj44hj9vuj4ub7vtu7212mv9jug2fe09t7k1rrpvhrovlkq1smlns882obtfvpndtt1eosiahpbkmebj8e1esb7t0mogtleo4ahqo", "3peek2oa8p2p5jo27ij1ldb2ao4gkiel5b5es2fed4tbv0eae032tb4pm2r8h79d0487u6ne61lsi7u3affmn6lsuff81clpq8hbh40"),
("o8klh8u4uan2909i0nh607tjksj50h4ir9tpiuekr40is0pirokts7ne8h7lit8feh7s796ibnjs5kecrok70hsv9k6rhujhusg01uo", "3q55j5u5vv85e8gf8hjf1ts6cp4fn8dnbhp75db0cne207as4pf7jdhekifpls3p1r5j6o5pnhh2553tje6uu0cgr8p0cth0nm070q0"),
("sfobl2grqopr4h41to00o0b891246utqk7t9r9kfrj8mp50fulvi6sshskqac73l965d89ticudcv2rc6lb2galloer6p9qhtjcm318", "3qv5lej3rh2k9mml9fluusoi12b7hq68bljduorhpkcl9sqnmv2oub5ogfhla981lj2ras9ge0f1efrv24c2p1582t8g8j247inamgg"),
("81gve66qr3egjl6dk62l9g4oeqkd9ufrkjj6r97mqjtqhu2jpphsik5kgef7ap57adbmlbq1rpaq689a1c8c3ju7j8dgov8h9fkoi4o", "3t6m3a66ggeagk6cimta6t3m0kl1p3lqil4fekdse7pp9mn7tl5o2po495bj6qfn28p2s05tvpf1742qcvepuo31ml9r4gm6q7ncdvo"),
("8ch91dvsq53eb0o8htm48k6g9tj4p79mh8avfh5fukecak477n16b3nme4vgeou29236t0g81b3te963pmfnkm5j2nhttkp3tid1130", "3tdqs6v9q3k0ks594cjnq7h3tfm6rp770vh27sgih0npgmj0q75u3bgrdismknq36rvaa1k9cabg8kq6ld52en2lv7559esebd11s4g"),
("3tf6naam3lbv2t49r2jtn66og0k1aajviodqcft4do8m5q3s56o36cn2vgln1ikgjs3kpcp49j6dmupp6c8oa583kc15lgvvab8seco", "3ted41dep7md33p8u8bjaqmphjg07bn7ard2p7crhftmjautd88hadmpng19j6vkap8k5kqj2bsg204u8f6uehdsf9i2vvf36ulpkdo"),
("hklo5u1e1pgf34upo08a42fbsg7m9ipov18uh1venag5uftkr0d96bcg02nsgmsn9qe2hi4j02kk14p2p9nosegt2qbj4mr911b9ek8", "3vajd06ors9rk9kuf2arnf9m0vjfofldk1vn4piq855rshda94rr8fn63pm7a6hk2t5anfogdgqq793o12iqhb6jcqqmj68sic2cf80"),
("5quqf64vove2mttqkkmeuthr8f6v31lbuql0f81cf71tcft86thfoqr3sthn3j8gaduekbbvkfhu0are7j9pkqv60qgiie9f9nck3tg", "3vjpu857hnc965l9necdf3inghnk6qr7cq6qjfe95lvon4ranqrciob2mloa1od5ihiin1vk8pfttmsuraji8rjljtde79qs5aji660"),
("tbh0aou5422vvr1nosmv0475uhnbcacqjqikqrd26jrtppeb441llj4bb5bbjpv38vv353r41o78qrpdk0hghtqgpl5rol8ju7op9o8", "425nh036tl467jc3fkoansdblklfb6q0s3jsfi04f13jkln58jlbuqnoqu19hpi7hsvq8otl2ofngm400grk9nelafro7q8i0jc93f8"),
("q402mpqaqpbtlnjlul6icm5rm786beb5u7k1k383ka75m84s43q12dc50llfjgvq4us4ca1i62lp5vlq3bdhcg48mvnfbrr17m66h2g", "42h1lj6ukee9bgt8p2glrur459i28160p8p5j3tvmf4129nikam7vd73gdv7q5pm476sc5e25hj5rn76l6qjrgdt6dltns0lct35rn0"),
("rdbj8fmlmtv79gkctfjotlfbde90kskona4pc4e5fvbckkcca0pc5i1no0b4te5sebugns9j43qi9jc96254o5eej9ph40oq8ms8270", "4521o0a4jnjm91bbt7ij4536vi4027gplpbpk6son5gipmd4b6eskvq954qb8r97gk21oh7qvk336eptqfso3j1gv53dg3p7225jif8"),
("tngl47et4mh4tc9i7bvjrdfh3cto27596681pri6fga6d36nr0k7hrk61qpi049svqh0kd6ef2brda3hu6o2lslo2mbh1n5aq7b7cjg", "45gtsmpl1kqic6n3182dui7012vp4mti5me6lm2o7h01kakb9739e9knetqutgoubogm58h39faaodfd13vdqh04t5t225k41nuuvko"),
("9tuf8ra1i4b144mjtft6eqnuhschacigqfn7v4eai79i4uos61k4tm1t0ljuk99lv5bmq1sl8lkmgnop68o4n44aridq63vs3jn66fo", "46k5epa8ocgme4i2f6l5iv25gfsk4mciqc00fj5f6mofvcnhd86b5lnlvgc26j0r8hhse3d8f80gqnsenlpofukb9npan4hmcquo67o"),
("962shuch4aldkf599uhltns6ucmlhuq6as7bltgmqbqa7kl1k1c69gorgpv16i9amubij8repsbp6nql7admaql91j637k5lbfed540", "46k5epa8ocgme4i2f6l5iv25gfsk4mciqc00fj5f6mofvcnhd86b5lnlvgc26j0r8hhse3d8f80gqnsenlpofukb9npan4hmcquo67o"),
("2hjr3sgjpp3b3mjcj57rlflquchbsc4rnejc7nke9usa867aonh8qsp13aaj1m5ercpe1h9ptc8krk1l7i6667fgibrrqv4elfm3f18", "4arvsugh71l27etjie1iihcftfequ93qb8peed2t1b46m9rcfaa2fob1greabrcjcq2bbm68ksqejlo1sm0nvoks36stje5bgrj62u8"),
("n7qu3i1emf3q0h9l2d8n8opkf3nqaq4qldm62r045344b180rmd92q0485bptvdrjan0kdtutl848uvlppbrqdjpccq4ar1bap7e1r0", "4ivpm47s3b2m12a5h8h9jf7p0016gtesfso50685to2g2rs1l605tmuvqbqfft544bfb9ru65jrv14sr848gu2bg5as1c6dksr2ohc0"),
("286d6j5i6hebtotr6pgefvas70ocj6bpt55ni6l1ia48fm3mu5ch3hqe465jrk66e4slbbdc5fd67cpvkghiclbms1l2u65v8dboncg", "4kagoo6g6e0mkk8t6sjo8jnlpnmv24lrga0rn0718fncgh43du8f0g1fdhomsnb3d8ci7498omhqhv92b5jk01qv8sqbb9nt6rh929o"),
("jgk0gal6q068v7grlclk6gu6gf3rltk0eru3fd8bee9cfhjcmuci2kigfl6ul3v5ep6abd09kbl0bm87mcdna1h7jmbuin3f5541b50", "4kf198tl2961sgmu52463rjmtd0jlvb0idc1vg3v0at6aatr1q36ah2ois5blh0ltueojqqpg57bji8dtrsumfgo6mafb3hodmhqpj0"),
("le5hen66qr4j1srid76faefbftsvhfhshlqmh1bi2qq743n6sg8h7ohvj10pqt8p0si9405j0ssf4cfq4osdja7f1j012l2ou9unhn0", "4mvm7i8kfj6a1plrhctmat52jldn0i6jtfn25ubcpbos827e7gtrihlthtfh1c5gdf69frs9chk01h8if98ab0ca8t4foc05199te0o"),
("enu764o8i4qjoajka2sldobqr95fpacabq2j2mbuj2tij4dprdv1bif9uuursibepafktq2dl67p72qhbfnq6v2vkfbfpra4mt5rgd8", "4s1mfhuug935v3qemubl4eg7anaur48m5h017a4dtj4vn9oeaeluc45ea8nuqafhd6simkjf7rs8venfjr8jrkcjm6ertld59vuc870"),
("da76velhr1r1u5aofl2e1kk1tl9uddld0bo2qj1phdn1a13r3l6tfi8vcd13k4gt24pp946cmvjjs5rqinmu9gbqpq258p5segehf5g", "50n0en1csqg9rndovbue6rf8eoptis532ggk70p6p0fjt8ccl3k7s4segjg3hlb04oqvgof94spvhj8andpvkhirt26mmgsk01iudo8"),
("4iio8ptc1dmru1ihodqci4krs2q1rivap4shuvtln9c05dm1jo6jqjuackrqi24jus6srr2hm36j7kmi5ibttu8fl9egruc4gh83sd8", "53isb7gbtsv0nomda703ab99fudo71e0nemevcfredqo58jsom1c980v56pg6122eqhr8hm06veo3f24l45fdbl99d0drhrdpsp2840"),
("nfmmk6aiq8qvokf123bobqdf2gfabr96ets1um3jevu3j6t9mvak3l6o4cgdn8mie0hfn5ugnka5guhbb7o5iam6e9sosccnu0rufu8", "547ueg0mqmoqu0qesnt24kvhuh2872con3qmnslgnlt73supcs7qfrtc7r1g880p4q5rvgg7q60klu4vaf9qcr3bllge894c1su0g2o"),
("vncbll8i6lurii4e29kndk4bs3lbl8v4eqnbomlb0hakda5paasagssgqs3u2thq4avfr9hujmgvhlfphg54dvjsijv281id98ejrm0", "56mj29s2ueoto54440iteo4l645g33aao6b1um1k5f1ucvum6au2c0jhhhv1qurpjgf7eaapnhe7imcol0ejh13e51g5bpfs21tei5o"),
("2ai8qertbt2i3aaj5uehgnc7taq8l5cjlj6c9do47vpn02sl6hcqqnbsjbc2s2m82928fsqdnqjkteo7g1q9jdq9la5harp1l5jl8lo", "595c9n5c1026im0pss7qbed45a9tumavme96v0m5cgeq1g8iqs0gdtfmsee9cqnduof5t4b0b9pl7kv4thls4klrhgqhbi8l1mnqhtg"),
("h9tujfjm7ji823tg2o6s5vn0bp3a4fi7vekf0lji6jhoqaheba6jqpq7dovtuu72hs56qg05ihf3mm4hc467hab36s5dovpu7pr4m6g", "5hv3lah9ea1kt99fundgmt2b9c1hehghvqh0m3gcnoo0oadbvd4u506c0sl98cuo07k4el0639bdk99ib8334mcfe8q9u9qqeqg5skg"),
("edkdqf68dodqmcmkqrgo8lcroslp1crbe9b97cu0l4gr45uthrksoijm4ifrth8p50ncr68hc0bsnco770c8m871080v5kdonbb7990", "5hv3lah9ea1kt99fundgmt2b9c1hehghvqh0m3gcnoo0oadbvd4u506c0sl98cuo07k4el0639bdk99ib8334mcfe8q9u9qqeqg5skg"),
("rta2hf0e7eqo868vfll91skkdjb0elhvkv4cbiuia4ldoda4sh565ivshp4h7n0q72lnvtr9k6onl4lhdcethbt0hsfiv17bqqutk08", "5j2sqokpg496ts27o69bg2ucg05j4dhjoj6leq1uu16uuol70er94nklvev814emnp6dcdv3h3nr1poijmoilo1cd05jbf7vujso2bg"),
("qmkp2gu5f7b3u1k1ftcg0kr6tolsoikjtan3hmdsltdgrrodru3ujd5um6hio1m1sj3q69v5okfu2oabp7kinbq96phd1vi4v8jb9s8", "5k1dapmttu5dada6jsrenbfruh0v07sa42ja0jpdmdd6t6u8c8k66fml0aal0g3pm6q3uv4av84ch2ogp84idg7obvuuos300f14610"),
("5oj4njpjq7oo7002irhivjt2md0od1utmdnafdrd81gbeo42bsv1hu9c00ifbsfgokiv8l5o241v8l6uh0vkshih6284tmcpjas8bro", "5pck4kntf7usvojmeuutgbogm3u6kb32s8i1ucgn7krgktlvnu4d4aekkaqpm885tsm6i5jsbsm7o0iint017gm5a5ti4q1sl8826d8"),
("khtnbpev5rmlmgsntafa5s532fr10t2kref30linmsa488a3es1noqb4d53pi2evkiau7o3dk65mi684nijblbcncindsqd0n45h7p0", "5r223ki394o5t99bo6kss7t2cv23dhhmuseti7rlla85clpi1ut154i49q6cgcrp36okd7u8295av93qe3mroap90udrs593lkikst0"),
("arba1fq6f4sg0fsiqo2r8gvb4ndjop40tec4041vb25bn3opbn9o62thg75mptqgftebdhu6snrrqjvj46h2vc2uud2dp5uvqaq9r7o", "663t8qpg6ufvnss1292cjp4l0h0q24udi15c9ccar6qqepsaukghav01340vbskkore7dmijdchp6patfnktpqa6fjbks19cbvle9ho"),
("qfv90uk8fop0rfp19q9qp5qhtu7vs64l4cpa2dn8j1cbu94jri29a7e17s4di4vk2fq1k4orr4p9j3kadei1ei9dscui9k4n2vi8og8", "66g9inh3fohunumm88p8mmkbq9iqgefs4odkv2svqr89slf2dc5e0h7gldklejv2e6fhl5amq8318eos3890r7ab4n3j4shbjg233k8"),
("mistsd8t7aets2dvmulto4mf1hghr6nqtnf5g0qoupik47itb9f5h07foks6qc5ms5bkbba2dj4urlc5gmp3plha46olf3d2fvl15q0", "69jcs64vistm3h7jrf1ar63se34gs2bs43suu0cqhrja1sn5nvn0fftm1bk0pvlifklmm6j7lma4qme8e9mi6n76m3rsusm557kf5e8"),
("0047n2dip5sqg33ccv5vp502q0lkadtvjfnlg7j9psnk8d5fs1h0btcr2kmrkgbvp3r812md08elc6iurm1hssr4e3g6k01ni603id8", "69ps1up6jnq0o4b59jac00a6fiitup0jb1hpqm3p5p0d18aghig46b1jevppuvronqcarm05omp77ngmg5c444vfce5u75kqg5ov55g"),
("tjssa68nor4c11th93ph3c3vk70uiro9pqev4vn43o64phiu90ji2h694qcpto86jc2b6qqkdvupasc0p91uhlmltv7imttt0l6lnj8", "69u3q27s4f6l75rfnnela0dmlru87sb8lf8gun6thni3h4ervsfbnm4uvvaqe56jbkr846j13v4qbgafv5j3v7n4fgrn48rqgifr92g"),
("mjd9u4lb1ji6tkb4p1kom8aa2rmfjj39tvuje6maorjuc31hcphbhjpbea2cgm8d1nbs257ijo5oi1c5qr4a0rf6n37iu7ouu763t8o", "6gdrm11hvjc0257tv25tbncq03f9d6lh3p6snsn8d13frnr1dg0dgkfuosn2u6q0fnsbpdr53slbp1q239hjpka525hc0vunki4umq8"),
("f6ekdfg64n0lu02dkdcsjja8mu86dfif2jirq7eh2fv41km63kdire4b8o1cotjm09jlf3mtilsvfrf8cfc4u36ifd9h1mm2r5vvq7g", "6oljadfdq7n738ev9uq2t93meva69pdelamjcd5idi03dg5fd3bu6er6crm784v9l20bvqmtb7knaau6dbedt6e8g7r6qh4qdkobf3g"),
("kr16t48adf1srrm3ghqs1htk0bls9ubbp7nli53a4n9eamkprepvematmio18n9ak12aaj5r8r5msjevmlqm79qvfnc8k51jnhnrkl8", "70mehrp1puemqo5vag51ojgblc62eb94od42bi5jekn9g95b65e3ddo6grstrha3ska78g804naavic84vih27mfgldac7pdc15m2cg"),
("qnbq40auqtvq81kolgvl630jioc4a7fs7rej2sep467n627ivvn0d6r31j8cq1go9rs3jn9tlv2pb92bqinpfdl7a2irb8pp0r4qs1o", "72ja03sfhgsbhle0iqpg4603t6th9iivo7v0fli72f1ir40h4epaln87tcfc8g0gqp21lhbfc5nda2g1uhvgq8b7v547ldt1tn1f9d0"),
("1135va94krkkijquugf0c2r98jgpdrlvtour096suhci72cap3tj2n42cnkatv4iau4k04f7mr4034426c8fdvqabpuse4bc1i1vdco", "738rb1m2558156bho57c6jg3qo41pep36rb5eb4sga7sskqt9mjjvo0ui8ctvks1rhldbfh4g89ojkbtrf745g0evqccin13256p0bg"),
("8biros59hgo81ons016aj6ji0h782j9lpj1kdi4r1uichnkbmd6q7fntkn5vjr3kodhnhahdhs1hnlj8ef8chf8kpne15iop24aufuo", "7600529ie9sf0rsirfvee4viipj087odm974rq1alpvielsqpmum95tnsp7ctgvupknouekdhdlkjg41qq5itlejn19q7u62cdcnv8g"),
("kbhvv4cp64fhk6athvrqtg4sjeab5rp9jutvuncclm6v6rb038dbst5gc6as5hv4cnrv5sn4o3hpvs9pho9cbdg4hiuld4824sae6h8", "772kgedb0ttrd835161gnl19f3djg3l47748g90n2g9e7d85bbc9v7r5377lcjtpadntc9eodcumcj237mm7abcfbs05fglajoo7md8"),
("50053au1f6j9305qvro58aq8qapnifi7fnlenf8rn2htng8tm6od196tu3pbcjs9fam7r40c315prsv4pdiauff3baq67hu2odu2egg", "772kgedb0ttrd835161gnl19f3djg3l47748g90n2g9e7d85bbc9v7r5377lcjtpadntc9eodcumcj237mm7abcfbs05fglajoo7md8"),
("eqqsulfd52197b5he8qbvn9c698uh9ccb0su188slkdn92o831t1d9sgsfvqfspqhp504k07l1342llfklo1scv2icdcce6tme4h96g", "77bp3gbjq6e84lmto8jj3p37d7g43ua9v0jpu84pm7i86brr6c0hvuo1camsetk7pdqv13hf9hlr4ht96a5cg0ptk99hll5oel3knu8"),
("9tvlbhmoscdq860si4c7rvd4g0ir61k0krv9115tlfm6nbc603mnml0j00p8cnnfohihp5tkulcou6rbn9a7ffudl2ehtuanjvjnnm0", "78na8h6re06v44jmtiva0nv5tmnlo0j1iil0n28v3huf8nbvsbhacoecdabbh7lr9jalq8nh175upct1a1v7mic88kdma48im20hao8"),
("rjc3iuho0io276hul457r53s81i4bim6tfchdhirp58jj2fh62130mk39p1tcilif42us152hcjn8pvh7ug1m50snn0sphg32jrc920", "7940mgarqobua8hv0jnt5v86nqg9r8nb51mrhkh58o30k9ksuqdhvtl7pck9ddjnj75hvd587in638lek26rsg93e8bqo4ejhvvjqc0"),
("3rlkfu09ghluqm2etoflp1vor3scove56hvf3uh3upu9ega0sn2bmgqrkjtpif5vjr5prh8cn60l8pebd280c308mu7figgt2ej3guo", "7bkd7ppqa0kcocsnhorvunr8g97us3iqgdh53hv7af7kds95s304o1gatih24v9pki7edvmls8vkmfll39e8r2r5kj9q1957ugu09to"),
("9b4bss9k5p8qp5uk0oe1ajrm6mgjfggoto77bjm02rj57n6feo66q9v2c2krpj9ludt7r5l61narqjfc8raeg69fdofbbt154r181c8", "7fs78tt60ks31h7643fdicnd8kq7njocgj33bqjgi5f72u2bst2rae2ov8sbmnsuk3aknfsf8binijcjvqnorit33jep7c9tnt7gaho"),
("k34s5luj1uc1pamlan6dcqt53cqlo2i1om3893sp54ghci0mb226ics5cem9pg2opm0sh1bsn18dn10sk6bm9b45osss0oid65ecl4o", "7gmfq4b7sgjm63kfq34eu6d9p2h2qv5o9mctjrlpur7c99ljgdf0a1sta81vrelje49lgjup34f8t3b5b4qhtirov6vqa8oa6hrp650"),
("mnq87f4osjdjj8cb0d2b2jcdpo4jgjmfb2iha4cg8hilbd0vkopbrv6ov40auea2tad8532esvvsh4j2uh3tms54ovi2i7a1smpkm4g", "7itmsr6tfvnrmcb74jg2djhe2j5il5bk8mcogff4a3uieavkq2acdnc7ugu7i5qkieicoop5n6034jkipm3a46ighsuudvv82r7roto"),
("lmvpi1j5o01mfk7ldsrbrcnpk5nj6m7ts38ec0acd427ve326vm4gvpo0ko1glco4824a5gg86kmfq3ng085bli4ogfttc5itjb5iao", "7itmsr6tfvnrmcb74jg2djhe2j5il5bk8mcogff4a3uieavkq2acdnc7ugu7i5qkieicoop5n6034jkipm3a46ighsuudvv82r7roto"),
("kn3bt8gpmmidp6ut576efndpn91s5pp1jm81qqrgqhk02gapsner50tmhbr0u9f2j6kegra7ab9r83idni41p3ldeog7cqkloijgss0", "7n55r5fnr8eaik2iadruhln6vo9kcgo2ebk5rbutubo3d1anhjkfelofe6kkbmhmub1i0vjhvmukvfbeme7skselfgkfkpikg0tqkro"),
("n2oe10iqt1uvgojo5sndfiht5fe2moukbg3c7t6jdeqhfbm4pgems07osqeb1bhci2fk5s2820rrcm758v7p8ergtntcq7jkivkskq8", "7nnkln9vqhco74qtg8sriiqe69nh19q0vvppv8e11mq29qmqlvvap5u65jf9v3cufpj2lr0gtl5k35qgdhml2qsrcnmelaj2p2s5i10"),
("3eueo62hbj4sv3escn6sdkbu2oesjni575mqjc33g7k1pbhcjn68phrhg0v9edv4nti2rpfhsj0oreg2of9a5oshlk1e94fdrjs3rr0", "7r0qh631fr1u9oin43jotg070v1adnusg34sian8a7dlr1l311emb8i54qervhf1ql85tl3r49gearr0afdqghmc9lnr0ac0kh9hseo"),
("0afhgamm2mvh28fd1e7pd9bml89uldv869m1sn8ms23begrcmaplcj5ukqobl7ctu7ikv1n34gshpidk31evq2j14d5a96736cvogao", "7ul0gaukk7lj81fibbliau80ul6n3h4apkut1sprqpsus1494j6p3nn722igotavq42qekek3e7mg11iq7kunm9giifnf6qjutp495o"),
("ccc5ko0gv0vu3dodv07sl63q531qnihic2m2loc3p41jshj4og9pdv37fj55cmtghnt21j5m2a7cni8gaaulimqe97setq9fe1qubo0", "8079lvl1c37rp8c7m6tndh1rgq1i70dokjfiq9sgmgsbf8klslpvncrf4rq22c8me57nljlt0oct8j1j7fivv3rpvri63i6qfbvnhfo"),
("9ikjop45ddnc97ecv62esvjfopasd6ra2etbeidftad9d3f6l50vh2jt62121go44uk2dnqbcfn9oekfrceii7icfs7lg08s3ksb4ro", "8igtrmpsvuoocho1g2t8gijtvdkjevgt0rfn2qui0q9bg9kaodlalttu7ha02s2u35mupqrci78pi6ho2fq17ciaptr6fan9eechbsg"),
("0meqk7u8eb6nq6otlfsrt5n60e53hkvcfgd2e99rmmnnftet5ki3ev948hjgjlutnfkqoqirceanko26t14ta66n1ote7p4kjvqgbo8", "8igtrmpsvuoocho1g2t8gijtvdkjevgt0rfn2qui0q9bg9kaodlalttu7ha02s2u35mupqrci78pi6ho2fq17ciaptr6fan9eechbsg"),
("l9a452rvhcjcfl7ao3amhlrq6lj5555prvt8pn003b332l6ccplgmuhjvgbujbcasugat0d8u91e1mbcdfk2tfvb67c7bu1n05dctp8", "8nmrudrmkmpb93fc8qd543565qf1vludhg6llcuvfsgs4ucbprijbdlm0ghdg3c12n28s3pk7h7d8menj5vrkj3up5eerdoo2mkst9o"),
("mt6p1b2lic6obfdcudn1jv9a06296dvkoln8gou18n1pdkp1r0hchr182kri6avqrd7sjrodk6um372fkfp77qnb3vdmeccoav46h4o", "8rg618vts3m5dieo44c4ks9mou4lt6kp1rvj36do266un0tonl2ueutjml4qb02biacj8ms9lugjf1c295qjam231ed9l82vvljq4jg"),
("d5g3fpngnn5677u6kq9gft94tobuaflbkp8116cemdf9386kkrbatlc3ki9g87m89jlogjh4l43d82c2gcnvcib22stqpl9dfa3cprg", "8ru73nqjuml85q6198nothcve951d4dl28jpfta2grb3r0ppf8lt1k2j3o8jd8nv47npmgos3bpn87v930rleejjqbm50qo9hbfgjo0"),
("hc2bmodiv70q4j4q2dbr02ii5vvrlf9apq175cvub4arc0t0ugl5i4v933npa29tlq5p3b4n7v546id919dq2u1p6kutc958dng1vq0", "8vkpegcnntsp8unopqnum92ed6fhjrmjbevs1g3f7t22s8focpbnq7bianfhmithqneb22higr53fsp6vbgts4sa368d5060gg88m30"),
("shnf32g48baniclnb3a47kbrvva7mieinsb8s7ntiok9vuc270av8mr27mrobkq4i8k5nad1rgkgkcq7fp4mjpagbkfjkamk140ptog", "9278rqkunn7d98s1oro62fkho0upcmp3fmq9mk07c967r3lj3crlhd7v84kgdobta672f1g87kujv8ejr6en70d4mkmv140ctdac5l8"),
("ggtoscio9vaons0tog6s666hjvj8uig1ud9tv1amo1hmjfiqont95hhtugddu6nmjieopeebi69gl4gb9ieo5eb1sgrdo6gihu6tsm0", "92rpa4pi3nsa597hurq8cmgdipdad7p962s8kto9nrnesl4pbd1spi2o5n2399qb77v59e2d482urs2j4ii1tl47b73aop0o86gg120"),
("b1npovssbl8o8bbaul32bes1cbe1svjpf1vbvi2nrrcpqi01s194bb3ek1eo7gqueghf6gp4ak4ji4556908m4bj2hoi02cr1rgc7k8", "92ujopkbheuio43isfrmakv15rml55a41vg3cs60kbe7gfrpn3ihj20bnjnug12f9shscd2a04db9ev6h9v8tc9c3oiko0nlm1qd9hg"),
("rn7fnnt273bs2eb4hrps3v9hde8ilo1hueqcnk2bjbehsq4ui7svr6c0v9ohrdm0h50ujjtup23161lm5pgredt39a7l1q226bk2oio", "95o62lsf5rthmfii3nd58ckalnvojhgsrgj9j2ipf0botrq1hd8sqoamhtqt9hg8kble0f2empd119p77797e0lc4m1180g0450g0rg"),
("jojcd0bg6c6p4cjlv26v0nf9nu9djv8rc4u40ujdrpr2cde27nsovae63rhteak0eph6lu54fuq2gqr4om3rjjhl5cn6vvrb6mbaeo0", "95o62lsf5rthmfii3nd58ckalnvojhgsrgj9j2ipf0botrq1hd8sqoamhtqt9hg8kble0f2empd119p77797e0lc4m1180g0450g0rg"),
("3ic83i7htnr1angkdpvhpolk3icdjs4ss8mp95843gn5e4smjpno71st54oeep7dlpmkhiq6bidc6jfhpmcqlv1md2m2bm65qup3d3o", "9ao4e9op7j408nn9f7ar4cv92h74bkqh9acucqa3vlt4c6b0akikn3v5uq00vlsa0lli6t9rrc4ksmtuigo5fhtqshershidr630e10"),
("4cl8v7er59s1hm73jc7svcudorhr943v78hlss41rjebij24o80ct5493qp35nhvs541a63slpflhcs4g7p4irithvuo7vmt9fl6g60", "9b2dge77munt1ks7b7047j0omce233quq9q45d36ja5jj35acpksccse9q7tfbaiaacbt0d4sis2brql7sfnkkbqg3obdpg7lorj068"),
("1j4ov950ivd2s6i6bjg96ebte6j45ci7gs8i4vd872lfuhi42eeuqfh0o7efgfpt7glu39dalrv1dk9ilup2g9l69q32126ta0v0cc0", "9b2dge77munt1ks7b7047j0omce233quq9q45d36ja5jj35acpksccse9q7tfbaiaacbt0d4sis2brql7sfnkkbqg3obdpg7lorj068"),
("dicfvkehjjr53v41ibq9pqv49lbfq05r8imtpjhkl394g9a1hgp867rno0dafogdhggo9kltsg0lp7n10igbk7rkrp6g0ouhb2q867o", "9den8ke1668uo8bvfhpgufn3kpltijo4mgl5coka8ca5gijdtlb19b1g7137va9j5h9det5g78gtakn2v5kk9mkjmvrareigft8ncp8"),
("b050qvfnmnot84t7njb4tee4bmrf1oice3nf95cnrv0rum5lug5ts3tqf6gije3hkdvshhkbj7o1u4ent3q84b8m17csneape53a5sg", "9ermtdhgctgq8g58c4rjas200nbnvuo1kicru4l9ahh8qbkj8qq95as9dn973h1sqc4e3avr17ket4jipdilnr49f7kklf64fnl8c1g"),
("bvips5kgv66v3ciic10ddvf9en0tv356grp1jvftcurbj8q0c78flq6hhg3dfrdnp13j1s7dgi5rom14neh3to4bcc4m73dq064mnp0", "9fr663iiqaokgmo8gcqqdv8jv0e3quth518sedd4e2sjum2r1n5f4vs1rqjuflnb0hntl41144o8omau7idqepkdd8mpprp50l6pf5g"),
("b5tiicak42ig26pi5806fl6c1q8dqe782eqpvtv2uhqtq01hhshjpf8jhj6hkes1dafr5meqq87n8lhkl82i7i11gptt7ooi6cnleoo", "9mshg7cg5jtku1fo335oesl87o1jgclgdrtu9pjk1qmh4e5rl8gsvq9sng227tvfg3l42g3sres8i95khssk2enegu2bl1quppkv39o"),
("apnf3l8i6usr2r4c000ljcotaa0hkaq22qboqulqsgjm0duhkh0s805i7195pi7jjn558j9rran3otugme202hhm3i2f5074sbl32kg", "9p4hvbsh7vurfhrp7pcg2ooe8dl204jn5uc6m8qslk6jhbejbnb7tvqhmkr9pksi9s8bpfoun7d4bd53sbdth6tld2es9e102sbnr90"),
("m446am978g32o3sgdgvtmt0s755u8o6irh12rg2tjj410fap6siu7p2c9id0apr2kbp5l1rjlueqjq0hv3nbt6rblsen8r4sah9qar0", "9qds934s8lru3sbhqa13t8mu2eq6kpklk7kuje2iq4nehrgtrosacuthbi0pllp36i1a03h4imp5hkjqq50f0m4k4agah57688ajn20"),
("50nbjptcuk5ocolm5lvubr7ejr1csaqqv9apsh6l901d1bomsa319pa64uk55d092aju3u5jjvs7lltk3kcgtscd4ghe57kpc0loav0", "9r57rjn7aum60thfisq769rheu3oc9bmmkb8e8nmnb3tc8s11l3f4aotiep59g771d0n4bsq7ap2ik42o42vgjnoate4297vemvtqi0"),
("q128cilb5nlum5soa2hbo3mg0sgtl6rqqoioimq1gktnc6ag92pmj137b07fk31qd9laajkt1km1fcnrbhfkp1061tprp9qo9j38od0", "9un9lst5m9u89fio8idaj60j05nreqoqvvcfuqh2921i5r1q7cmstptqa1ot4dvpt0evjp0hf7vbpqmtinn053d80k1hqk73ek1f36o"),
("pdv41q5kc1ofs49tauqmtfjk72lrgbt8jth7u3upg2qjvstgq3nb3sir1m8qmptle3k623fh7q5jckn8tti6l5uo65qotd97f56u698", "a78s5e0b1tiglc0mbij4lm0mdspgj1hb7he9o406689j234emhh6j46pi01prn5gilukns42rporgrl4j0bhv8t7ug48567o2d1sq88"),
("eelgocsj32ecic2d5rhmfmuoneddbth2u9lne127jh2ogmnq62ijh54d77np5fntj15pgdaegs2apkrha596pqil0kilkaios9onh2o", "abce4lp9pgph2oe6c1qsp3ecaff9utdekl0369tekvcb1i91nqmn37buve91rgjlpv8eprer9b1ta72g2rv3r9aqnv10pbs8fg5allg"),
("5k45qatocc8jhntu47s0md92ahooe3e69v62gmotaurffqbshmh22g728su5cgojof2kil95vqdmttetm69mfj0q0u8r8rq6ha7v7d0", "abce4lp9pgph2oe6c1qsp3ecaff9utdekl0369tekvcb1i91nqmn37buve91rgjlpv8eprer9b1ta72g2rv3r9aqnv10pbs8fg5allg"),
("v8762tohj4irobor8asap2nphsrjklkct61q3kngiogvpemikq623v9uf9m0gusg9u1470vaqpej078f85lalfqjrqduqv31b572ekg", "acl3t4fok16ifed6hcoktojlksv4mpau9kggv2k4q2vlmiqamj5u05973e2duik5rg1rq7chif81ucq2n0ash2sr51kl07cmh4399j8"),
("69065tfegd6khdmd7d4qtb92r1vpbbbuf2t5l5boedcme2ttn7a072op53n6fd5n6hudtc9ceocbo2tbj7mf03hfi83dqgtetrgbnmo", "ajcul54flk62jh2e6eco40juna1slgbtjk6u488lmi3ne3bc2n5h3fe21f9q7bssd73etfrpgmrn7leasjgb1812k2k7nbssjbmkfv0"),
("5kb052kfnrdekreo8ujnkvjd7h2q2qa6gu22uhkp72an3mhm5sfuqstjniht1lq1ltqnqh981r4u34ckgadkb0bo1pkidnoeb17lp88", "amgpajqv02bhort77g6j2ra4qdpcbit0iph24dsqu1vs3rckto2nlhpj5vqk5ukukeq0coh51fc7v05qri6qpmmtd6gt1tffhiuadmo"),
("gvdd5p303a57t4lotu7g7g5b1an2tsn9i8nnf388l1ndtsq6e5c4ecvsk8jh9pmnibqeddttgig1gtk7e7miil388kepbjf8de74jfo", "apars3glq46hdfbt8vjvlkteufhpves2g9mc35o24ld43d6tj2q391nt7r4l8uj6o1u388j9hq9jjctqm75i46p53pi7j5ct7c2jck0"),
("orvaqtc8v6skr1aj3dl2d8a02erjtusrhi3gl3qcn131k2ii5nrqm15ufjtm2adtvq1s45omma3ot3q8fd472uji1482i2ltepoj9jg", "aqfq855vh306ldclcuaj9edlfed68ab7vlnqi3f48pkjf7h9aa2dkig8im2ae1ugpo0q1uvmidp8li0amm1346t4rt1ots0fglei8ho"),
("1dkiqsaso4748duo3dnsr1q1o5t2e2a4ra65mpo94f09ioetc7d76d7r2sf43s817mcdc09v039f81858un8da2n5f2s16d6tupstqo", "aqfq855vh306ldclcuaj9edlfed68ab7vlnqi3f48pkjf7h9aa2dkig8im2ae1ugpo0q1uvmidp8li0amm1346t4rt1ots0fglei8ho"),
("acbdgs5a7kveet62qpkms420jf8add8tu2tj3idla04j9od54l30pulncg9mjei83jgt9s8sd97jjleajndcj2rqg46sj3e0bab83kg", "asp2sh071j6bt39lkeru647eabf5ci9ktnkimbbq66d329jp8q6np95b7ckkac57forbultgj9or0p2p8un8q12eku2l49ec3qcth0g"),
("fn50tcm7cdmmdk35mtreob07gejrhscdt4gdg8cpail4fdpfhpkst3lpdjf6u11q3ukqhmsobalfl11pj3jcdkk913mv78e7h3mhb6o", "atdf7v034vsikbg0jn9qripgpai13u00md2kld47hnl5bgm8tpm314s7ldje7ubfknvn6a1dg4mjj0v516jgkv9tevv4cferfrrcsn8"),
("l4mnjoipk9svaabhsm2i7nfdgl7eil1tjrlalr7ha7tj6r1gcvnum5d1q3rl7dkc469c7bgdafgkq0oe21q0sa8alv8ff615al3bgko", "atimcgj1ad4v5fdqo3eot0f5dulunp9arm1g9c4qtiv5ab7d7ij2pscl58d5qsikcu0jmfhmpksp52bpcjrbgjp87uqcrqppk14p1qo"),
("fq2ns6td3t6edud31v3lv47vv8lcnga7agaj2gnaecp2dkfpu82agqgra3efngljb8fqcs6pd8stbnt3dsg33qsvn8jra7ile7arc58", "avfj2iipgb53dlgklgcv3r2bkpsq2nl0klsvfhu9nr8019hhdvrcons6e0g5grsc78ukk4j9mn4ekb8r7q3m18nqth35co0lue5s1l8"),
("6eoi64357r5op7qv9lged1raktf60mop6h506hld84t6et8q6egbjdb1555me3vnqr35q1i7mrbo8gsq9kr7i84c9fi0l6cbstcd6v8", "b1sbsnembu6k35gm4av6eba21uge8d7hgvvhpvhicjrmq576qkk8ugqmltem9hrjiicdo97r8p2tu8cdr64e2eppotvdva19i5bs7bg"),
("9r3d5e9q1oo3da8k62l8o74b63ongfc66snglg10u49ll32330o0s4todl9rc1d8r5jvq93fudp8sksbiqn6hugsgra9shenagn1mto", "b3nmt2p7j8qr34bh0nv0j3ipphd2ahhb3egv8po58suh8hm5kb9f4p96jdt9i0vri9nvad6hv26kvhdgl4hjfqjcq3pgl26jjkpqma0"),
("opkq7lr9vdngdhvmftakmej2n2ji0oa70us20hpdvm64tjhu2te975or5mdkk3qpnqjf5rtt46if4fubhe3nn5a1tkj8t8ffjh32vo8", "b6fcuu5c7pg6fdui7u99uuqtcpj2gidisb7btn3jvp43ftuabjpeov2duvd3no1su3l5cm4ua0ot5be4pq7vbv3jr562lu69rhldg8o"),
("rfu2caq8n25ne57q8q9qgj5pp99v1rslbh11a50v3j43q96j8eo9qn30nlsiapcaifvi7dpn6dii9lqclm717mbjpbnop0bgmnaspbo", "b717pg4utpghg87cl3sri6fqt9aj8e7hib9e3hgvgabqno65obts6b47kk145661vbnv6bp489c5eafsgoeg1d9prsoepnrbsskhha0"),
("m49sfo0vigivudh3ndbro5b8u105bnr09924jl2hjdodaapad0au0205kde52o5b14vjhpi3c50m74i65mgrode2ve5vb87pobslnc8", "b717pg4utpghg87cl3sri6fqt9aj8e7hib9e3hgvgabqno65obts6b47kk145661vbnv6bp489c5eafsgoeg1d9prsoepnrbsskhha0"),
("gmaoigtjr9f745q808ju2g8i1i80bjaarsnbsb7sgup0v048fpvdbsd86458ksaqrus640g71jlrkg4ks2mo07pcttfrcukjbj1ruk0", "b8i7uvvj0nfn7p2hm53da9uijuca6sugn10md04kbg1me4ogc4pkk6v02h88r9vftef3uar5pmahmsnu9o5qiuaks6s8blu62sj0e5g"),
("81mvn2fic87d9us3ck369vt2uslcj06ojusqk11n3ki6pmk8rup7rc0rlkn7m68jr4l8ntpq7ftt2ouo6nsrlt009fi7vcc1gdul1m8", "b9mso2s4s844s6145u0mericaud2n9m9g79r26nptc52t8154flb6rh7p4r4prsvaeftsbeh7prsrk6dip134to8nrd2r1581f8hnd8"),
("aitfi7s05318ahcpt1hr14rukagm17s7jagvifn3528i77tp1kksvv7dfngq5h5an4o3gjbrvh3mm7tp2fg27n4mt45tn42g6pf7tq8", "beh3fvcvnol15mcrn1kqne9cjfv3cn5hteulsuai56vre55j5v4hnpkls8ba1lbousc3psmlrltr18aophb3ncv08pg2ecbk7q6n3u0"),
("euatkgblikfs02jetnqg1vmol7g18704hpivt0f86u2a9krvak8a5qd9ubbf90ord8b4ct6mfd9l1dqn1426o86me6bljo5aaavq218", "biiqm6tj79jcdut8dmfqp3i2tdbr60st0p9b04jh58601oget7ck6ci88iuj5p56o0l0h8qcbb1h7fh526t81gjicomtbpeg5rlgqoo"),
("qtg07rqosnq1qsnrp2ur14ner5i2k9h5stpv5igvmlb89c8p00v18mgqgb6i95eoeje30r1g85asuv9tg1tljcadcrumq5m32b01ko0", "bl2k6rj6sgkkmapm2atlf782dtcei1duu4r4s1c3n0ijks408f1ck02q20e2oous9poeu2hi3cs71hu6eh9gas58bl00bp7maqi31n8"),
("dlmgr7ugpm1ld095mvk15moviji287ep69j4453pee2eee7sonopt7c1lnm9rfbames8uk0fl6k8c80dsavdisfepiq2ta300hru818", "bld3pci5o5c171b6pp546vtfsflqevglr9f9eaj39um7squirfq3dfjgktdh740efdrb84e64igg92p4kohohpglgcad0af6sn0sa70"),
("jbopg4600bhm75jh8fso0r11d9p04f8mf3f5f00jep83vcpik8obt24qagop1t1buodklges7cjfdgopj8o2rhqpkrfieb6so1qgfdg", "bufh779t6gcjavq9rcrslb0ikqc9gimh9cmimd7tv2gv3suba5jp84ancluppkmqn9o1rf23m4timthrff603319l94humirmcgvjb0"),
("1cviiqfvum8qrs260f6t75h35e6dg583b50ilvgqpu0bfn78044jcin6j6jds8voln6nfuru4s10f285mq0ib3b7u9vu7k6if8hamp0", "bufh779t6gcjavq9rcrslb0ikqc9gimh9cmimd7tv2gv3suba5jp84ancluppkmqn9o1rf23m4timthrff603319l94humirmcgvjb0"),
("p76uao2rrpu2jv44256pnlhnja91u71jkr41snqqmbr834tt1elkj22e0qve9frs3dthb4gm269us98asvklt9ogtb353ap0104mpb0", "c0volmcdpt19236vksjeifl47d1ac32k7s01q6udmvcv09idojfjtcj1ig6h6u9cu49gv9gl6e4hm2dms3s2dun1vqe7ujolaseq7po"),
("pgiampeo9qpvnkecfd40tpvue876st4na7n8h97ru3rm2e25u28t0eadostu4sh8hvp6mupe8q6vhcgt86hg4e25vhbtgp3ls0o8v78", "c5kpd552r4a6rpch9d0eo92bfdp7fuarmu8luf02tpprmka96fagelmpnl0dfgok79m9p77v3nr7mstcqd9j558gbpmd3ea8rrmaqvo"),
("82306bm29jp5h40ko9h47gtr459c64m4qvavt4neh49tlgjetlbo1qncmfn9ao0n5qfi6v5bj2t1jtfgdsc839uqpejq90k4p7ej5s8", "cfs0r7los5641lh7g9mfflj8uni5tf559pqab3ctlhm0b01g1u1qb4mteup3mq41efevnrtg6g088cde71mtmf2pufgfv6oj1o93hc8"),
("cvgiohaf7pv25472urcs78q5ad6j4p328cs90ba9sq44als4gc5e1nqod5ni0to1ocg92tqod05rhg6ihb04jjcb4dhnds3mbir7pk0", "cghqlr1vk99obebespmn83761jsiu3673ucsqufg3egi29627s3tgn6eictdu5oigsbcb91rtdh8hdco21n8qjocrrfhv8sp3vg4nug"),
("iqpgsttdj9o8akn3hth1moi9lneu5r4e8ts4m3fivhqt1akl33kmesh54hfgliio8inkd455qk05hvd3u0mbmhdsd50ugnlmutc6jq0", "cgj3g444es8ef7781vrqt2eg0i20no58nkm0f41qq4kuv7v32mkc9otcnko7clo1o92p5ve5628fgeggu2cih15pho0fhmcg18de0q0"),
("dgo77ujcsjli8vhg4mpevh9khpngt54jq5638re2g6iukv7dn1sfvr20c2n0qt37gun984kiqrk339dk4e7l2q2t4869k6ebjedrb10", "ch5b87nndih8ebejk3gsnhrgtsf5mhl5ktbq1dtdrndo63kg3k4p4r4m735qjk8hfd364ar90igd7n8d5o5q58ha5hjgot2tp7rpv7g"),
("f27eko3apj4lmc2arag57n4eohc1ch2tssc5d63cn40s7hbfdo8shamhnmh28ambkn8l2pqb714f34siufdnoj0madmtdecsm004140", "ckp53sitdupljoa14p075rb1l7p2hf64fttv8310e9r3as8dilmed8t1vksl6171dgcchldn1ta2j6kstlg2al5fklhekrchuvrc2i0"),
("uh0qkg5nvmumnehjlu96n90g4qq8itrptisvjj0o9hqhldpd002q20v9ubj6o0kcsulss8lkt8m4esalrgg76qg8sg2ne2pqv7v6hro", "ct04pu4a9gms4cfv2c5ejgvhokj4b0v7adraa7n2fp4c78ls0f5kkgh3a6pcgor924d2dm2btj6hu4obobihqtsd09al2claj4t0h4o"),
("l0tf0si5lp0jqbiucb43kg1ragh56n11ljid9renf1jccgar6253077ltmd86d2r4sjo6gu1kamh2nn56f818eb87k46tu6hegicha0", "cu0147mf8u3qicq1b0nfaenls8tc0qsld7m2rcuvc254plsvtlfl5pfdtplsokbpcfa2j4e9mttlfemm7v2ukgrgp4i205ep0eahpdg"),
("9vilpg4g83tl38m2jb2jj03fkgsnikqp4cbt5j2e1uucb3idvn798edk0erhlr9vhdsa04rd34ed71bjitcc8bvhhj06ko9ma4bec0o", "d1rv26i9604so1evl9hb5eq6ij7qihf901iuus4q2s1i7dksd3knlc33pqmvqje1eppfnt10q6o43qr0ohati57ssikiobrvds6atr0"),
("toc8rdhg5gntjdfsq0np15lhmtgdjnoc1ijf49mjng1vccvtnupnnd13mpssdkqribatr961piqln1shl3mjpe3jdu0gvj93tjugb3o", "d297r6onu7qbm30i4qupjs4ka3h1k5l3mmj86k1chdc7i04dglrcj2i0pj9c8789tn2d73eq6vv6ivdfqderorh0mqbmgkktlvgp028"),
("b7934f12eoujkrcghkffsjihrlgd612u64piago4ciihdgqg9af9vasep7easdust436vhsc0m2le2ld3nrjvf62bllibschhh8dtqo", "d2etvf9rugkm1ud4tsr40ib205hsgj4dlkfjm4e6uiggvtak4imicqncush6ntoafkfrt8pcm7a8kca2r3gc13s5rvc3k2m2tffgug0"),
("8jg5gh6m8utcniifr64b5evku7uakncdh6bt3h8dcp4eh6m7rj24hobfidddl9kk42iknnta2e2e9ttsr1nq7nf5n5cna65mq2lhrko", "d2etvf9rugkm1ud4tsr40ib205hsgj4dlkfjm4e6uiggvtak4imicqncush6ntoafkfrt8pcm7a8kca2r3gc13s5rvc3k2m2tffgug0"),
("abi35aekd28upchaec2lk0rg91c8cj814l882f8jptj2iurm7h5kf44osa2crbn5idbe0o3l90do95hgt0h5s51cd5qak4g39bh4s9g", "d35gdeqshkh940gf8tifdt2k9filstb8is19m5ou7oehp13tf8f891kh1gscvnr6p9u9cmep0u5n7u5nnbsmb36bt5t01a35eaqo7h8"),
("5ihnru7cnfg3evhk6o6dr1hvn76auai5767bgmavve752dhb7k126q7iqp2vij0c0f9getcocng5e4sflilod5hhk7g2nrrdv1rh1h0", "d3u9v67jcf0d52jjr5mqnbl8lr0i11fou0nqo937s76kslp7g44etqm2ms8lpbamglcde6accm1cu8eagaheepsam72rohci1a6d4s8"),
("68fcd470r6ggbvqjaaogjmfr4ghpodc60ftkdrqhmapql6svu2nrjbp9a8md69l6io5tnr06lfi19l8g0p8urdp5vpqbe0i73k01mc0", "d7avq2o6irl06pt6ocusjnau0l30fvlqt7283k49h9g8nn1scrab0ld2ufapq85c6d0sskberfc147r8i0hvsvjh2593j9u3mt1vuu0"),
("qdb79p6857fs5lq0pj7nl0jj9d2cqg15e48ek8k898ljvsnkq6nqueu42g79dokr7nkjo8do0gvansh6456krjee6pgrivic3c0fl5g", "ddajpisr81dt5kc65u51e8fedlukbeid9270spjdtigstlbviup7dvktp7l7mm8d3kumkni5qcpvcabh4tnio6cbo88fbvnnge6fll8"),
("2ia8sospsv2m2g4b24hish8m2rmophgeljjk768ks77ffbeusf88epvk6boc11ot7957qcihf35dqo1d9v1109q0hstr61vc2sp9k48", "ddajpisr81dt5kc65u51e8fedlukbeid9270spjdtigstlbviup7dvktp7l7mm8d3kumkni5qcpvcabh4tnio6cbo88fbvnnge6fll8"),
("4ajnpmb30c0g9jgkoklfl9lqetekdutqgfg486gnqcf7ls148ot2i3a86dnqncn04djsn3r1dvisufbbcf448rbgal0e15geveohka8", "dfb353bumrjk31tfbsprscf8sun1stvbkr95fboea6svftk8fbqv93qqtsq696q6jtafek504ckdqukr93ct5pa4bj2gqdg99j5mn80"),
("uqpnecj5toe0dhjpmt8libmqjdu9b4r2goai8v3uocqstm2e8s7t9ntuto8tmihgvfnib4mkophep8uaadqpjhgp9iakhbo8o0h10u8", "dfnu0g6trb87pi4249j6uj27q8mdd72oanb66cfses8r02u4humuvoqc0uvmtt31nnalr1iv1hu2afj1sr3q96nojsoqmpnstb93sf8"),
("bgcumj0ckui5uv9muprbjhbjdgifnal7bjbq00q5t39e4e10160kr9o04i157rlq0o5ca1qc1b91298fasm54u9l1bks6aic7qi75g0", "didfvebv47ak255mmd8654404j02tf1atkv0khpqm3ojcsqqq554vsf8eflb13ve2mm9oord3eq0o2tinkfq7eljm27t26g5jb4bbr0"),
("6b1jj1tt1peih8e4gvglrn01se10o9eelqo3v04kclhm6u1gqc7i8g6cjo4u2ro4ul5naj8o6rt5atb4leu2ic4m0ams517enu1o7mg", "dl9s6nmh3mf09nmmfdc3cga2s8vvbe6ccrnuqspi0dhp0k33kk9ttmfsburk6u85krqa7lmr0vivb1p3k1vhv8cm90t4vhtd5pc7dp0"),
("2n8nk1tck6igq0rs2a68i5hch40fr29g0tpa7365v45ag1rjcf9j16bf3lti4cpuoc41ig5sgfn76nfiifnhh0lk1ruvtvtekrftamg", "dra7jvlehmi7tamd56fkule26l025ff220uhjub9ui8rq9l40olmuaafu1h8dn9f4m7vr48enal8b9n2d04ipp3sroj5ltk15e0o3u0"),
("9dhjoi66ulr8ao2nnf3ddca0r9p35fqivh1f5a16p7dh2qf74um2s8i8sqa3a0s2r4667s4iqdfa46p6cubrfu8i0u4hmfea28sujug", "dv9aladq6qcda0j7f3uvpjk5jvjmof5cnf1cljamu5aemqj017m2fv62b3rns5u8u63cvvjjvdasp02dki19ucuj271epirds93qj8g"),
("dfgh2bqqndls04vumvbhkntmq7bujvpnbmcut34eqj9qoj1gi88h7k6ijibnlf4p8kolfk7q7dhrnvvm7aqfjin3ktru5emrqfhb240", "e026paambshgtk13ko0q9mj6m7nn5ouq6sv9gf7bs5j4q1oesmbl7l2s3a34qe8dbq4n23c1gs0gevdna21p79ohm3bdig3v8jbp5ko"),
("d419n94jrio8plnckpp2co08qgaqo3v5dh1oe13dff13jjevv87ljos4sqilrufjl99febk9pvvj3laoiosqc07beviab8mvk6cmsbo", "e0tjmr66f1jbqo1csnkim3515uopkpg1l93gn90v4tphcfb3v7liod17m5dv0hp4endu1e3o6e17qgsv0k6ag9cuolrmj053lufmqc8"),
("ppv6ab42daalhg3pa3et4qvk4jdr3hocirrvuo31vl5g4sm7dgsl6n7fjor722iu60gkvcjsv3do91oqq6n0icu2fb1duff5r4q6pu8", "e2aq3es2agat29hveuvnmnd8vevgoubeisn8fmsnsjf2pot0cllmoprliashggku1fvppsg7sm64qqeios8aeui0025m0ms9boabbt8"),
("758q7ababnahsoaoih62ghufj6s5cb0rqn8ejjpdu2uvevam1v9a4cbj2ongql48u7ne0hc7ha2ettn50n4p6qil5ceccffda00djh0", "e2etuklsbm3v9k4o95r7opt5h4ju9q2frob1266hqlf77ut6d57ah9dep32si0r3qaanflro0is06rg9fn91lj3viivm0il0g7qgbsg"),
("jvk71uhon18l7h90b2ar2q3fqlqkjt2r71aadunmm9jven4u42m15d75sunft0nrvercqbqg4i4dmhru43hkr026jgfe758egfnou8g", "e2slb8krek2gqbumgo24o5fm0tpbuigmtj38eapag6ovq3l5l5j6rgh464qteskplg4vj1tllbspjpf2bpbt748f4pc1s3ukbpha9ho"),
("15qsd2n1o95vtdm8ljv8hn6caoqku0911fish2atrljutd5s6dan3bd3lhbg05kfl8cjkhjpsbocrmd1s7rs0ol0vuv10mtc7b6hsao", "e3atsl0urjeljolmspig7lcq3p0cabv92vrhjblvrr12u5irfrnms2tvmvpr20dvdrkgs41pa4ulptgg5m9iv6tn3kuubpkbveictdo"),
("mubntleqcqd31nepa8omi0fp23mrf3mkef1kjkmk2revdhobr3paqllkdq75j32huh850092jhhe02e69bmkvpeeiguvs79rps9t1d8", "e3eb59ur7htcgogomp9vuk5k2lj1d13rqoci3jfe68a6pr2h39ltp13s8lm3i33kb2kign5b6ioaukl555t5c02j8lkt2dr4h6j34s8"),
("rdvpnc9bl39v25dak3fekecdmin8bd6f517mucss0g1birsgghjphp0qfqlt3hpvam4c38v0jid4tli7uj1uvsen8hif1t9e6qjbg58", "e3ts7d743bgb0u1mh80tevs3kp52jl34spdphohd3ri3t6skf2gkranjar2ubqjlsj0c1q20m3ue3v7i7n12cf08m7hqkk3uuch381o"),
("3ulmo8u16i4j4tp42ttv834vjugfvtafd0qou1deg0jer856jtr2rck8jjtkstjmfk8eed0tgevi8ro9vdr5afcotmfre25o0s5gu68", "edetgsbli1okcje9mottb9h6pd64j4pjrkmah0q06j995lpuo9vdheea693gc5bthf6h71k9ko0m5hnr28p5k4prek37sfdum6a26qg"),
("d167rjhhjvbce0j3f2hmcim4u507p90ldcgf43ghn7str6qjhnnnasm3m6p0dj0ntaljmrf092usjih06it40i16ou4hg8fh6v351q8", "edfucqlosqmd73b3lkm6qgqqm0qqbg747gpnvdh3thjta585arbc7lj5cnjejctk00gfp4ao5vr0chcju9crklpf7gofb7tutkrr2t8"),
("79f8gvgsdmb9k9g63760h2htk9dsghvugvnb2d3c3pd5d6icmtgm1o3tdccjtt2vfrh0gec57k8bqf58ra716n4f2fhba7oji2mkmlo", "ee1hqe62b5utp2mjd62d65lhlo5ld4ssbrihp7d241bhdbhpprcol0oppmu7075lohoktqk508v4m5o7kj56hv038cr7ffnh8lr9gtg"),
("1imspdecioaj8fbsu4p3prqi7kjnuj5q7o9titum9j6bfq3r41jqk32rugp6lf2a28b0h62dc7v1a9k6oioe4ne1c33ftsdoc9ntr68", "eej1rm4deeqq9eud8gsflj5rdp1kepssi5t9ftv9itpvqp1gs2c6nf9fo1o05l0rma7mb2i52kofc8rj80p5uijj7rmmhb1id1v6o1g"),
("3d4vvda75c5lqod8lc46k3nuo02f2bcaigsbufquv1eif20nfba1o4n0oja3hv4q5ov497o3tdsa0s5dd2g3okp6ven9rfn6qjk1s3g", "effskvqt1ssul08sknedpc41reme9bh9t49392pv1h9kio68c813tlj0sndneqjjlj4aaarcf5p1ron0gmq061j3diradckn9ejv4eo"),
("06ct475nc7h4lvl0p4pebpq6ipurqkrhetftauf4oado9jcnl88akvl658a1m5pknu7o9qs83tshsr027ue1i523eqvudo2spkap7ho", "eh033m30rsjrhbatejevat7a9tv29e9mdn5gje55qdnboo59gmh6p7tplvgj282mr70tdpihcv9hbrkjfljtj8ddo8b99lvflhgrav0"),
("9aam5uq1qhucr10nekr958o088oqe71nfdd0l52hrtiue5cn3l7qqqfccigil7pgi5k1o3ee53u822754nrph2a865jglogipsq7sk0", "ek29hbd1g29fitt9q9da54d8blb29k3j07gon5qpj8m9hgdjt3qtfo5lvf2m4arqj1b69dj08m53p1i6jjahk0mlgfi650qaq5hugco"),
("2lnss8aevfvea1870sbkqo0ng9rbcl0na34ekj4eg907d1frtp8htt8shsr3jbp68h6cjgj6s03nq8jp8ghkogrpucjq27hk493prdg", "emhe4q4bb9mon5iotqvo5cd3roa49ufvlqhfp7r45nmnsm7n10053vu97ea3lfvmqtijutstcusujud8qlkj1o6hg7tgo5n26c1gni8"),
("craja4dkg06h204mb0kodm9smvptgh443p7bh37gf8fc71bthtpt0thdcj3k8ejsv0gsc5t1ub1p3pg86fbubfsp0i531uvkii87b5o", "emtqgmnvqj4d8pe2bnehevkpo0h4stoalpkfe33if2n84iu5l2m7ob13kvnbmmbcjtgh6um5ietvdnlha2uh8mh8k8m31mqu67nuacg"),
("tnlrn072krm13tsmlhcu3rf0ohrhvm06co6s6kdd460qdc67bhh4u79eq5hcv0ip3p5pla744cvurfpskp9hhpojvlugod38397obqg", "eq500vs71oudis6t2o941pdltnsr5v2432e83ast167qlktdrhcn2kc1s0hqh11459sq7ar1u7k53qh1io36o9qoid6tb5l7mnsjoc8"),
("4gd7ofrdapuuhvmrr2lfmi4ktm5v7tj5kdj63vft18qadpsc7ttl73p0catadmg1n1caht71rn9t5l6p5ucv1fiervonef6l1q3ma8g", "esnjh6296agi02t03smtgbht3jbf4lu506qpn6phh2nf83p5ge7cna9h6du044b896vkm0v1f4f1q2ejt789ot1kbcus1dgq8q27ajg"),
("337mqrd7tb08qtf24hc3lvhac2oe7int8jhnl8puj6r86g4bbvfuhhjebkjve8rte8n8ha1e0fu9f3ilnohps24v6eggbfb8289731g", "f0u6p14encqb74hljcvkuc6g5q8t2gcgun30h2g0jcoiu8ai561orkmsov6slmvcf7m7volcflu6msi8aqttu3ptao956j91ui0m810"),
("iq27u1s64eoldkurt79b1hii8j2blpu0ar6ohffqlg3qp595ntoio95g983sjvdqb21abinfpsrg47d6c2iqhl5f26736de2tc0oie0", "f2ekc8nloobotfraa5kpbaa4fcgcqi5vq13ifj298b5obnit5kvpset7l3joadbljvgm3upkoqeu57ro434dca49kjh51kvqlih7gqg"),
("l0pcnpp95to0al511slojn3du883iohii52apni3m34rcm04gq3h105tvspmc1230hd443d4hnsoeijvtdfjla878l0mipj7tk0hco8", "f8qsdoaf847rc8vr8io96g63n98089v3k1f2a7vtt1u7tuaoi7d5l1ngblqf9pjc397gpc531qht9hum4felte1b82encu8sshb8nfo"),
("u7occuu6la7n4o9553qd5gojekea9cpbmq90kcls5dkhndr9tfob908c6ubr9qbalnliqh6kkb515ltl2eg5ef8ap5rbm8im4psc1cg", "f8vkqe5ac658ag7alvjsrmmcpr3952dspo2219cmubi91i28djuggao4ik0ev5a74ol19itiduf64eiglenpg87ma3ebe9jlhaana58"),
("ffqpop544ep3hba8m41cd3hfubj1s3b3259dge3561t4bngke84vjdqettr86hsnnh93q68ccgg6tbiuf2bh4dbn211pja4goqakc1g", "f96p72pf44mdhovlsbva3ic3rau5qore98bmqq6dr6k7g2o148bkmureuulpasskjnmnu0fhos2h0krtmsbraclbiibjnbts7v949ig"),
("gu9ghtjb9m7snbco6g9fr40ohfat53h8mabb52h3ih5h3e6icimk5phudeam1l5tssmnff29j555n28b9brd4d02u61oo0j72q7djmg", "fdmc9k5pia2lh20uf3kdp7ra65l3m31g7q5mq0hk5blbpk6lc2bvb1hrgu43kmlcg8hrdtp6md6odcount5d6dev8apc0n36h3ep030"),
("alpeaa0uf1bevvr5jgeelp3ts1iqtg844bm47m366raa5lskqn28r68nokag2ijursih0inns18gqv2e9ps1ukp6k9l73vqre4s1rco", "fdmc9k5pia2lh20uf3kdp7ra65l3m31g7q5mq0hk5blbpk6lc2bvb1hrgu43kmlcg8hrdtp6md6odcount5d6dev8apc0n36h3ep030"),
("gd1f0fqkbntdhnt58cbv95dkejotb8fc4ta8jstdiik1slkb71lu59rqnm8qvkm30asbnl3amgkhi8963e1unlkqmjnable44c8p600", "fhtpeg78srgp9243pprni545ppk3doeh48rnr3i78dkthkdbrspo9foia8h07v9l9lrl2mdl8hps0p66phavje4cvjksgm1d8k3erug"),
("pnenuf688i30u5o164msiuk8cmcp1q0ggsmpfdf794gs7spjsnt2a3jcqmuuvee7eqi347g9ln27qfk49j3tbvlf6v5u3e9kj3g8ato", "fl2935vc2lf9fj428vvpjpchif2o44sqsn4g45ial5vmhk6ldsb1ct7dej3cg9hn1uv0b74tt0q7k9js0rvmukpgtf2k559t4mophog"),
("56bomba36nfaade1uoubfjrvtptr5t70c279r4ntmvmm5qdrdrqmfo9kdksd47aoqbheqapmncutggclu78gb8qg162et1sgt5pr7l8", "frrf4b7gp2ttg48tf5epbbp0nqqhm4e6hvl9lamiolk4j6rg3bd7a5equj6iunoengp44vfgavtql7i3jhsbsf7jvp719olk3sqgb80"),
("es6cpgnj0ghd60hqlde42a8loqnqm9spvb2jsdr2qq2ood3e5ntk8adj39q2cne9v8ijek6i813p4jcuqfunrm986ap6lhol7r76org", "fsgratfpe6c3tvtaj59rn5hkfb0ce3001o9ri24infdeslqtm9r58b3tv3ijtpkipqoj63ln2mqerk9v8lghfcnrksrh0lsv1olt81o"),
("18roifa6kmc601vptkipr4ta2f3u3nnkv5a7qkmamiqecfvag6gtavgvlgbrjl4681c052tuvee5h71erirlmotusl870o3p5n7bum0", "fv10apqf3qgl88jtr7u246js1pb811gqcivt6t3p608ja68mj8eg03c0gn8slsgtg1vmmm4e4mttv80b7ejl0qds53iq0re9si7nh28"),
("mp10fmsq6r91atsklkatpsvgjmobg9hdbujfkd9co9iqmj2esh01qp7cceb02bp866oh0skde9ml0ilmr7qu63ie60tlnml379lrbr0", "fvjl3dqa5h8gt222gg76irnejncjsajsb3e78qnqlg9l18pq4hcgvfe468tppflti0n5fknmdvf3tf4djrmfelnb3t3kk8spag5lubo"),
("4uk6pded7g00qaoukfub487kcivr061kqu7t3e83pq0gkck27e6ghlj7kets72kios2dths9gb22dsfrsq89e3b0n3818dqkruiusm8", "g1pj3fsvdh4m704jff34vvv0be3gb7ol3n9l716lp13cjm6tt4u4cg0kn5v84vr5fh0604t759f91jostbk5ov8c0ijelai3qtv8d7g"),
("7e824fprcsht0i3bdemm5nsrmhdusp71ksok4fqu0hfvjkk8ccrl0bq051osf4051bdrqod9k6h0nj9h3l6rdg8vre8c1vm7rt14dp0", "g4i4ppv39ur3b2n5nacskhv4ge6a1gqq9b8heu5orqeo2p163d4uscg58emmq62p4un2uijon5g0echn9btph0nek4se8bmtng86pn8"),
("01ajjr86b0d07r85odbcvh3hpotil17bl58898247m999vj7bpr66v7uqfocbf86hr5f0qv4i8d9ol98r6m4agucpmk8jhnubv9f9e8", "g5ksgvpfcvr9n48bi4ia9p4is8r59vi54r64428b84bv15padnfepobvhr6c8o04ccadekk05nm1tonro75o7nr8ucl43jg3nvsr8t0"),
("ts9r7ro0dko3ucvt4k5k3msn0jvh3bj2os4pfoh6h8sqc4mpcka66psr7kk1o5rihhnihe14vk3qcugap2i7mhbtautbbmh26j2hok0", "g5s498pkea3eh1m723lthvefemen9eudrgv68sf061jl8c4segfl8gn7m7naujrohc9kj9g866u4fe81imlbm4b8tra1ud75anvn8mo"),
("mb7dq4pol3tfgart30pb06gv2sr9i3rs5ldgqrtukl33nbdjpsrm8gfe3s0cbmsa1cdr13ndtokhqvovg2l21hq21emlpr56rafs55g", "g7vbi1ussbkn78m3593j6iabfsqj40o93va8rd5ksnbuldjv5aclrpbskqjor4vooru6nr5uqvbq50lc902vrqen3l4dhsgtiii0f50"),
("q53ot9j8lvh63vgv7d1695jbkgemd24fuc5p2d2itjf0kb9n5jbhnj41liv1hk0mu73t87qs6s4gq1oso7bbkedspnvkhfs1ga6ine0", "g8eeicv3gl6r19r10kqchvscu36ri54l253oangjgblbnucjb5sfq5uoa45s5rau6osi2kvsf5925t9qbed6krhltmm902i8fo4jbj0"),
("s0tbi21vi8cu8ev2h9dtu2v14phqe0o9u4oaujtls60bgptossddl5sibl9c8vmdopvboj0hjktutrnh3hvpeopu1b1lsaq5748g4eg", "gc6k7ir9hn8odv73dlgl826feagbhdfeq05ua7jm3dqume11lu4ud3e6ljdqllbv9jumh6l3j8k9mch0h4b651p9ipflrco0cfgkcb0"),
("9gr78v7o1vr9n9tbre1jvc6789m788ihvui1l4lg6ej3t6k1mcv0upcu9m7prn85i0mfuh32pmeae3fe139ah43ksero4kujpmccffg", "gdn1pf0v1h3ulbbgpukfaolu9i6gedtoei6739e4051rs6l1a1nacgp8oeoacfsua66vj9rqn831ig4fkfdaa8huhoo78hnei2sqplg"),
("fcumoocs3n1tr09mp5feda08q3v2ucc7ois2r39stakghc703m6rfll35uia99l62qioridqug2mgv74g0hhkef4cfqsles9n99j1co", "gesothi5ub6355dsfcne4jov69ls2mnplvmm5tt1fcqssd9p466tjvhqdubh5u6o7fn8j0ks2abd9fc39mfl5tp2i8nef2ggedrtb8g"),
("t7givq604d7jvg74qgiua7gn9kgjnpvnlnsob0e0ejgtti2qnifu5885hqtea2umq0bjtjv86vjjb1ps4ev8ol31uiq94304pfqero8", "gibusrrsdccjhs1hk1vmk18j0v8dv1tqd5ob3g0u5p376jdh5h84k5f1qnu5s13gmv8f1jiqbkok6nqfrirvb953ha164216bqse8a0"),
("f89374bpovgt5l7bgaf3ubhnvg5o7mek6pp3aq87l80udas80gc5bt8366tot3jmuth8ra6p81u4fjg6bb4ob04lriqst20ntg785so", "gkos82v8qgmvlat55hd4l6c9dtlipe68lmke3gnjp0vkjtac1h77n9b7prduc0u2oqgmek81vh6jh09o5540nvok4ccsvb2353eli80"),
("tfvior5t8fcacfqh645dm7dqu5m7uidm549igq6semr36th1vfmrnhutjhmmatr32nkpf5grl0bse972u86dlbl761t7sqig7dur670", "gn41pkltsalsekle84jhmdk025g6sorquijd0qsh1u579fd8s3co8ghdcnbu4oued0s9hto0qvnbilf4o29r6is684a6ce0a151bqg0"),
("atddk8jdiqrggthgfpheeandsb8fjjr8saq7ognf9oshbqopopmebtog2pb0ba2pub7laua5s78k9nuu9ae8pb7grqfvhq04b3tc538", "go62nl2cn8olt0h43ql9tmn49uiaa9eaftmoaj4jbutj4kf7qujk7mm7kjg07ctmno15j5f02ruci2pk4olfaj0gvuv8424jntcq3v8"),
("kqtj75hln3bdf6g6coenctlmsbbafpnjc0hg0mo80njk0s310g7of199m23n7elmasv97p5vbqnqgbh1ggqlh4th5n9ckd55aovaujo", "gpr05tft0qq29quhjm3tqhscof53kmv5kfge94kedj91fqj8rldd8d0jjmp0a241j94p4nknsc0ipup8csdnevb94rf45g737dag1m0"),
("s63aqj65ngtia1b1d87ns3qnpfhsk4st2jvin55982jmfjbgq2igb443q5m36qta5qdf3gs9c7icio2noard7retlh8tiof1apds6ng", "grijafkg0j00dtro1gkt0u7qbsovruu8srl3955uj9khturo78j748dcflpa704de45srf69gg4p4h62c0tvg9iv9f85p6cpbabeeko"),
("jr2qijd1frffsd83u94obt2ou9a9kajrb07aa8bikg8h76sqeib6uecp7n4mu04um47reo6pne8pj6tgghp2bmec1bq87nojub54eug", "h3o81dvnhtivkspcgnsh4gm4bsghrd5kq0e1eg9q3lltncicm3a369sua211nll5qg3k2oboep5091rmhaocuc81ceohd3roqafclkg"),
("d3ju3paus1dd3iuumle85do4un4dckhbs581ere42kr3r0eaqms33agk6jek6oaitl0ufek5bcgu6ngdhq6lhso3d7teqbp1qkkt9r0", "h438k9mqvfme49fap80ffn2p3of1vr02ua5ud1ks5l124e56eekoqi1piuo7nku68jesppak5a8tubaj9oqetpqsadaqp86bn716ipg"),
("pa9ag2lrf68ggh2o8dauf0udb5pc53fft7h139ha509bkgbiaolle15e4kvnq9npt08lkaoaab4gv60fbrfk8n11mh80fiopgpdbip0", "h735qfdgbhdvct48gj7bl8va5r9lg0gmc481l8lrrhhb19d7il1fm6dk8g133fvsmr3nejfjtbacvjpbgq8dujnib382cqmi0ea0r6o"),
("ktmmn3fu1p5uidnsaqu31qdvpaqb8v6i7qfhvg2kjo6ifnjlpigiob7l79jb6t85cboqch2ivt7ra2skqeh828q50cflf5htbmldaog", "h8opip6n9hg55aj0ppke2m15ll90cn4bqdvft2vijv976c93fe10ihcud0aer6ck48bntptot8j8i5kph4mcsl9594d6lntvaf253c8"),
("scvji7qq9qm7ug0cio7iaf7lontcoha859706eqhu2j8h0tsrihdpbdhnqfcs406ld63kjspapli2v98gpb308mipl96sdokcj043eo", "hal1r2fshmir8gj3ufqk1ob2va3im3lc5q18gcla2c53cja391v1tks71m1roo9i88iq9fcat8av1jfq7kl2rr0m635jg36v3spv7vg"),
("jvu9ukbuv42qn4o44p3t8o6dua2oeam6b9ushh7pheeniq4f7snk3cs7df9oc9lafe5jir880n3c09peoni572sgd9s40spcmd8s980", "hcnrsqk27pgphe256cn6gtpoqkid1157q3nhd71k7a495h6m5d3qpl0kj0r87fl45t8rsq98bvd01ikm5lgtm119gd6eebu9179tv6g"),
("j3a4ra3cnkq6bit0hcem1dsnk25ig9auo7rgionj7ujlb4n87nm1c0kk3va1i0h35ttk6f0i2hccnhkpi6r6ik1f9kmrns4957htn4g", "hcnrsqk27pgphe256cn6gtpoqkid1157q3nhd71k7a495h6m5d3qpl0kj0r87fl45t8rsq98bvd01ikm5lgtm119gd6eebu9179tv6g"),
("jm405bt21j1p8r5t1tloofgem6vndrqh247dv84lug6bc1lem31j69n4g6c6b9ruhmekfm0rre127acun8a6d48r9k68fn4q5q8edb0", "hdpso3br8v79n3a4nht0p6kguu255hkncmpqit8erge1dvo5147iad90r7kgn05g3joe52svn5u5mn83j8nc3vtmtt3t3bcvurnvjfg"),
("l1p4smck6t16cia0rou9vehgrhkral94o17gj5dcmasg431um0tohr4ej9r8dedkmaof94n6ovsg51ltjt73977vd0puag8ukkjtssg", "hh0qg86kvp7cfn483914o308mmev2dffovt5v0mt4gaf6i93k269brje5pajm5lp6hf4mjj6v03e7v467113jmif5fie996m1u1qjso"),
("fm7vajb6j5scok639dnh509s1h6ggctgkm5rkp9onrcjv8e4jb82pn8sql2apo8j1vn9eapne3mo5fgt82h621ib8hdl53dfat8k8j8", "hirh3gqkhangkq5k44ma4rqn1i39bluana89l13if2jjtj0k096liba65q3bqffs27oqlkk785lpcao0mdsv4466qu6vpl8m2up7oi0"),
("6juig4uq5nus57smh4e2h2rlvoqkj1lp7d6b4iuk6qir8h5opfjqtpt9k87s2i8ae2mhcst4bvlbkj238fus5j0677pt1bc62bto3k0", "hirh3gqkhangkq5k44ma4rqn1i39bluana89l13if2jjtj0k096liba65q3bqffs27oqlkk785lpcao0mdsv4466qu6vpl8m2up7oi0"),
("u84fr1nq938bjqqft1ar012c4btnuhj7k1h1i2vnv0lf09tn9kr9bm6j1u1d7qcmh8gcsd9iiv22chdus97bj4ft52fs35t66bp82j8", "hlnrt4fr8bg3rd6s1bd4tigbodgalur6d3piq5jrl5f5lvisppjqa8no2sr4chs74la0udm4co6dftgiiniio51if2p8asg203jinfo"),
("hiu6j8v7n7tklcho6iacegkno8nhocogm7uf6t0dddm1936mf197gu6s9m1pcjn6f6esmuao809frtil1lueosq5fsfhpg1700n46ko", "hlnrt4fr8bg3rd6s1bd4tigbodgalur6d3piq5jrl5f5lvisppjqa8no2sr4chs74la0udm4co6dftgiiniio51if2p8asg203jinfo"),
("9jjmkd6fuvcivj8tpdjpmb6bt2g9o65g9c73a9143p3t5pdjd48840f0ea9o1rtbgq4iekksr4mdpk71hb5n6jn5teuto6dfcrpgbcg", "ho3dmjdp6kc49tqa6gdqke5tir35ai7n0gtlmsunmbp34ijsugdtfvg2dems3kp5b8ba99h40j55prlver84kin4m5cs8lrsntlhh90"),
("1tqhetpis3semgpsqrhbohiovk82flv8d4nuqh9kn6stct7pi02mpr5b433eltn0hnltk6hps9mdf0u8l5kakm6b6pfcmr8dlmdd0lo", "hq72fjd0nma0suoehfglq1rpui6r1vlv3l4dl6ul71qas0k84ciud2r51bk88fdgfdf58s6d35vd5j61sbe5do4vb1n56uve7drqtc0"),
("al79kl71pgpq7l6qq6crsp6ta2vrnuiaa4oolh50ol9lr1qt7k8bghq7s64m8sbr2j9542i610qtragr94ahb9b3dmcqulmluainh1g", "hr6neelab4uqkij0kj72fi0cjlgpb0pia8e8qa4jeef1l1v3nppijd68ivgd4c7vtiip81bai9hf0hj8pgm5vh302frgskdgefi060o"),
("8tu0kt33k39eteo9r2a78ji8kpkdm9sqhf1tfluehjuch31u7blqi5m8vfaduj7mppetjkkgnlp1i5hhmk2gd53rceaihpmjmllvafo", "htbuuplbad3dqqkn6qrpnt3889ma1umq7g9p33jlu377quc0c2b7bsnuncsfqsmdq9ic6v8ui3usknc23acv83f58kilqoqc113v5s8"),
("nre2ui9817vbibnchr88d7tt6ot4a946aofb06n7v024ev9sr58opl8qd4i763bd7u4q1vf0d5urv509b34mq84s6j2nodbbinh7d9g", "i0u0tbhdt0c04vtse9pgo9lolesao68sfhrdt66b0nf464n96jd9ju5s9lah5vhgopjes93hu2odj6r981h7b72q35119a25jb05f68"),
("p8hoecfagjiiml7pu4vrhao88q4g7t83qgpcfvtq4mb0tlah2th0851ejtddu2gpmrjrah97sj3a7ger33c2nhqg1cri7pojrq0kjkg", "i5a83tbis7vrlrkj89rugne3pfe8q26u9jjqlftaj6uhoiag4ri582ubq4pq2melnds3mgn4iig4bg75vsb895pdjanahs0s8qaa130"),
("5oua8j181913h9hub3p62ls60rb4m117dcano789sgna6f00hk3g0ej9pgd1fuai76cqffmf37vp43kc3etv2cg01ikiqcr87cv46d0", "id3f8p8390ho6q2nlrrdh7uba297b162lmqr8opsaeh1sdbvl4mpflmd6i7vlhgb4jirnfjn6ps9uuaocashr3n9tbs0am0a57e54lg"),
("4b0cgca5bl9sta17uhcjlc41p9tbkq6n9cgki9b0dhgh8r74h0f3rle835qsetaau4lhcmjk5rljkkdpc3utdlprrhpaf1b28u393o8", "ifbn2omo2gntbk8blmbpch4u21lohcdbajodl8ucf1m34d3asek5lfmv8uap2u7sc76bjadk437tc9tk78nj1s3f0slfppr8ifnd3no"),
("hfbjndlih53nqe6v27ggfd8beb40pg5bhrdqd2rha4uaisvd6lsulp76b7ei3ci18aen50b3i23ejtc3uvnr8u67ctl4nfga3hkg3e8", "ilumnc7h124cv9te33j1nfidu7nl8jstqd98qerk0llaqid9ukubs2v15s5jiv0qr2an9kd12464hj5qogc0jpao6k6gjtvev2e3m50"),
("b2cfhs2cof42g846uesqs5kfver39dkc79rdsev5ghg5os4g1oto0154aj3k6o4fmp6b0il6cgjd6dtqdibbtl8bkk3se0r4r4472i0", "imf1csl19n2nllpgnviqcfqlpf4rqc6uu53ggbmnaejofpen27imrpscg8lgatge2t86um0rpp9ne7cslcuho058msibv0iihi6s3og"),
("mh3e1cttonp8tpjedb5l1r5j11l6h6beaa79d75bo0p5ubd3fe2k3qm4j22pn5u1cu9v58o0srmsdvpfk3ojkolpos0eafi00bor980", "iodr11v5o0jp7a96h93pcciibh1vejve9992lcofr6ked07bqbscje2o8b3far5m7safteo62ofl8ru5s0n3eu424lo0aji4s4mn9ho"),
("g35812lh32de1ngudsi2u1pf99lot50ellsjs9bt51qva5eii30nn1cd3tioo7plsk9kad74ehb8gp7tclpafru29pns4pv2s3rekg8", "ip4fe8vqvf8i0g1itumnfol0obks5vfa2kki8449bqhhi8ugr962cvo6c73k1vhc00k1r83u3jva0tbjr6g7r329pthaqi8r6grh71o"),
("l9qoccnc7ar44dmillhs77uh94dqkbfs63iq0bdqj0n42sv80s5if8pmkpdukjf4pedugsgqvukvbk7ba76n3ov794mn2baui815ctg", "irv8h0tqkst8fatcn96o1llgh7tn7qfaooe4h71aedn8g11fpvff4qkutaroj24hlo21dnqnbup05j53n7i3co03cs3pnnvh3b2m56g"),
("sbjmino8mv27mfkmg5ae13ap9pusiu6nar3gbgame2n3nnggvfutqsh4pnph0v88i0rksv69ajiqgdg006cn7fb5h87g0ddr5lbhjt8", "iv31oa278cotie5og3h3ke3tmklsopu0qf3453s8o1slbor9s9ove7nb3hddhfrj1akgrthto07kt2ondl27n5aoaiqgn1dn0lskri8"),
("7cgal5382ld8vq3v7q5vdtpmkoci6o72n0gsh6oledb7u32pnmrjaaocb089m8vmjoqqnfpk7d0gov1ccthn7nolm11rr2tsis16hsg", "ivjcn7doi9t68p4ch849mfd73a8l461o8fkme0036cb3a4tsnmnbac689ur5bjar2let4dbpcjlu5aigteg5u0n8rqnu1jji00etbc0"),
("p05hhnoe353rs6huc94ptu5vbcen4e2bo8kl9mbe087f5jpn7utb5a44rpcgrb07vaj0lh0122k5345at94bba6rjjmvv5p3a8t2lh8", "j2om1rlep46nj832p7evsnq3d03fri4h2uu78506ak7dk8dckud4871upej702k99dj063t1qjke7qtitirk5i3b5kr876vqqj38bgo"),
("7pop540v1k5174uj08np86our51735qhkdoact1cq3udc0pjoeh5pj7dh40sp0apfijoj5osvn2um32l2apdkht47gial2dts2sl3g8", "j60knulisjbl9qt2elas38p11cesdfa1okff349cdj1rivkuojftvi3knlbn91mshjlp13fvul3d8edjg7ue84q5t5c9jj4gbr5gqn8"),
("t81s7apm0flk0scui6ap65sqmoom6em531c3fo5r2iivmddd2nrll3m2v0qsq4s16u800pq430guh3iejorbv6ko6j2accsosl76ddg", "j6hfl820uhbq53f4ue2gr6pgl47bvcjubkrn686o9v3ebp498lcu82t4qeipkdd525df7bag4o8bfkkd3qod1hgkd37hu28afjo3dlg"),
("801ji6h80pi08gu4n26ai476fk8406vaaquo5alv80nhjlb7421hf5tul7ab2vn273tutqri45q9u0h94sitgci4ee5m60e4uqd8328", "j6hfl820uhbq53f4ue2gr6pgl47bvcjubkrn686o9v3ebp498lcu82t4qeipkdd525df7bag4o8bfkkd3qod1hgkd37hu28afjo3dlg"),
("r77uo372oimfnfpg7dc4j17a83uhu5ijirthskjkr8458qvp301ihfch0e00sneb2n589fmpl8j310mdur45ipf64n5kcr1fnj32pg8", "j6p4hs046ualv6gtbgft046bk9qnligjc1lmoioeeot55o6pvkhioie8k5v1hc9le7396hd6ingb43dcgv5310p272sb11n2svdld4g"),
("66ke7unkiq2sp8og3uupgk62ch0d4vuiidjba7khtbipis8j8ahrj4rpjvhg0814dcmdduhrre1higj3cj621gfgd5d35c65d487cro", "j6rqeg0n5ufofhmsv0a9uifjgjm7o993jc56kdbs6tbu1f5v90qt407g5aee4kud6eat9d6049kacrp94h9a9rim7nsfmfofirrq3eg"),
("nabvub4s8g2n4b31as8e56cr39tnc3iribdenspaagork940mst0vt08nt8s2v4epbtcsr5k268pg6n3303p6ajop9dbg2lhk26i8d0", "j8lldam12a4nf149rmej0cmn1cdl0m5lsgddre7rbabnp1co42tqgd4gavcj9vkk3vt0fp3h9ah8ip3o1n8mapk690qfoqd7ah5l1uo"),
("asd7qa8s6lth7g223bmhneh50g3v9f2r5ugdf2sgb7a0tbms6l6mbf82isekotfnn1v3lbt5dp6v7ua9bnnhb6iuaf7i60rra8g1ou0", "jb6v1qvu1sf9ofn06iqkci7oell7enarci2q0gjpvc0mrrudkro6ok2cde6jrms7i8f6g6g6f8ooq5cal30nkcl05qsl0o77j88hni8"),
("14dm2eq239d520g1qhdunn4lqhbu1pnchhfsl5f4a86jmge83k0077ipdj334qprame641h776qvamj5kuj5rqc33roq2fjnrajgepg", "jb6v1qvu1sf9ofn06iqkci7oell7enarci2q0gjpvc0mrrudkro6ok2cde6jrms7i8f6g6g6f8ooq5cal30nkcl05qsl0o77j88hni8"),
("h0cc77s4o7mml7kt24hvs1gdetv30gdc173vqhlfcm1favhk3br76l2c3o1v8l0c3jd1v0c78q4eccscl14coal09cuqel574asqt5o", "jc5rk0tdg69rajvglbib6emb5jm40irm6um5hl7um4qdhl3lvpa52nj2ogv5p3jrl78t88c49mh3n8ccojc3h32hmvu04elogohcejg"),
("br0cthmfk1u0rtmeu8onv4qn2k96e6bqe9vetcvatl2od37edqc0qgss8i6orkn8o5rt9eq12p0n5dc0nv6f4bsacutc2j8k8jnao1o", "jgteh5ic209oiphc687alas6hmp7gb8dheonmmreoqkvboe57obmu19qtoiqcisqo0v6m0gbp12o51h8p6mdpglihhpr57l9bb9kjmo"),
("9p5jhqv7cujo45dovnvpg644girkjg8eul63lobt0vtv1s1mq37qb76f8ccbjg3hab8qm3bnmpc5b71hslul0bha8htj693vjh8gpn8", "jhjf76qacbl7c6hh08cjfs8tcbittafr8fpg4sumucu13h4mc4rlqgob90kd5e34juecap5b7hldviecc9gv0rbqdft83e2ldo6p0bo"),
("qrahvakomhfgei3uilgftb0qroierlm90detvd0ujn0ctcegp87paa7a9jcq41gn98lbdm2211eof4m4si30pa1chf2ghl6setfg7og", "jjr2etdj2h4o4fjafu4f8s4e8kkraqrj869cub5ek3ugd3qb3bgdn05j2jkml9a1kobjlhqpbml72n1hv0o8s5647ft3ahcg0fbug1o"),
("35jhm261mfuonouhf06fercdhsd1bttqngcig0g9q9n4vosu150n59argb1tva6m97hejoltnktlok2jv5l2q0vi4be5n7v24h55hco", "jmcfebfiibj95n6l44mo4oh478ll4gpagj7m503fqes3vj8gp3ktiflsf6ieejvq8au078lf04avjp1eqrv28bq67ueeld1m3eof4s0"),
("o9c34uabg3tivmjr0n1i2glepjljm5ndboeudaaugqr4kpma5lcgqm6pq7fuo7uc3h771192q4taiolllh1cpbvp63gu155s2b89le0", "jo2kgvpevoshf17ivkl7onnhbv32k5nsgjq1seqmcujjf6g40hcpbvkrmurg8295deuc061qmfnemferbg9k57gu3cqd211vf1d1d8o"),
("3j72ksc9f7u39vep3jbll30k602jdkh99s7untmcpohkeiv8orrs3dk89oqetcdh2bl7p7k8qgq1ch7sntgu6eiu99mg37nsq1296jg", "jqrne4cls7ctdjgks9nq4tuj284q2kaiatc54qidq4l36ulg1qo867khjs63hfcm5ea5j66b6gb6u5h9hpqk3hfdgmrlg71vg593oho"),
("v1isfq2gjug91fkg7dcg2mn5efnkn7o6m7c1j3dmomju1arg22ti0946ap7rqk09mf0hs41aol7h4u7ck3r9l03pmmcjrguflphe088", "jqtgqgk955ephf1v6h2kr8noqjk1ucdoj1ni38gdmp648aas3484jmsl6d6bld3gn9h8acp1mc4pkgegmh5n9tq2u89maju6229qgk0"),
("d0ptrgkhgobcdgg9in1fi5uei2lt16ikp0orsmgae6fi8jdp2u466d9ijflbhn8e6hrjkuc3auvon663r0jemtb5u8tesvot2mpm4k8", "jshcquf3e7ele96fhum5gno5m0rbhqh4p4hbjqpfl10cciffrtqsjktfj1u9a54p20cis848vsfm50jigijfj0ihp6in0on17h75b58"),
("asd1knlnrai5p439b3b7qj7r7hsttdoodu9foinmlk4mec5p36le7am0fl5rdsmd33jql16dfltqmkbt2b4ltno1gq01tc96cd18jf0", "jv96cn6higm0ahk109m65okar765arf544hlg2vpovbujmi0ufml8caep6daot352dqea41ctdngbcv8mpfd64lfq46bha8d55uq06o"),
("anbi8cj231thn2rus9heud0l9da8bd6irar50di8u15998mcuog5gcr6mhve9993tjqtat1hvj76o4qr5crc7t1kce6abddg86mdtj8", "k1vjh6noccql3eum8lfvufk40j9mvqlcb3h39sgtqghg9uevm5mgm2vph85mqq323bj1k2qbmcqin53lu53kp288qn5dascn2boqs0o"),
("0qcio9icjdqiltnjpci50u9e2f31urbb1480iunacdvk4qelm92su5e4hci9djbg34gthld2nnl4b73f8eh66agdl7o20ler59192n0", "k1vjh6noccql3eum8lfvufk40j9mvqlcb3h39sgtqghg9uevm5mgm2vph85mqq323bj1k2qbmcqin53lu53kp288qn5dascn2boqs0o"),
("q0k8ms38tikqng232cv87vi8o4330g97ieovpcal9k9nttkk4c952tfte3vi0qvmse279da60q3j1h5virpv76kj5jln1ojva5njnlo", "k3blvlh524a45klmif3tofa909ant29vaprqrvv1jqbom40v274bs2b4n4akpcn1irbrls3072r4gv6gkvvhf4k0lipse9779eqa6fg"),
("3nmfej267gepcn3tvlfccsne211r723t6lruc2egh2o1fjoafcbt8p6ckc2hkrgm8d5qn8apubipf6ug9uk189167smdl7u96qc6kp0", "k3blvlh524a45klmif3tofa909ant29vaprqrvv1jqbom40v274bs2b4n4akpcn1irbrls3072r4gv6gkvvhf4k0lipse9779eqa6fg"),
("v8ren9bup55mnnepkqqtf71hiqputvv8iqknrqi2m3281t95tgdu8e3puk8gg1ditui5v5ngkjodic9rd1l5knean41tuto6211s810", "k60qfvgqnl3ljrmdcmle2bolmu8g24p5hk9u4mpd4hbt74bmbihcglap468ebef976b2fner0n7p1p1upbkf3qp5ecu97g2p5ida1ag"),
("dhisohk21n015jetd0i2k9mef7e9rrtqelohe25r9lcda5s3019u81sa81vureect1t92e597hiuucbas59pp807vmr0utqdmllbv9o", "kcgig57jdvem9h49vlkg37c897jjf9784mr10qdau7o0ujq8mh4ja1gh1ddf4d3epl6umee77fhopji4nsc4pc3ihsangrcjqd7arf0"),
("dbgobi2dj8kqbsj04l2n1tb845fmh10p9dipc45nbt86bdvs5m4t3o72t4nq9h35kq8mcpoklk08u6qarviviko1oidosj2oesqiki0", "kcgig57jdvem9h49vlkg37c897jjf9784mr10qdau7o0ujq8mh4ja1gh1ddf4d3epl6umee77fhopji4nsc4pc3ihsangrcjqd7arf0"),
("2f2chd76vgjvtblb6ng1gr8sp8pj4v5o5tlrbckpbb54qiudjs13aor7m9shg52pp1b5vh75hq3jemtge8iq2dv1c3pqvj136lcres0", "keia4v1hifdm48t58tprlgc4e39unsd1vf3t1ucqvpf7130sdp6lu3t0vpev4qkicvqgk02i5q7ijvkqlr5avmbf37pvmnapt8bq8ng"),
("kbhj9tlesuaoji8eg45s259vrvppthvo786t5nc1droaai8adburoqmv92j6vr9jn126q5bcao3ig8394h00im2fgrp50l40cm7eufo", "kmv5ce92g62gneo27h8266aoifrqrlerpqktu1v9f2tav9eouvr4bdgq6m2p6v6bds4no5a7op1057fogqpaoq3jh0vplf6im01kh1g"),
("d4utnhfkfa7enu3io98r0g9eoob29irin1347oodmvpdkp4m4pde27im269aa4pjdgb56v0m0e2mjjc91e9mr00o98suh6j0dbtp5to", "kof8d55u33ncnj6spgpao1e3cir42lk08d92jv4o4o9uas1ucgrm2h7j57o6ro2vog4lr3e4uf8lath2sgvg7qgsk6aima1b6j24j2g"),
("pm9of8enskls0grg6cmnri9j1lb68p2ovtv2807dfgskirfivsrse4dqter5hsa17chruq7jej8n5s9a6tk5c8us50ahb6tjvb2hjl8", "kpv569799jjeqlbu5d3nqg7uo39cl2frgu55f1s0ecp47d02upmm58220u63ign4ugab3t804skfnh2vluv0gqgd2qtnaratqmu0mdg"),
("rrqjih1tal0gr0r9dv04hvi7jp70ltu4ni0iia66o14dutmt9dukf0oqsuvqbqcen3r7nlec43lrf76tbkj9r3ckcladngdgdsl7l58", "krmoalaefhs4umdbv4p44urd5v7uf7jteh36830ghhnm09kiq24herppgp9f79uni31hlckvs6p3d7esaoo5deot3kvk982ntjdo9io"),
("9sivvhd43r3gru8m9avqpne5pdmgr0d691cd4vhjqcvdj3p8n5birmao5hmdne71mpnegvrue52aqrlbtv9n97saobafo7nmh0hbflo", "kvb929el0d1t0bh46gubtoerl1edqajc95eka3m2b5hqfjcld79uptqdlfnvd98qh38rv2oj9o9f005k51s6riokjnsv6kpegjopn6o"),
("vkbgvt6l0aagdbte35e3g0ndbbqdlagjftp4s58p6eg7o0i2dndti3k4623tk5buoh0nr9e816k5r3ur7kq3b79a1bfrspsbfrq3of8", "l4h8eum85gr5mpektr5a447rs9b2de0d41041glokkbb8nheeoof5utl5odhbrf1bltclicrml2juph50ljsce8ckij44l2kva8jen8"),
("1900t09jrbkd101s9paq650i2o5md8kpjjikbn9e525lc4u8971dec0eot5nhe9kmo39k6dg2qs8bocjvem0eiifdiq3mpqfgenev7g", "l4h8eum85gr5mpektr5a447rs9b2de0d41041glokkbb8nheeoof5utl5odhbrf1bltclicrml2juph50ljsce8ckij44l2kva8jen8"),
("siq0pt2phoa3ptu58vi13ncq6g91q1dsang1q61ipn12i34949b2v7gvf63ffe540qsloumu8sesb3gaq2v5ksu7iu92hodktr3ghv0", "l8bba8vnagp74cnjs5cj7bold488ns4is77nb0o4snqaom4om8mdpmtqerv5531dmgtm21j98ms60fm1u9bjfgu9mba3q9a33bscvbg"),
("s3hurcjf0af53oq7u76vv7oc9e68rpnq9gkqmpr2rql5t4up1teshq379thsubh75imk88k9f54efogdmse9tc1s2o4bu3qlogb0ij8", "lb9fheltjim2ohct3pt9cq5ob4bpoec4psi4eb4msfsa6p4c3t460hkv2o2a6d0207idrd0vlv3cdo6kn1g08fgalhvi55tfnn22rbo"),
("8o3h6bhlrldm98elr6u1m30e0j1oi607n6l3fuj7nq5gqjlh92ufen7mhgivsqujse9e7g1cuhn9li60qgqphguhsv63so1a3s79s4o", "lbb6ok490c4hnc26sgrt0ke3roirfsr43pkj360o6tjti506a0767a7s5iiktnafq3ca3n57basa68dc94090vlb4akra0t94it9fv8"),
("a3bq0homnei9qp4ckkec4u8vrcod19ln0q8r9dkfila175btbc8ljr6dmc66unhln0t2m739leov407ghfud21kdtd37di6ps2ttvt8", "lcsfmk7f0f7i5285cmbhr2td9th5ud5bujq8hjns6t4q1kfjdt77qj89fupeclmo7qmbblu38m0te3dftlhvaq08026hdah1gjsmgsg"),
("n6ndjpi6cmahpcn37b662molvkrro9hi095hn08audfen4k217df08dktk40tldvmqqliqvciclval6h02ms68fbu4ogfet592up5jo", "lea6c4igvgk6l1n3mqi800a15hv53lqd7mhnqrfoc4s1b147hl4u215d874nrsdhpmfbll1rdh9fliicngs97h4k8vlcnp3i4riff88"),
("1m3c0tg63hnfsv9viq47rpfot5n36vsks09vs5q9bm24nija3met5s936qvkd668ckl8ca8apo4gegoachhs3isqek5jbod7i2ge3p8", "lgmoffe4hdpavncdb9ijr2q5tn1pgbv3ojh5142vet9rlbbdff7j9dpfpu2vg4d14h9i08h1j1nmdjun8trv6f8oduh4ontphk24pgg"),
("ncfigp9b04qmqv5euob5vcr6lt958oav6nf7v75i6ogiimp8rratko5ahb8lijktfilk1368h2isauminqd1nqu0hcg44vqpjmp2nkg", "lgu7eapjdt6dirskgua38q9el8qa0gd75iktoe4rgjsfroen9sfsbcs68ns6e2hfp3bvsl9etnqufivjs6k7v1t0vvpevs33nj9e07g"),
("1dg85usi5h9jjq81g6b4s9a085uuhng8pqkm0die96m7bj9tp2j4die0uhnml7obp8doa2nbokd7ipqc8ckss5f3gcvc0s68vuccnj8", "lj0jdmnaev7k8i084tg44mmcpfdrj84dj7cg9k8gq6gldifo37j931js6ps61ebg365n4d9rrr8jc3mfhfl2q5nop83t2f0nfit1t8g"),
("80adkcabsak9nvqmeabqnfkft7vft3ktmckcb6a1ea9ff293lr6keb9qmig5kbc2g9ppu34hk5g3ti8i1fvqrlnblep05ph4hm9tmdg", "lp8r0fm3cmmjbqm0j4ju5e97ol2sjeglao6uu651l62nt37oe3pcl855crqd1bh9t6824nviqpnh5miftae2sm26lf8r7vm1nfnsn78"),
("o1hah70uptrn1751q0lf6tsekbe72l6f3aks8afavgg1qjspmb6188vuom7ip5qm9sibuojv8tn24ck27qhm1iqdncr9kgs5p3lrf70", "lpo8bccrva0aefqareg2rdmmn1kubd6he5ls56t7s2da51c7llik6v4au721sd3a6a575vtgg9rliiqnqiuh9q21001mb71kldrn3n8"),
("p0p64m84s0domo8hjq8jcfa0a6is2purmh3lcasuuah9tlo1n114ehiesgcp9uvqvokabo0pbv0dmd3vl9uhcd1n4mukvdi1od3lesg", "lq1mkgq144dpki4nb301uj69la88om46lbp0l63pmi4ijihhr5bbbknihnfrh3vt1oouv8upbm39brdii2g8opkadsn4ahm8r4o9v88"),
("m0vfo5obpgrmt5oproenr6p96ic31be4hmr04198ughqqmfs4svqio0f77ueb5cq0aph702fc2atj3qpmfp0lu8ntu8j0ivsm4g3k78", "lukebul8fnqh7khbuimg5v7bmbc40shurihl0mshb3mjb978c43nhk37mtfdj41o88hldpvfhsrgf8prlvv3grdkv6s8sktkhiom0ig"),
("1om5bhnlg74ogjbcgnnscaho1eojep99q3n1qb7bkmt4bp4gk5fjmopqdrcb8unatqvmqlmvsogh08t6rovbiilhumrh1kv0vhfurbg", "lvmcobnchgtaugbkbibta7m2ho4he57ffhcs3e47uqlra4isrbc41gvs1acilasuacs6pajb1jrdpqqbve29h9c3rr7bt22omo7mpvo"),
("7ravbakc0jjmic0paui7cndmnmkqdh0il9tn82svp76hv543c0h826eg06126rv0ha6okqu904fu162jk1be5uut5f63fdv6di0h6j8", "m0ru78s13jt6os9q21r7vm6erodpim6j3njdk1jphm54qkvhvpcbsc2jn47ipaa1mv9f1fe7pf9924njbd5mha0a2h0ra1k2j8vn6p8"),
("4qf8rn789evoa39p88bhbeqn24j6lp9vc2ffr1vgrm3itp7sdlrlce3mjn2p9tb2gs59j1cjttr94bjp64qknifquse7n9bqh6kdi30", "m17hsvvf35cu78g4it5mcuib3ejh5ap13370bitkv71dgv8eg47l1c94hohj2cmj50nh8j1ctto56smjn8rjs0s4lrko9vr7ish2am8"),
("mauu6crftsh9t2gp1g2blk707un7snj0r4ssa3m4q2esnecpari873d506i8pgnc7iid4et4bajua9i8hf51rpqbkigfpvdgmqvb4rg", "m1nft5cpr55a3ulve8i5p3f6pafjqvntn399jn4j95g9crvetepaq7sdoeoja37jn3vo15c5ddracr4nr3el45njbrref495it84oso"),
("ce1so07nje6nln5h8v2tbels0gjao70j4lv268a8ui47lj35algouclqfk27lqj09kbjgklkk7a1a4ng64a7cu8k977688mpqmc9cc0", "m1nft5cpr55a3ulve8i5p3f6pafjqvntn399jn4j95g9crvetepaq7sdoeoja37jn3vo15c5ddracr4nr3el45njbrref495it84oso"),
("c2miovsrhqd07ekfvvlk4mun5j8nvhlo6m69pi7t9ovmsfl5cditmf4lmh59girpmakrspva2lkas4sneqep47hel4k8ktu5gm442ig", "m4c9vq706ps7lg0u0fb9c5r71gcgpjltu6f294i57eepa3asc1mesfaae7isgvhkbg1k1e6d4c548crje1peof5ba0i6u50em514bbg"),
("t0k3n570s2rpqe5ch26v5khl2vd7cm32qda85l85crsv1jinomi7quscb0k75mc15iri8sfdfme9vjrkmp1bf7hq6p4qchij30p4ik0", "m4jnf7knnotqgvcafpbs1u6i62nl3394oj7a22ic720nvkmlrmuqgvaton4vcpvqjrd17t6h2jbdtbkneij7f023kcjtudq4qaepvkg"),
("4n0k4i7gq2a5vld7s5kpstkt5bie5cld27h6d7j9bmts5mtav20o3016q26n2popg4ssgl818abdpsqufd79u709bqe3qut5lpdod5g", "m5pf1np35pcveii0mgap3j0jb3ldlgh6bscp09fulcluus7l9pf7detp5mludlq21ge1uf4u7il6f3qdktvat5nv9e93m1mver7al00"),
("nnn87ilnjaksm292k5mdqvf7cs0mf28qg97cj66b2qk0li9p54rfr0rco2j1oj1p04l10v9055nnlb6vgb2ve5uvi112lhf0r7qcqq8", "m967eoj3ip56nf7v47740jkmv2des8t945tf14if14735d40o6i02svs3q5ug41ugl0i3n5qsj9i95eldgka7a6f3rrqku60ji4k3p0"),
("71sifrnhaququj6o37fo10paupgkeujsjjol0l4n24epdgu5ke5dq84vo9jod9cb38dap7j664qa1e96tbcf80fci9jra9quqddn2r8", "m967eoj3ip56nf7v47740jkmv2des8t945tf14if14735d40o6i02svs3q5ug41ugl0i3n5qsj9i95eldgka7a6f3rrqku60ji4k3p0"),
("dtpvfbgtuogcr54b1grvfneg3091h02civ0urvc14f25um5rglkk2pk79ov1t3br0kamutg7da3jbpboak1sgtecj6rkgiovmvpc9vo", "mdg3v25c8r2ee72psoc6k1bboii539abqvrheq74f6j93d9q6s7snmpt56n6stse6mnl4e94q34a30ufg5kt01hnakqapcpmd6cqre0"),
("erptsvojj3ui9j264jl5u0ddljt75337sls7lt390lnligath7v17k5od8iq9emcb86gcio0slo2rll3kg2hhevvomd4u9v88a5vc30", "mghbs9s2kjoin82t9bd6ose1ob9cmtrhohd690pgdomd65kb8alc0ad35ri272q6k5tj7s67oturc0gkkhf2ukvu7q3naaau1aiiie8"),
("fcpam3in47s182fe1gm85jdnirots0132viognuhuiqvpkn27i0t1rdrta7bqqv6qsiq72v2oqgcrc1rojfopc09roalsklbjbdeejg", "mhncs7mhch6672g5g7ke46bbg1hktujb10n77f332u62i349k51iavgbt1b5psivjrnsf8eqrpsaui5581ebj0vrqjvt8ufo3ovo7u8"),
("bbu2518vku8mikofgbj9q2h4laqer9pbvh7ifo3rkah2uq4767a65duucnbkojn73ggsadm6puk7l1k03i7k34l17qf0upc9agctk1o", "mhsuhepe7smn9kbt2jrmf8g7fnu475g31557gsq2m66i6ahh6bin8ek55iqda0prdcjtkit41n2qupum0jop9a9elvg6i77svsik16o"),
("g18u6b9h6jprnneg00p01b3gclm0vb2u7hos4cbkmapagk4vl19h9iof95idg7knslqhb0s1dq4t3a6r6hjrans91cahl5o7shot0eo", "mlsovgc8oqhs09udgt565ra8v049g55blm7pa8k7vhpg8mcu1ongt5dfhcfj4crkpfhouc59jdu3kuernk9fj5jqlbruio4j2e8t05g"),
("0fh18pohb9u7qk3clq2k70hucd62msrbboq2igl6jpkpe790kmb4lr47t8s8mb3uckf45lrggmvn0orhitgc4ckst1n60q5gvp664g0", "mm55dh2h6a95umscfr47hdsf8arqssq3hqqlq60gc1b1budpvab9ci0hger97uqer4utfd18ptd7hf32io8u3ibagtr4rgpm3a5g2c8"),
("ph6v7cm9mfjkd9av3secbll3t60pia45njo490s2n2l9qj4j4gn14p8efma51794qu36ab3t9rhb8db9v3cahscthu4g9qa1mp1daeg", "mo843h5i378qep2pvpmp41ag0u12qt1c83q2smdtimampdu75atha05pq1l8qg8etep98qoqht435f8fksg4b0np6acv1cuv6qrm4n8"),
("ouh5m2vbhvr1838j6eaa7sosk99jpg3mqv6erh90uc8ho3fgrfq7213s30l5024tebm8ds7u4u21kbctp7s62utr9v4q0f6o3hn5888", "mpci9tfmiks7d453m5ampvqfgio9be2eouth44mvs5topd5mkbrke3e4k1bc48e4to5q3bf75hc91544kosm8vjjglb8vg1j1dfc970"),
("h5de77svv6is6ak8p3cn9utea1mh68qt3urrsa0j7r933mo7thv3n3jpo8rtimcsp65q9h5k8ibtj9fpmauq1meqc2mqjf2bmg7le50", "mq69bie7ap9vdsrb7mu3hq8h5v37r7ojgsrbuan8gmiip84sa65lk89gilflf1cogbaa5pou6o68usdru27ft3408fekgah5jtp12f0"),
("r53ctfeuveh84ae8uir9o56lp8k65g8t67i7fgtnd56fnufsllpjjm0pkcvo4ad9njpt1uq9md9didts1cs83fism8f4q5iqp64lreg", "mqb18vuig6nhc2mhqgcs4om1e2aqjdvttnmbehstlmphhv0o9b1le3tnfmso8322nltl8g9ss293792ituctd9uk0t2aaf72oen2l1g"),
("giuqdimt9ive3n1o6kp7p8me94n9o3qgtb57up1dkrp79r2b2kirggmv7ivom5kpiq15f5v3hv9s2q1ienmgkh93df7jgdist654ou8", "msaodlg1iggsu4v4d1hds7cofv53bd9fu7blo9a9ktmttoljjkch2j4sjfngsb11nl4i03dnl7v817pmiqkelqor8pe3bhlecf5j4oo"),
("3i44k9kelkj35e01ipkfsqvo3ak3e84tcumthm37n4uv17c506i1jts4v0297mf248bgbdg7bucboef8p2r57mtptbeiki95mt9v310", "msaodlg1iggsu4v4d1hds7cofv53bd9fu7blo9a9ktmttoljjkch2j4sjfngsb11nl4i03dnl7v817pmiqkelqor8pe3bhlecf5j4oo"),
("sep60uci5lglkhtfqhcpq9eqn3r9vgp9756e7j3f2sj7s2c52i33g19sd7jv829euv771c5gs0kjd8iudi8905mb1t35ldjq4r9jiqg", "mt6i4nec0i72jjkq9eu34mg18dun9lcehp9sgijag5pqhakhe0eb71uv428npcc6ukh6vj3md5g2jbbi8vi4t4hv5k3cb6aes98egf0"),
("u2p6tbjjfsnijmoh7ace0k2cp252gremctgir2mopij88f85d8mtj37im7hl9casrtkol1cchu7d32b61fvfrn92a89obv0o8pll198", "mu537f2qn25ohjfrf86mlo3chgrd4ch53of17o6il5g3p66rujtlt9fvt0fbhrua5naq1gkc6v0a6dlrjac6muip4jd605tnt05g6o0"),
("e2mplnseigrpgcold26cdhk67abk1ja11ovk89eo6dtlao2j58ib61n42pciukt6sc6cegt20vhl63sn3jqricvoflkesomhtbknn0o", "mu537f2qn25ohjfrf86mlo3chgrd4ch53of17o6il5g3p66rujtlt9fvt0fbhrua5naq1gkc6v0a6dlrjac6muip4jd605tnt05g6o0"),
("ob9ro85um96c9436uif6s8ghb70ffe4jsac3pv3a2of4oti0gvcqk28t7k0mjc0itte0un4kvb31nquckcbb5j3sjk14tq9s930pvhg", "n0354er0stdhmcd5joejd2sikkt7vcf7vdlljal9a3qgk4i11vjh92es7rc7t7fn5k4nsvhssn7hgd2e6n68ahjtlmo7et48195ahpo"),
("p4fjhfr6dgub0v96qipgs4qkc44s4haeu30g3tod90u9f2uuk3aaqlvul4fj8onh3ks3quq4d0nup8uge41kbd39hcq9qs6evi2pp28", "n0kvlkogqke3g5gpc87ejsf1a3ib8aaqks7s6itsalgq1c56fkiu0vc3d3vb063f4ihie79n8t8sihc4u9jqjr3u77o29vtn0e27q0g"),
("8jl87d6gbe71hm0p2ecgq1jgbmhm3uj30uqa1m1k8gva1h8c7gjib21nmdlhcbd3891p8tm8egr43vnhi8bkqen0c3lt9jfi22sdfe0", "n0r1tj1ngvf7m1i7n4f2qc0am7em10m7cm94gpu0d0dl2gmoumgkbbeji8icg0k6tgo8e3cj4fslpqd6g430u0e57ea5fkg4bcrn608"),
("o05p7mummojc4rlojdcmliki39sqbv8bmf2mile2v6il8ophsh6einlsnfinj0dj2p7rpdd0hrabnq9gp77bn730mipa2opa9bf9as8", "nf9ff3oop88rt46vuqculr890ctq31468k9tgo0gksgbuj0socd8lri1jmgioap5nea4k35ouuq27p43l80ucb5u4tl5vpurh13s5i8"),
("26uv5138vke6e8d2qkurdcb3gj6lh6c99vi3uk2lc2r2hfamnre88ocpf5sc3s6hva4eg58b07f8l1cv0a96c215nta7km0sji0fj6g", "nh19lj8n1e87jvgls7j59m46h3m7j3hmkstthn1h8u85cptaj5h16vf6ui23250801hc8d0dd7bp4590je9k3h53f75egm06l8vg8ng"),
("ltp11clnoueenfqqg0q4is3dhtbc3j9bfqqhgfj4iknh71c87kqt9k94d84ia3mvhbf1efdqni9bis0kvgaa2h89hvb86e8m8sba6no", "nhgf3vf5a8s2p8j4urjplacn83u8gl8p5git3qdno139no52nlo3mvjltp6t1ddala09694ngqojj840qfp1t07lp0p7b66h70ppfb0"),
("79h3ru8bhq6trtm1rmlf9jbjufhrq10f78ellbiu4bjd9l6hvs8m6tc2m0eirhdrtjti37r5gsaa9f8dbhb22p1qnj1n8tnlr058ldg", "njd47grduif8umvdju0s2jt4jc2djqgtutvtfkgfhc6si1fo51rvaiub1f7qmtof65r90q1cjsq1pm4emkpdgsi8a0ngbhnvkeab9io"),
("8csenrkla8ka59f3hsj3b1ejde6gb3e23omsvmpp1m82762l0a8ruhfnem2vutoh6c2pbugegegcb9h0pss9nvv9f97auq7tk5veb20", "nnt0uih3uh0sk9iimp5v39gupeq5kfposk6cnp28evp79uit13oku2lruh64lme3rjajp5boj7reikuj17sia7l5aqo2rnp545d4p08"),
("s9hif4sj79rn1hqg4der41ukjhu8hlf52j6papkegna5bqures55hrqot9e1v3ampuf0braqs4geslcr5qja0dgtetoelv4ivuvlpog", "npsuvi6mj3c4pk3919s7744vpv2vprop5lu9fhkv5cnleib27d1pog1sif2ejr82i5ni6eg08mkd8lbb9pafqua3dmkslkusi2a9uh0"),
("i3p4964nl29rkmovlb4rfi081k0cnrsq468d1g207lde3itms13igsscpc86tr3t6m5mutmn4cho10mlgras2fv3673u4ttrhatq76o", "o1gkneq98a8soo3a2m067sc1d0i0n00fcpphne2d8lvg781q3at7shj3dq585lelbpmd4leecdomjlknjlndj7upffr52vcfotdtga8"),
("tq3skpmunelnmsdh6pellrh5agostf2gs6d64ofs4qri906iip06ep5fcjpb24ccnde8fhma8jgan9ldi43df73g6iscfm0bnp4k3jg", "o4b449u7jkhdgom96162klfotlbghp4uv3n0s1vcltp61dor88jhoo8f3vbhtk4nkuqmad2d625assjuplmf8smf0ua27qvu00at37g"),
("afee48n0oc4ur6psgisj7kepgrh467eh8c47g8pfjks8muitjd3s1i419v9oso81ota42isoe91q7bu4volis25l21ujt3t575rqvjg", "o57g98cnb4btj7j3fq3hclab2teavj6er1ns5tnbg0k8g261bk3nu960lqqqm5qm7m2ocaq83cctogv0hdffmqqtqkonto3ts9vt3p8"),
("q122dimlck3r4leuugke59hploue6mbk0vr1q212prsguuu3koiddi8kae6au8hcu1u3rsvafnor9shiqpdtobdemhu074thpl6nmng", "o5ahf11cimv12b4o47fqmsr2v338jhm4bkeecquscgk1eca79teg2ij725uiprsqn8qthuj2v8bhfah3ptc3i59io6d5snvbddeto4o"),
("5u04rjjj497dfsrbib7mr32vkf8tidisn5v0rcq5n7ppoc9oaun6cekdv0qu1jm3ih6ujaqqn3ghiak17lsaeq0c97cn0s0qcuk1cn0", "o79d03a3ljfapnqmejk7fp10f7pmh2976km8ijs7umtmvsglndbc10a40m2a2vgu64ok5178fcepk7b8flb5m0hjrkc1c7e0hddup3o"),
("er99caod34thrfeq2r66035ib4j2ep1ku8lu1nn0od10pgscc5tccb9dk5hbb044t9m8jqufsftrak0fv86aogshccj32k9g8u3s660", "o8kbedq1ol7iab60n6bul5h7dkodqefvpod47iqc8kntseaj467a37j1e498aunb0ph4eocccks1sfgvr80bq87p57mnvm43uhs2pug"),
("k6ms0sr9ke8u3p3d9tboc1mk9l2mbemkir5flh2fr6a9d2vae7crkt2b1vsb9b1bkpgfuk57vf8pltcklhvj34rcqldu3cj8tfpg29g", "oaaf6ednk53sm416kas3kp8noc3ml18a5sth8dinjj8bu4nuf1vcptrho6co9e89i1taomvf1dildgu92sv029kg27fn4qrdl8ocr4g"),
("deoerok96gb6gghfbf7jrmcevfrp4kkdj50m01k1a6m5ega50k90p3312lcjp3ct4el37poveriejlqh854tq4d21p1i486h34s9vd8", "od76hrov0f54n7h51ipv3de201s4fitsjglishtp655eaqp7smc65pg635pksaf0dbasln21dmd05gbnu2b0vehdsro1pscpme6vf9g"),
("7trpgvpj0il7qjptonq8p31bs82fo2vpnhc32if1070et8c14i0n2e4oef8uunno0t0r7dikcnfecjdfouajrq0t1g2j6nlfhlpb178", "of8ashh4j7craa42ejtnuivrje9pmvukkd918hi5uf2vmblmlm5lbvn0hrq8fo13irr329nj8778qtvq63mirss1u551im5blv5rguo"),
("36v59seedcflb98gj04cekrrq3vo0epuak8q3ph7jt2i77kpsmvg89dha68hlt69mvkb0it7a3c1dm7atsmdaeutsgfg8jfvu4mbr80", "ogn9ta29okbo4aoimea17k2fg5vtr6298s5nvuill6f6htsosm0bef2vfugjuffs9nb3jvqh1fd5bur9ko4kqkhedcptf98ogj59ugo"),
("t8ji5kdja8kosotjkaopmb9nqq8j92ksb2numejrc6eb2mdkv9eqjf9uco2s66ub57ogm78rsbh9m8khm16semu5olbbqikd4sq3tf8", "oh7fapf6nernn9aohffe9khshl99f59dan5317sbhogv88r1gsaan77aeca9or1hjt6uvl693sl9kc001in59sb0cn0girscvtsbbbg"),
("kn02hbrle8q6jr912j4ikkhvaf7k06no2eoim5evdrsg9kgvioik6cvthvadev7r7lmltcne5nfodqr69tk9edoosqs5gdessm9tavo", "oiu0d284ide8rpd23f1godvqu77d615v7d33b1sodais4jmvdvf93v35msml110ie49ion1svdunmaj8dca4a3q0aeke7i5jsno3vt0"),
("qnm5uuqnoqispkf1f6bu352oarsm51ph6ild34krdv05q1eba6r2r4l2554hvllbrn4rs0affmpjk3vau9b1rlj24gar70105i97tq0", "oj35807341iu6smqmnujeumovp3t213av7k506pkjp0r962n2ukuinu1qe21bmtc04gbb0ijdgvk7gdlejl56smumi9ied9nqq46smg"),
("pbll78jve1ucajih7475qtibebls5jm0tu320f4ccikbgemnrkif038kiq8ju9j4shgo539di7boa0cf69h9uabim791s1k1mm4qs98", "olu5agsoleg0qa76lv0apbb775393odi1tndepb630dqibemjlo0qi3s59aj4rgpkuik3m1kvihqfbnamukdpt09lc3hujqjkglkk7o"),
("t5cevt3j90ude6ram6j9jls7aaojmbiqdp06aid27u622hmd68sk3ohp04g1kvdmg7640fjmtr95hee7rdn15qo2a9ebc2h54bbsqd0", "omtib3pv548bu15r93b922l3ueobb0r669jm5e3b5v9vcntl2q660jmo4ugonmqsq8231pl6bl590da5239fsqb80bgfhplcl7o964g"),
("dg8ibeg1mnuna5o9j7e0nc05d9fnraehehjni8569q4s8grem80f6oh8rjor7prtrpvnh394ljd1l3sh6cplcqlqj76b64vpjvhj7m0", "oodj1joqsksq4nu1qv2pcf0s13uia8f4tqi6dk7e0hmtd8dmg70pdlh50umvicfjm9ro9me0jroq47ggcbim9l1fpkutibrh6er39dg"),
("oal1v4bhr2pmh9ldkokpif7u5gi5hbsfav1prsgck5ceou7mhnfi3nbghcgkaoog6fphp2qojjevera0qvgak81r8nu2q4ncrmcjvfo", "oqrv5t23e38qk5mguqngtc93l8l9jda9r2g8a3to5ecfqdoa86e3jmddrs8t49uhj47i8gsuuu9h7nd5g5k18o8j3j4qftap9d8a5n8"),
("sq8tesdev2u6ic1rc9tmqmbs1a5n9dpjt7q610157luhrmlb4ocpdbsfolk4ldkh27gqe1ogmf8njpp5ls0pt59fhk4ebjfcvtku9pg", "os15vti4bmbrlh0r094um7b1057e4un0btq9rrjk5ai562ir8ts3iu7ue6o9j9n42dh3ltdgokq106bhbtl5koj55nc2cl9a0rbnto8"),
("r51mup8kpa0ouachgetarnh7e1giqecv7j57jhdve6gtakks3p3icd28naoijv5d4ek7pe6nu7nak1a2v5c7ikrt5d7oc6f3uglsd98", "osvbhpgkbl3rf90v3v21hbt3kueoegjqe1o3ki6egerh2e1askgp46uqbj7f8haguioluf4ulsbgqp3ecto5dmdgajb521lfspqabro"),
("5joo8in309okb4kvfiua2bh34mntleq1iu2cmaikpe6l4m7embdj67smfedt89dvje9cljspejhdtj0r9cc2d2v3v6m7fk7n91nhlug", "p05tvatns8td7bavumf1oussa5qrhskkev3f8f8eg1u2cc2srsf3981durmo4pm1e31mlioauqet2cda89p7pr94ill13s8infuepl8"),
("5i15rcnfermvghp7p2b2k377bbc5jdf1p01nfsuv8a6dmkcuhsu1c40gh3pn50ofsae4vnf578j3db2faaunkamklhdaq8om71jv7to", "p2jusdtite33duft6i5jcve3rfcoelnkivvs5q273v8cfuau9ighm1k9b8vou22le3hrba5hfc1dvi4blpst7joipvsu9g2moidb4o0"),
("2l2apnt66lke2626a1n888accq9o110tkjmegul3ut2skrjmmcn2ht3lfg81q69oagi9h9akupoc5jo4am98cb33lmsi6t0i8eh03pg", "p2rua5fnvceln8uq7v5pf7dkn4i9563oq5nhguamj39a4cl1sfm2asupberg4m3so5782nb46upcf1i2ohnqh038mqbqk5pdtdgo2ko"),
("ujhbpk4mdteg4b1m993r1v940vn0pqrjhpvr01f9nhmi9548klspio0q53kto0qqjuq0a6djub3lqtlalc03kib1p566dqc3ckj1jqg", "p37due6bdtcp1maf7mku4rarqvfl0paigu5bj0bod9vuj19l7pe32h725sv1bmf4ts5pnponpb6mf1s4g84uv7lg49lcj9tn7rghdgg"),
("2p7g40grs9tltnb6b6s8eqfs6ti7q4d5gj3o18nqh1nefvjomnd5s56cve35do2v7o9ouo52kos07ts9pk3co7k3fa6ht0nd6i5t5j0", "p3echaauvt12jcuthcua4s92810s0cd22r2or823gb57jcpc3b70jlfqb4rhispakgnvs7lj5ctvlc53giiemvp2lhc8jijp2ts07jg"),
("07ekrr9972ppknva53mlllumf4gkop2lm1dm7p766rm24h4v1qahntptm8okbabb31qc879ra3s0gu9l1un2s6715fhefe784pfno48", "p8ob0kcl1t3hl5j6fotfn9fjulshbeinue8b8c0ppnormt8jor4tlv7t6qb3julu4hooo7clhmg9okm53a1rjsjcjuuftqfh1fvv6mo"),
("2eskaeha02c6m8u2o4qcftoq8ih1032hcm8n0r024tqps5c6co99j50qm3pb2ptjqgl55jtr492qhm0famnrr17hnr70q4dqso4o4ag", "p9cfghts1je8d2qdbbl5oerm4ef4fcoc4um8k9pr8vfduld5i3unqqta525ss1pkr4cool7ubgovnekt1fvihosrv4o15tv43rt5sv8"),
("ncq0ljoof6e5h0i7c3jtoka83ed7qtfjqcqgnvbrrs69g7iabd70iprj0tg7tsljja9mqn2r70j4t07hdu5a7na9huh6eq0sf8j6bkg", "pa9oftd3piubuubgngpb6c57irkv7avp91hh53cfflcb39sa1eq28ka7fm940va9huhpkne4nqrmoniubqo55l5ptnfmi324a2uu2e0"),
("9f00i25bbn2rn4jlhfbkfmlchsp1njfeahkfmtmcapv2ipvtb079ir2v0caom448rnge2gm1n0146a5p0ft1ffupmii4gg79ho0bodo", "pbj7bc6s7kt7ser32gcbb46rh064m9f2kf83ftmvgr4iq2hel77o2e441286o4o5fnm3t5vnkfk3k0i5pm647loset7v7jai5k9975g"),
("vebm3c4e71brqgnlelschvjjcq9kqbl65s6m6gp6tkb4hnc8algbjj5rniism622kbtrqc2kf4o7ir2b8v61obhnjt96ao8v77mmoe8", "pk5uoimkp5jdlos8acll9r9auatvgusf132gk3m7sisbdnkv8ali0446dtqk7u22rtqs5c1a5pjtk0at55h3o1n8750v9ska5e131i8"),
("uegk16gr4024mrjtq1n09bf829bm8n5sq13veon1rhnkeb3md2mrdeeq3nrku9v541ni8obg9a8dh05r2fne1gms1h46bbmcirsukqg", "pnb9dm3o5hul0nc519t0oi3rem00mp8o0slsin8rh90vmigtqjn6s8kcd9qt8mqrfheo6moj2cc20n2o6hntac6qk18cbkqg53ktjco"),
("mlidm6ulq29pdt0608cinh5eechg0kbi1uq1f1s7hndsj8tohc2cunrjv2f5fpgcivjbjfljesuag99vbimno79g78cdmlgn365qba8", "ppu20jehra8nkmd3bk0aqbvbka8o2bfbs50u5176517unkmq9npeo9msg71i40flmi5kotc3cvl4772s9ba6u04ba2gitdrs42smef8"),
("c5mplcbb8riuo927dvn3tc8uok73srv833n74cmeb9bs5kjooosappp8j09uia6o0mpr9a6cqt43ae5hk5akjreev6cll6geleedfb8", "pv4nbuh9dihp0f6n18qj362afhmlb8m915ivmtr5e5i53beginaiu72nq64q910hdd2fdv1f7r32umm8kd8g20470df758gk2qniefo"),
("isjtcj0o3njnusc2k5qhokhmertq0acpfe86n866tsivtuvk84qsplicfq4nfln8ndk6dkc2ant2o7ed3c7t9dmtdgc7memsg2oglro", "q2racehjqb1f88bf3hu5n0vte1d7cepo3dr7evbd9mdvir02oe1bpneh72f8abv1oek07a4ifaht83vk4rhrmo0md0m13e615h15g4o"),
("71qskbha5pol67n2i1rk6kmm91u4hedhgspuv38ikfvqfp8m7iqaothcstramt4l33dcn8vg0caj7e4lri2cg4bu5qtk030mtfk9pvg", "q2racehjqb1f88bf3hu5n0vte1d7cepo3dr7evbd9mdvir02oe1bpneh72f8abv1oek07a4ifaht83vk4rhrmo0md0m13e615h15g4o"),
("17lmn02su7f7fnni2q9abpp15cpb2620vnsqcttu2s8hmlu56pj7iscgocqlhr34fura1utnk8364v81o6st0lf2rpsfvv5vkj8cjg0", "q3i5vcl0u0jpkk6h6p437osbe44gmhrbckodd52n59l39v72oar2bge8npue4551cd29p7kuag5mv3i9hsdlcro2kppbdlg1h991kv8"),
("8aepn2e7on97avmtohhd9phi54sdukm783f1bdj41umg6lu7u5bk1p2ff9aqmikood3mdf4ok9bj87pqqf9oi92b7nu0it35tmf1eig", "q9g1gkd9bkogf8v8pibgppihuhmj3oof8btj82pg8p8mjla7npshsh6ujnih7vi85tpuudqdaca6op9mrc5msmo84ju2686dag87c3g"),
("oavno2091apesh2shelbdojmmh8ekgi2c2l0gmavhuaq0um9b2e8dqo8tmgmhfs7npp6gl58cujl4ctb69f4d0plufgb3cjgtg5fpcg", "qb0vvu15mljmodetuinlkhu54e93rr4217hq2c2djbkfs8ouoibio6spc2j0avacc1f01gtloari8uk26jjdcm3kbg32cos9iue0g3o"),
("kk3ruonoa2l1am4jp14acgr2gi9udr71fb8vooh8n0cco1714mrgg181j0dnhn64abaotfdnecii1se545nv8etpd5019bk47s472s8", "qbqhgsvabnt832qc83m5nntdm8sbnc6udvdkl5ocaajn6du21pv53151tvn481ne0phb239eeag1rqtn8ler1mk34n9h9dtc6ikmmcg"),
("cudjfuj934560jhcad4stuoukhfhmun84i6ndlvj9rpu3g4lck8fqqsfjtrjf02uitk7q8cd98ppjtrtkio10o7c4t0nlnrc5je5qv8", "qekohsdvje6fpims560g70trontg4kbvou67snlvnigbu5kdmikt1cvhe1pof1ltm6nsgoortq3sim3t1rfu0k5knrsqnnm1mpgdgjo"),
("0rblnpukputri4erqglg55blmq8ef3gdv3t13bu036cg1rvp0ht8rb6rd7fev3vltbtdtcpd32kmirjltalfl74ig3bluuponim8r10", "qf60j5ta7s6b7e5gcut8csjtk2rl1l50g45mla8lhf2p2f09cc101kjcriv48q3ri4cgo6kp7a1a8hs4c0g1tnl5taietcf1l37ap28"),
("vadfv19s8hm65m6gllggiinlpdif3u9ur8sud0p6l3resqoo7q48lj1i3of2cqn3t3aro6gkh57ls2du4hbrbq2lpljrf394ro5cq6g", "qfl7tbr3n7jg36k3psu55tl9sep9krdgsnerbsjnv4ec0n7oqrd8n81l404gm62sidnn5oocpl1jvu115tjk73jfb1bp18dkpj7ipso"),
("eguhg8rgvnpvg3n4o2h3eulp9bjqb9na3oj6l97nt3algmum6e08e2jrgcd5a5t59bh5s582j3dneonod308qk3gl4lct5229vif3no", "qfl7tbr3n7jg36k3psu55tl9sep9krdgsnerbsjnv4ec0n7oqrd8n81l404gm62sidnn5oocpl1jvu115tjk73jfb1bp18dkpj7ipso"),
("9t6kfk5b9opug15ihqebtaik4lc2ikp6enu58rrvm6ljhjr3jn45c0m2p4g42qfq0lbh64088v3rbeo7lftaq64leom1s5ntbp1tbko", "qn7r8l6493a0c8o7i0hup1nm8uthbefh6q5hhpseel3ijf3pbhiah588jaglp0kev7ua8e8351rfencvafkdtc3d2rv3g7eki464mcg"),
("7i1bgff7sgsl5vm1iookh84lti92p09stfrt837c7sjujeap5nbf6hh036djtq5hn0h6vn6mgqkc8d1arnsu0illrj327cki4jncimo", "qon6npsuou7nsna69f68671hupdfnb5n86bgsn5dnr9a6abo28941e89nopgqabn3gt74g7jcbttijo2qlu8ht769ohorohfov0t9ig"),
("mhqmc8itlk9q2rfbv3172aljl748k3iihdpiobgpso5oadi2eu8pn8akcbllenqh41h4p281bjagr9m63t9p2mmqkvr73egumflgua8", "qunk0ri8tl52pj3uql397jdlvdaa4oq38mfl56t9arln9dboutcsn0a0apmqn3q43jti76hhqbd69kprnirru3d06ghkdbevm8ohaj0"),
("8f67rg5gqindmkplsidcsflf3q0qfnkf4q97qqfcrmddkcl288s3ih5rk5bd2nsjjc9vpk0kpdn8stf5haekbcb128orqq2tgrek6r8", "qur6j0vll7oon8e4u49c9on8f1ujnartojppvmd80024e87cppd9nb1uj5qf5gr644tp4a0of30037abbuvfs99g9vht0253k3m8kd8"),
("t41iq8sc1enfo4dbh6a8nkh178v0c6f42dsm76puh600u08lnjja1it9gi31qe3jb6f5hn0u01eirba0d4cetsag99u2tpmovq1u0jg", "r0aidu2ke0fgge4fqjlu6fj9pefrgo0u91tb7eus792egmjbjk6rviff9vh1pf541tu0uvd0tag6dbms9naj3mt2fmvblkpjt19nqf0"),
("l5b72htheqkrgbv304ek29hkee2o8m6dbaa48a215madop86ta91kubi8at0bfrrr1gmptlhel2vdk0inq40uq6duu13chmth3p9900", "r0kfjla3ptj13af4dmrsno0aflc0tql9q6r7d3nsk44a15sjp4gc9sgqs3sv55c6u4jpp7us9egdvsl1rvfh5t07rgv9cigh1e3sa3g"),
("alhetk97loebf61sguf8t24vhf853ee63nhlk99b76d0mtr1r661jkf9msq31p2uo3vh1027qhqdklqjkl5k07sh5hntmeffkie026g", "r2dj9deuibhgjsi417bknmqa0brcqv82dfl3ategggpl8gljctre32g0vdisogui8trp5cd2ig571a3r4rnemghb448p1fabouh55m8"),
("5381i9qbakm6o2v166r1j40uu5ft9l48gi80gokndipdps7ocqv4kjulkt5ir08kpmgpks66bfouso123joj602nefm3lfkr4uj24r0", "r7ujj3rpc0skl93ua19ppg2g5pg8lk7n7i5agi84bafm6mcoj3usqv5b62m9nae6qrshfaea0ejnfia6qdtgjuk6p11q53hpbtt5kqg"),
("uo769ued39r5je81f3h041v8i8dlul3je9lai07trvr16v6vre70dmd9ijbe5p7ejp2pc6sec91g54vmtvlok14o14detsq64th1un8", "r9f9b2kqnqarvilqo95qg73uiov9bn34vbcc0o5gnv75o2gculp7ial0r41qdcc4rosf5lnkmn7sq4gki8ha03e4ot2j0cp0ltbb6d0"),
("ckj61er8usmj4jtscl6gphgpibmjkdi9i2i6225op1j2vjh4ba2cglv6qtg4nbljnvhk5le0ebopnmhhi1tt5oaqan20n86805rju4o", "rbik6pvtdcp7qcjfoo8v246ev8chafdcga22ct6g5tthh7n6shn7l65chlj3onlhsqm5spupn6316fprua2vikk2o15suefvdsrvlk0"),
("r204s4u7aecaiif34dt96807fjp6qgfb5std7cf02chqkn7vn6415b4g0umte5isme6b018lbm3172akkeo4dg7ljpk2h223sol3er0", "rbrl48siup9qvqnkfgs1tln8td7ksk19ntsjk6nu026m976vjukb0qk7kr16dtmfldipdhdm99q4vp5pdsqlpbpl6enmhjc7l1r65po"),
("m3c80vajoel7pgbnc1iddvtpgu65n23c36c8s78j546t3dg3fkivq31f5g177k8afp3i7fe6qi6t9i7qgreu8b05eou75vk5n5om70g", "rdal4ln1jbl36hskm28v90b69jpbaa5vl1q1glg9o9ir1cba3hoq5nqnah4i8clu3f1q8dbrab1bqa4bvv84hktfms5ted12nt6k8k8"),
("1scct82kje965647avk0uo8clle7ejmv9j5q2qlbo49u80st6nh9rduphihbk6kv1tfsv7ufmu7otbgnkd1voh6tnc8e90htb8doh60", "rdfdb7rml7osfvhh5cbs49psqt1hqodeb9ej66u568f98dqm039rm4md8f0ovppd2sm5rcm0h12hk0rdrnj9jp5pak28hvj5cev08f8"),
("7n5q94s1hjl4gqjff6jcnup78f8gicc7n7g7d9hn7pn1hr08d0ouhld5h9ocnnm0h5683ve4f3m8bovu6er8jbefd576p31m9q5poqg", "rei4u1fh5l0n9vurnd6edf1okil9g1mc1rc1gqh4p0q90the3qhi0ade3hkkndioc5aq96edtnhlmbjr9f6pvnrrrq8cva2q3qg92kg"),
("ml7ivb9no6tgqnsb9kpi8ni4e7ootqhuirc1gsgv02p2fm72c7mrju9prkiefip6b3if9crb2e28srml4tntp08o8a0eld7iepmeml0", "rf6qts4vgjv89su00embg56t5m4kkj4t7huafbmg639povbvkogiro8vcshdspuqae99e5u41puv7lkrmsijqnc8m35g0q68uigtbl0"),
("e3210oa8riuiq8tvf9hrl7g929e51q83t7dh264vj062ksb038g12ols11h8skag8i6hfn9eors3m04go8uq3meeqrmlqlhdh64pc20", "rioennqp19ljo0k4ffga94r86n39euscjobbpalk9gatgucrvmeth4fug38e0vfetubk22bm3nj03hvdgtsas9bmsfhb9fvtp6muqu0"),
("2n36a92gg8ij8ghbma1gui1ap3f7b7a9tspnikil308imiv5plc7oo3tr59du8egtubodpcktsn3e2u4qe976lupcess7hakqcjf78g", "rkvfrmr7jjsir8bhlrvhe794t95gfft70q8icadt449h90idmn87tsja4e40umjtphp1v4r3o9lvqmic86jb4h4rksm1vndfjn2s138"),
("s961mfsmmo06r3trtra3ul4f0tmb0mrsbo8a7nqmuqbjujm3uk9cqn55impki7f5rum8i9cevpais3aku5j7f50gi8euc82g55trh1o", "rnranmao8p924tih8g5jv2pfdho9n0j1q9mvg4eqob49plfljtjqh24pmqq84um9pmm0622n3gtg6j7bg3pm6unj640arco859g36v8"),
("ukklr0i0fb3s91e3lt1ad0js11aa1t1cm1jn2haq4j99nj140pcs52kdmu737qf3juq0j6p4d20ge2piudbc2fk70t8ofe77k03kpc0", "rudd0e1mejejgchso8lqv4ncemab8p9a137q4tfnbjok63u88jt1k7k2hs8trp9d65sjc4i618ntdknbr17q7lhut5vilkdg066mejg"),
("jq4riacjdmicl3v2pkv58enkegn7bop6iuu2bfuk0u193pjdlegqbgbshebhbb7mo6rocr2pn0v9od8nnm8u1og2m2ppfs5surmp57g", "rudd0e1mejejgchso8lqv4ncemab8p9a137q4tfnbjok63u88jt1k7k2hs8trp9d65sjc4i618ntdknbr17q7lhut5vilkdg066mejg"),
("d25of703abg8391sff3jhe0jo98729uppsaf8gbjlpcrv01nptjd0vki3r4dcpjlg34j7ftv8b4sbmge0kjgke7qkc2uqfkio201ma8", "s4p2l5q46q9t2dj7ibt6d8itfe89q6ecl1qvp0a9ls2hbcbq100umbggkno8sbbgi0459a9v25p665bk0tcos1oi94ppc80m1o5ghng"),
("qoqq8egkflg931iku158lmb05csj2slqdhog6h05lgv7a4guokdjlgljmvmvcrd9ls76qac4vng75k39mhm8tiddbmo3e2gp5p588q8", "sai94s6tg8364u3h99jo6ns8lr1n593vo8vgkqa30sj2koj5fn4902ohq6qebvihhn5hk0pbmmcu3bar8rju700bpn73kd81uosmmig"),
("na3e92peejlk0mg5muuqkpqv89e0389mnl75qj5nhbl8ta5i7h768ge4epnb309iq6qqg3hlpmogtu1peavsdg1e0diudplcsi7gl28", "sai94s6tg8364u3h99jo6ns8lr1n593vo8vgkqa30sj2koj5fn4902ohq6qebvihhn5hk0pbmmcu3bar8rju700bpn73kd81uosmmig"),
("rom47c9gqblootgn2bp1tj2c5jn5tq1ekn1kt7vomkpr2us45b70mjbs9t8633id7kt38pih3bio1h77lr1s25upicvlpj1cc74eu3o", "sarmevrsvu7ehnh0thcgbjkhv9ks4lc3pnbg4d528epger9erjbsdfku2um76iodgmicee5oit4qfpfqjcftkbfhorv02s45iaibuj0"),
("5klgjbepk8vpndjpk45rvdab8p3ajj3s5epc2eb5vpghopnsavaie2eqbro9v65tapu9f75bk3ldnuil0pvke997s4930svm5p88s18", "sdcnq9cbmui691eqodiqr1jkd25m9jrhmkldh6n8c7a35o8uq2nttdic98753igjlc3llq0enn05jrl4htfsas2omhngcbu0p1l9ln8"),
("g6e5r1cmuqcnev2kpms36eb5mdlkstt4kcmkaptpuarp6kde7uipk8p4otg2q3kub6afnih624hli9crl72gtdtkofcsra2m6t701c8", "sems47k0d3as573ac0jllq1pq0i4kkvqlgo6tch52so4vk8dof1k3q8ga6a60toqdgigkab5qpv08c8ges1i5raofd10vq7iqit16o8"),
("duo3as4baffmq5fnfm1qs8pao5vklm9fr6jcnvc6s9fajocrlc6n81qncqidn8liqffpga1apni2ojiu8piiiiukaimj72jqsktmmsg", "skajq5p638guqla5kre8qp86fl6coqhq2g2maaksttsl4mgs3v7ualeceanhlnos1snqcdnr3ghi42j0k04pm5mk3u7ev9qjsoo3d8o"),
("blcnv5k6k1enk7rgtdqdnk0va0kherltnf9tjn9921mqve6h5n0brn4hmhnhsvuu670ggkg2mkkc16nmtvsu971nq51av4dnthar9p8", "sknjdopahvlnef3utng9atftb6nk3q56sh3f6q89ls3b3bt99sge3hm9o5bdkp4r91ac83psvnihdlhgjomdp25b3scr7nm9dighogg"),
("u9pv2h4h8kupmuf22ll9qq4g7ag4alefr85rpfj5l0a027apdb41cs5bqq0mo2q0qbh1cso0thbh0iv0kcrn898v5tp7gocgh88mhmg", "sl1mvfjkp13afnu1cf7403jht118qfpl4aruv09aj2qdsr7d4s7ansec77be7g3is2q9ga4oaqehho71hvrpc3oom6v5eajumg6uk28"),
("r4s5va8h28r43dseqec3d0hn6dcrgiivurvsbulalpk4tfh35e0m8e15dgjcnt6bvlpej3nhluk0qpfsq90esefnkb6ppqc6bp4m4a0", "sn4eq68q3kkj2cvqa967rq9n6uiflpfo2u59u2j1c8baj434m98q5fo71fgivmg055davgtvn5bec28v8ofcdi37vdk7tu6e32pk4ng"),
("h6tof8383rsqcfrl33g13lctv3f5mn3uv3o6i423ogk1q8mucpcsejvjdk7lp04cl54b2hrhl85r24nkmdb9ls5iqeqqp7nphpop4tg", "sq1mkb8q47okscu3fcm202cp64vinbqp5bjgcsaqc5oa51ev6rr0kudd11v91l3f4hbjc972amllg63ek1d1isb79unfmuf7tgshreo"),
("chqc6asn49h5for7d14oiq559hohnc5usqjf4mu696le17vl93gu93q8gat3rrjt3lf35ofccoekkpgcd9p18ejlq0g1cln6t5hs77o", "sq1mkb8q47okscu3fcm202cp64vinbqp5bjgcsaqc5oa51ev6rr0kudd11v91l3f4hbjc972amllg63ek1d1isb79unfmuf7tgshreo"),
("temdviq3pq3h88a4f1s0i3cge3m134t6bi05u5kmcq37m4rdr2gvt3kqh7qo05534s8oq5gu5mus0fgqtahg7ifhe4itq44nt79ju70", "sq3bo3j1pmnnjfl0e4cahkphe3fdb3ijlmjfnft2l6u5oc6f5e4ohj6ll1mc3m5m6u976c6temhquoaa79au4ugl61s5nullsvvrr38"),
("i8bhtp4sua8fv2cqi46hugvoevme0tgqgu1vu4tgsvv3i5jc41f982ctvliusdlb62f44q9m5vg2aj5se3kjm8prtnvcvdnck4k2li8", "sq3bo3j1pmnnjfl0e4cahkphe3fdb3ijlmjfnft2l6u5oc6f5e4ohj6ll1mc3m5m6u976c6temhquoaa79au4ugl61s5nullsvvrr38"),
("oaqoatjh80te33jf6tki22fjvbdvugocp70uahjmthoamjuo88v34l4jpd83c55bnu5qgp9mq0n2g0p4g68gnj2smgl2o44qq5oag78", "sv8gdsja1c0br527ibbl4lonhhl9a69medgi1frkk3mp2bg9svkqfbflbpa2us8sd63gtphagb6c0oo32a79p4n0o2pjc4r635bl1f8"),
("65ailueuqf0m4o9ub6uml3auk07qcllvbv04rf531qald721rc3a3rk086hkbmc9456urb0sadk1711rtqb81t7dlh8rjrveserv75o", "t5m62uf320iape2g8mmuo7l595a0kr9k5fcj8h7cm6svjcomhsqotfiujmgt74ovejh8bdvjb7g4rch3bridei670pp5hcpil0bcv2g"),
("nijr4h9v4kam7cbhkaciok77lc4pnolr7eaeaccmo7jcijgbmsf6fst3bvooltmpcnkiej896v2q8la3egi2gf1haci0ofubvoqromo", "tb4plvpunfonlusgimhhtmg3ctjkkhd9hutqasccved4jubpcp8br1kne4bmjh30i6au856n7gubvs8f42vefhut9c9u12m75noqn7g"),
("js8n78m4a6v2k10ajrbvhtmkgnuv95mrn5f7e3u69png22ui1037bjlsjes96v5b7rbt9tn770jvgrleks6sf3luiao3m3uhdvc6ql0", "tht9ibhq3svviign0vl03p2j71ufrpo6iv2jc4t2ikgo6ehntk6kfrln964sdpr2hbvjh9kg4hh4t25aneuibu9p7khoh3hg0d4jf5o"),
("0chkli1c4nv9gu1m863rbn4if7gld595su14eii92jgfcd76pp1d6gdjunf8hvq82ak083afu0kp56qanmc0esquh1eas19lqna377g", "tn5bcffu9l3u6c9ad5fflrkc46bbsun2ertlpm7526nrdrp5i1r17nr72viv1rmj6gpl8t4vfueu77bj3g8843rers7hcn01ibevkk8"),
("nfh57i9mpb8re46kcojaj8h3u5jg5nt18p3nbgkgkth2r65cbkt6ubntkrjl347ongairo3oc34cr7kji5a91ge5tu5aojqt081ei08", "tpg5ee8i063l3m10he0kcm2hlfp0ana1k9efi6i3n0rr5uaj1ra6tdk1ca94u7qcolkkd9vbegsc0pqval7q5dj8g4h8pv807rvt8u0"),
("ga1va4a49e34ks6b686k9kfje0hiankqig0n89bbqpf1bdfk7mu3staq4movhosunlqf6771d9grsfgingaqf0hlu3gcocmdgksn2p0", "tujm7elm7h25adbdilbger0gbb4k5s8dncok94g1u8nsloqvrl2l3vs0176l0o1grhtifqnaj1f28hkav5u8e8lo8up9d4glsufit7o"),
("e0r9t3pk6s5a6iov087qa4e4o6i7b2goufg52u202k55sskpgsrl7rp3qohcvorvmo1tn90m6f33cm2f7jlsul9bbifhivh0h7lopk8", "tupmfk7n5t794jimcshajbsm9gvlmtb9k2oaf2p59o2q945abnqt51q7jmbd1ifl66ckokg53vejjlup6l92c3rguhphdjsoi7kcj68"),
("cpr1e9f01kbtmkpucia164uo23gaivrte7g2a944hlk73enlj3ilu34vakrdg6m8omjg9ul649rkeolmthc44arecfgf9qrtoahvj60", "u2hegu84sq7u4ufsbicnrk2i8rbnjaadrcallfd4ae5s72uobrp12qgktm4jetu039fnijmrhe44ersqnqjt8t4i8jan0vn6d77be0o"),
("bhc1avqftebtddahto9ga5e17jmjjmc6do8gbbrvg4r5jha9hs5oehk02ogt537hsommm1ticdf861rhr3q3j1nk761unksp9q40rg8", "u2hegu84sq7u4ufsbicnrk2i8rbnjaadrcallfd4ae5s72uobrp12qgktm4jetu039fnijmrhe44ersqnqjt8t4i8jan0vn6d77be0o"),
("kug5549pr1nf0c0t9etcbqqo89frjhklqdc9bbbsjshq2bf7opshrb8r2be2j36urk3oc79ppdtf57j5fr9s9i6nkd4sfvbk7l9oi10", "u3mgqr7a7q98a2cbg2v5valggaku1vg48smn7gei1p0s84fpvesub7otl510rf59fvsclhs0a4ntiiv5ru9i0vn7ifoju3m9tg6h39o"),
("upg0pd72l5bcmumr6pefd9f86ohc97655uidd3asiddlq6kcqtahkphkvkjem7ong671u71jdlk1sqg1eb167kioa6jg80hh1ssf9b0", "ue2vrghv45vfb5lr2ohe03fjpp269iboknbqh8kj22ntnlls0m2e4plmrj9pefcdfnbud259vvi2qec98cb5rd3d76edufdts9qjve0"),
("k1jbttaq3jgi19102qjlggrt5ov21vg6287et9mgls0ais5urp4l2av2lvlcqjclrp5i0cv0ip37emhpp722r9i4anva62g78lk92g8", "ueq2jh19h80je2o89s5v2vaturf70fam5uhdoma9l1109puanulvm2p12smsma7vge6me2o6hsoo3ch6cdfkdr0d0dpvunngfefr1so"),
("6ceil1ve2pmh77b9nj86o6hsd7gfrsou05r3l1orvirhcj4m8khig2b1rc055fgnuodcdrvar0gmi5evq4c70lcsv6qkge5fdnsfb68", "ueq2jh19h80je2o89s5v2vaturf70fam5uhdoma9l1109puanulvm2p12smsma7vge6me2o6hsoo3ch6cdfkdr0d0dpvunngfefr1so"),
("1t600cbs55hpksm0a22se157g2effj27cod9herd38e20rtqptndd1s8pap9vls7ukuoldvlg3mfp7kh0orf7tfojlqutvdt1ghc3no", "ufa1tl3v05rpr4nsn812u2t1aln7fu58rnfhktv767jcedv7dga9a7vbu15elev69u4lrbuubnqv8nequ5eanuuhnesum0miedodvtg"),
("qgjmppbd4ht2nf424rnf20fcfck7oc41hpctmkcr6ntddv41b4qkrbb3m5r4hka0temsj2t15vmofhd2p1d400qosfsg34b84bpnsao", "uk127hqp1ghvn2f853s4cgfhgsuqjj1d8b2l1crr68uriteur29e97osac55hcvu9mjk2tld86964jgtq7sq8du4mnmu8jse2oht8h0"),
("8kt4kvjqp9ssijr05ed4sdlibm4970r6k89s5663cl3uvdfr7aok79hbegil0fvd1qpb269nbnv6re2imko50enitqd3bb6hluavsfg", "uk127hqp1ghvn2f853s4cgfhgsuqjj1d8b2l1crr68uriteur29e97osac55hcvu9mjk2tld86964jgtq7sq8du4mnmu8jse2oht8h0"),
("djn6u0u421qijo4oro6nap5kqdd1hs9jmur7aa3bfo13mc5s9nlbfn3li0p1sgq9kgnlaumtb3lkqqqn2sjvq2m11g690spv869vck8", "ukdu8qs7njfkmhg2sgqe4rms6tq4h52p7s7978plup2hmjgqmm3vsoohdcgjmfomi26ud986gn9k6oghjr36qt33aaad5vs07ikr7oo"),
("3dvej4nskijocdip5bm2ik7uk7uvqn4qt237otpau1cogmovhp043jcmfkvm9ej79k1d516ks4ugjfvfeha5q2p1hbi1oclslenhevo", "uvkird1g5dtq7ceo8eo87ff20ad60ve1l4qcvhf5u8403dvlsi27ci025lu8nkhck113gte03s2t73pu061hotqh0dmljf6q0vuon8g"),
("3ua7v5iav90d6ppmak4ogdpnj4eboms636glskb65d01aa1mm6v3ahk8p3jr9ed299uem9hgo1499khcml93tui8ftrbr2mufsu9708", "v10o6tbfdkp2as2jpp4um9a67ti9vf6hoff4v2q8a07jil5qj94ftpr488hfn87ruo5ttph2jhkam0i7atcu3im2ogp4mvuamakvqr8"),
("j5k4uae1sgqrvjcgh6bhcdccobtvqb9jsdjafb8s5lhtn5ghop93db7ai8ueq18qsdhr30nccmtmc0ji8deh4stu3a8hvu5b8kjgal0", "v1c6j100chjho64i6hi2d9755khvvucdh11pjq0cug9p6j0ts0ipubsg5ump7bbs5jubs7flgroudes1drd7fstgha4f2gpep4qrv6o"),
("gd2ob7skt36pl37fsu0iundeo27vtoq3tetaadg0jejnpb0nrnih7uofgqeqe4h1e90lvjcpho7dm17nqr0ncvorr0uv1a7qkdfedto", "v1c6j100chjho64i6hi2d9755khvvucdh11pjq0cug9p6j0ts0ipubsg5ump7bbs5jubs7flgroudes1drd7fstgha4f2gpep4qrv6o"),
("vu6llmjsmlehoi18ts94popac69kqgedb1sohjdgpu21aqgpkev2amodpn2t8c76rhp4kjop8lde5rl1tblqa8df0b48s7fgnr10ia0", "v2cag0b5sfd4s5lve7r1ao3mcipmq70r52vj0m5urvo2bakblq8hd9dg1mecahlkne4pkvhob99uakuojsngiqulatn4b9qu79qlvag"),
("h531tlg0et1hjc2c62gebd7l4rvkr6j85mrbvvtp3ipun74flesq1no9u3sooite7270uha08273mp034u88nuqv8eabgqagh6l7va8", "v2cag0b5sfd4s5lve7r1ao3mcipmq70r52vj0m5urvo2bakblq8hd9dg1mecahlkne4pkvhob99uakuojsngiqulatn4b9qu79qlvag"),
("8llbrf6oj6u2da7vnuli6hg92fomgp4l5nufloif5ocmibdooqmhpm9613tosrp0hbnbkjjipjpb2f3198b4ftrc1ejqt9k0a7u2nlo", "v3tau91s7hd8915mk9t97ov4lm085mtrbsnns1pvle039sp56369s59eevogblpv0p6344ngm68eq59btkp9f12af0pg1pe742prk60"),
("i656f43ori3lgokhcn8ll7or74usr9thvpt80lpsh99h1p4b607u7d3d9vff4mmg45lmh8n8r52v8pm5uqqtf1rqdq16cqp2g578jj8", "v4srilcp0amgpmst0mbju91l5i5k14m3ju5ceod6s0jb6kh7cuu5s4v38f5gp9f0cfsuta3t29easag3c739mu912gq73jfpcknqg0g"),
("lfu9gadtu9e2o9c4vt489h3v1k748khco6nhvpimgktk2fecdng0jin97jqqetcs9e8vfdduqj16ku371ber89fqtr3se4gsnmst080", "v7g2rko2ic82htjedcovjkpfqi0jlv0738eroamik1at299gt0oeq70bhg5qpm3otv19qtupvrlvakn54aem9853tslhb0ococevgno"),
("vcfq2u7q45ooginrl1j3d6dt99mm530vggie63jpnea82erom5se9padtqi3s6rgl8j4s7k8vhhq9m6v81i1qa1ps7ofp4v7icpme98", "v8dtpsl4ra4e4srlij94rq375tspmhk0791tppsknb4u5gghnb710338gq6eifpr9hk6vcin0r3gni2h35nvjmoiqvpfs7v645tlur0"),
("2c73ai3kjgmk95584qpd9dlptonuteht422of2rqlhi0v982ntsa6ng3mj7fsv8oqhdqtf2t696pqv0v6ifoerdsi7t3c9p4m7abt80", "v9klc1r58s0uhaqkbquu6hke6c0go1q29i2u9ceb26fcvd4mii590clt0fncg2gjsid8l5g7mbe4v6d5ibbhad86tpjod7s3an9ivcg"),
("ojukg43n79n6m2s2fsq09ukpsila01ib52ddos7beul5feasce3j0a004816v3n99tj6lekkp0i4vev445hpfmdtqsrtfm83e3bfntg", "vbi1f6a3ebss526172o9jceavdnqtc6e4bk1b91gc442vl701gm2go2n0hut6ckckiobgvo53vlik5kppgd1672a4rvem8k2jun4o1o"),
("dvqgaefmamj9qfpo59cj9sa5qcvul0b7m9gaehe8n9o3h89m06nk5kbntu34m3q7fqeivo526esgqadi96k04h8unrg9qav77dth9og", "vbk6qoie54rj4hjduh2rbb4slu8bmn42utt9gh671mqojc3t43gi4rkhhbpovklhuef4e9n5m5o0fo4cje5o85t9ddsldbbdv84lfno"),
("q9h96lovf6rb7mnprf5es4mg7as5o89khetn20i5uk8bmmbfa4cel924njstdhh0mpipvlp0vgloer5p28ck16e272ocv892kvvgkc0", "vcad588l39446d2ie7jv8vkcp0mfn0thstq9ro8c5ocg001gtuj477uoao7cecv2ad0oc6f8h0572n3eivcqc380hvnengjn03f87kg"),
("oi73t8pfb1alsh7mnr1cfov494rs62ulecs4p410evitlvkvf1o67as9sb7neiqvjg9rnjqhr29jpite8i5m9o8ph5qi9224tu2vasg", "vet2pvk5elid9ulqnnks3n73k28nq6j751p7pgb6f5r64viek0mef2n35gu1q1fuipt10idf63p2tmk4llfgvvnr98uhms340f9nsuo"),
("ol9hgbi9qpmah9c47ce1bth5v7af57dvg17f8863o38qgq9s7v20eice8l0vafnjs6h4hvcmge32dp62t7tpc7ho57sli1fmah3u4pg", "veumbouiipmuk0dq6ffhfdom5hfo1k5lp06flkhljvi8qtknkl2u0ttof3ugkempbtbicqgni9iiuvn57dnlen6d78c2d8usvbiv5v8"),
("utdk6s5a40sfkr3uvke517tsi90spbhjg6ttu0lkn65es4d0gvdjprqmvlc5arju8uajq26sclhksta58q30u13i2bdc19g07c0dqko", "vi4i7hmj4rkijp44ess10ll28k5d37msm7v8dsm41p149r59jq1libh02f8nmq4rn5j788vi7jgu006r8cujkrh6n3tdd67gn99kjoo"),
("6npvrkht8g8rgi2aahguk8hfcfossildagnk6u1ci9babq921mknr5c6t1pbe8pd4mkodblm33hqcgan454f6otml6ap4vkif30o1vg", "vnogrjm78v816h72col97nssrh3992advr08acdgk7g29afcbk220he4aq6cb5qs1lkn08tc46i6e4odj9huigvml3n0pgbbi808ts0"),
("nn94p3nf1nc4gi4im9qgrfg6ajstp7copgel7960jgid9vegilg7avad5quhbmncef1upn1l4n63oa1ucan2he11700d6gvp3jj3e48", "vpvl5hp0i83uo28td2ne98s8nqe45hfagt3b2b4bpa2drm90b6cln8uloja4is70q4ru2dtl6p2f0231r7jdmikciel1ofcukjeni6o"),
("4g8v83oda2i3uu69qga6j7ubnl67ch2jm0hskh9eig1sbad76bvgh57cnm2qtsjl30f5uelv6j6udhp5jr0i9sha12nju8co2co1gj8", "vtdc69vehflmlqlqc20e7jvuomtqiptke7l84pij5ehk9jqfhdkgqfagh78s77fu10p1sc3b3tc86hoqn254os1ud4kkgfofbg32mcg"),
("3d6imej3jcghkq5qrmi3du3p55mvvs45b83af28aj5htb6tl7gomifsggue0nslljf3ohd5gon3ef38smq0sc9noe0ml9fbhmp0uogo", "cnp7q2qeel3f3kitn5v084lq4ht3b4qeaj77atracivlc1a4ksr23ro417ltj05geqdihts2i555d0l6d3lpfqu2r4puoeonetr6o0o"),
("4h9sgktb6jb2u9ubblo5pj3jl9nkjvr2coa8u0fkt0hjl8v1i26jppbu190fmrt8tbts3dfmqm4ohdeeq52k5hv93rt6auvaacsniig", "243evnehcbtmk52049o5938vijh89pi75cvu82nev5esi42c4vokvjj7fgj29tc77nmpupktmomht34to2a4i498mcdju3f753gi6mg"),
("4pjlv0shciotf84thv0lq3ub206sl3jaoui3s8u0c7h3eur24inmaic815ht7lgnb3fm9cnlvqq5nvogsrnld21h7i7ucf3m8dihc8o", "7cd0fcpc26qukcknd26ui6it20lhcemaqlrc0pgif14fibjdqfjdeglra2esnts8h9c91eink2j75flocevvm1ohi3scv5oiplh36kg"),
("7pjrnjil8j50magc2r4uisif4e8r1mcs0vke9ijtpt9uqivcrvjbfr3glqa8q13jheu313lpcmco5tli9vl4o96mbklnvkm402qbpc8", "h6lndpe1drouvfgsurk3nqvn9m0kdvpna2f05s85uctrd54jrf9oa143p60g2msd1d3is29ck4o4s2kadt38beegm0tkbs57nfnmupg"),
("894dmp09kvg4hmja9t415feqfd6h211h5pa1var128h7td3d10duf07c26j2oo3e5eohc1heqqpfcensmljnlurgnmnjgo958atj83o", "7jg2rg74kituvgqfbbfr2bvcs45tuehd7tea0n2bhupgmb46mqh3072jbhbl8f1lklp2q3j8p6k6g7ejeun4r4rrh48s5riq6psjeuo"),
("9nv10g4l1p8u8qr7n25ucv4ecnh8edqpjceft0ehg9htlcpt18a3fng3i5vtjr9iah0b18gj9lth2pbesihj96kd8uqjtbdhntvs9og", "3p9s2uub7g5gpn4f2r5mm3nlbeb05sp3cpu2neor5bf6tucsbgf3fr9ak4qbtcpmak31qe6jqvck544qhp1ck8gs5crce0g8frsi0k0"),
("9q8v27opo8jkrmpbfupa3p5oqintptr6mqodpik6nf077pjdrh8mrf1d7vkgvsqripfh6emtdn9ces0hquleihgaqep59230q8eskf0", "ibbsn1btn633glgovtsj4s8r0a00heaioal7fju937hpejmkq7v6n59mthscr1074k2gvdeojmdgho3rk6mr1v8bfskqc93b8v9vdng"),
("aale99cp23oq7ce1qavobr6vikm2v1spajj3sv2m21ilv18aso7t021r9nr04hd6jae3h7uhls3el84pfv4nvcmmj5m0lqeehr563io", "1n8a9idn5f04i8biccf2cbtbrvcesf9aj5rcptpc1ftd225pe95juru363aa16fatsai27q40kjvtbhgrd57enlesrkejt80dci7vro"),
("b5q3ql8pt24fqmsebndvi9im925hdcc1fhr4veeuccg48q1968h3177p2155tj8pnj7q7om5pfapppnorudjc08r5r85tfl1k2ktdjg", "a0pc8guu9fepl4bflr727m1q892l71oh34oi0iomnjgnve3aa7sdheufegr9jmra0afeqrvdgleu69e4pr2r7l5qrpgj31l323rkpl8"),
("evf5lf1r53g1ktpp4bu8rn1jakh1i9t2dk79rkkmjn63bihf3qm3e569b45hmplce7h5sncps28lc7ptptqgqlqtldevsrm87430mt8", "qj0iim7g58fi8lea1vptvo4pno8ijoitjtossrthp06ht4n8i2je71h3klibre29nn8au81sq4lpuhgaklh64glttraciikccm8f4ug"),
("f2s2phvupkecpb9cvtegi32s9o7hh0av3cdt76c5hq5gnu79p2duv0s1nar2o96hl1vmsloo65o1mva4hel9v5kvljn22827klff7lg", "32o2g31mq42r72s3kfh70gjmmj71rm7gdfm5p9egijf1l3g2fdelsflr3mrl8ui8soj4o5p6ib9mm04j71t5do7ahde0en6i0r0l9lo"),
("gcu35g5u0s16pejg74i8nbtbludddb86ip8rl76cvvhsijmuib4oqt0lukmq0hus4f2c2r8iclnh1m5502va266t26fcgejcuo9vdc0", "t5okns7aa7k5k2hghpaje8prhehihuc129on0akkb1r57kjan38i3ip8e7p7mlueesq49t9d0aaghjnhgjdbf2to0t3kvvdabv0sf50"),
("h3aa7lhl0qfqmcgsm67ucq2ekomt0nsjunuo4ekk6rqj6gvqjb138k9siidpej48sharil7nd1fj703pvqoinatmhuf6mhmprha7eqg", "7ojovnh75hcv1ak69qm4cl6174369kc4mq1052mco35u3vbffpjqsg5ql44u1hg6fkc7o64dk8hpbk6rnrlkohecefnt4fg3lmlbqa0"),
("h6jcqdlhc6h90umtvf9n2j4vv7vd9vpoecsgr3v79eskmo2s5g5fn07jkfo7k1igkc8tuuivuvmksci4g06r5rrkmpgtmk5q7nrogeg", "p23549emfnhg36lop7l6ga5vfn52rf9q6vojats7jg1isccu8p4qgana9qk8ele6k8liu1nkpkrm8glmpfa2a5gso78mlqprpdr928g"),
("hccocqsf7jn3vmjb2kab56ejsfbve1p5h14lj9elbuvfufjgojljppm15u8i1j8e72q74h7oikdjc1m83doehf4lnptiqtanq9jq3bg", "iguq17qbu9icdvbkslbakvc3m70fflji1nk0b0qb1l0qaodi9u1go1hn1mvip6cudn42h0skmi8df7divo73jrtsvq6ekg5g09pvf2g"),
("i4dac2ep1aonvufiqv4osf6512alg46f2lkq731rl8l4hiroh980lujg5l65dmtm248has5jtmf363dnh45puou3cnkjoldaqu6qpmo", "v4svpcobnf482lh2tq4ib78fkcu8s0vcpc8dpsl6l7sj6f06kkpb98apigs6fdk0gv76bati2l51ksj1lnfivhc8r1b09f4727kgk60"),
("i9d9hd7s6f7e3d25im4km0t09j77ct2npp7lqeb53f19k89vi7nabd533ugml0gss7i76oohnva1m06gbrlj289otafrs7qop3ngus8", "f6apu8rjcobji231bjedcpebtudp4q0ff70p57g6v8abh9f7bj47f04hhunnf0hhjf06p5pd8nhatbcsemucvd83s695igs0n1jphjg"),
("id4ifglpccu8b87tpegghrgpcd0bl5cpp9gjv1gft9cvpv8d5933ai9aod0dj6vgk9b87j7p89u22rouao5b28g9q8ne0lkorro2hcg", "cpj59hsi6kvb0bhelupl7a1pjtdt8b2sqj35b6jqersmq0t58t5dgkipj4dosrs854palu38s27hrteuhf4d0dsembd3jl6n18qk8lo"),
("ifokdqhhlskr3o9nq2oe5kmss155cbd3kg9onlmeu32niu00udhijim01kpsad8mqdbbsc3uvmdmjouqjpkb3h5eqqisibrgo4l0mb8", "uqe05cpo4l62pa350k0tmdcvfob66qbr3n4ng0g2372lafb8u6trrdk9c1bfammhmunm8knhbdankld0pvs9vei2ljrp5tls6h7q7do"),
("igs9jhfllf5ekdtrrnc0qg9oupgmoovfqe3t7qlt189q55ednauvsqgb5vqqsj7pdg0hmqjvttv1puuqamv6aivl5h0fficcvsi4g8o", "pq7jgnqbmr0c9opk37clhlqmsgi1276dnm1m9s651qatsl54csn7qcmpk62fae8q74pt6vjv1t823e0nima2p85gbtfso3sevp316l0"),
("iovti1dn0ij8v8e42919gcuj5as1fqat2uugl0at7rb5o0gmi59pe65pmni9rhuptvcap7ib0l4qspcbcqbb63k1anfe4g6nu6pre0o", "bfde1bvv7er3fms5i5s0d379lp67t97et5gs47tqb26tnv4vu7a9jiip0qt084l2tj6dnemfokqgb112ecai6hc369rglelnlmfgm4o"),
("j8eb7eslcg39pnuve627fugqo4gmffr99j9duif8vhimntdq8lur8kfdqm2g9q6gb04dkv87kfe0ncd5o4jbs9jl4ggldrf99dabmio", "k354jmnhfkd5o6i450sdjcpdshi2infmmv88ts1lnp081rdp03j5kgrd0e7v3s65utu33ipn9msvsggn5p5ut4hgurfdtbv5al4s34g"),
("k6l2p3cgl1ah4p6oqu4t00donk0bhu11q9io3tel18ip3hjpl8di7kpdu3i5qh51idlkbuugu3lmnfer4uac03sn4l39c60op2ejkrg", "f2hhhm6vh3o83242plm3g65nlbfjghl7qn1ens5u3audii2r65kntedv248l0u54eam6cphjdpi68v6fa9jeap0c1d5ck7llub1duho"),
("lb41i5mi6fim1s0isurp3hnkvl9jp5er9hm80dnhlf5n8log1ctferfra9a14t0a7d5hl0d0d6f21715gbj2mch4020ifjg5d92p910", "7ij6nljr7kcpphruddfjf18iop4nse0c0a7kbhrd744pl5lvcdovv4cohl11t8t0q20ags2pinnub0clhgmihitq4505cn1qu08fmr0"),
("lf1r84pt94aq3nke9t46ulfi4hou4p2to739ki2cn8c1v5a2o0at0mollth5ngrvmkc1bgpnbifpnmr877a0fgm03ba3nnudniokofg", "pip72mthn7qm0knjskuccsr9bp85v0ehkvu887pc1n2u2a7j46nq2unqbu3log3saedkv50v6jbfpcq4iu218uapma2ftpgbi2u58t8"),
("lm5tuk7p839cegrsb5tbcems8fcplovte3ifoak4u4o7n24h7d8pevguj67jpsnvfjpq4a42ju5gak8rhkso816bfirgjfvsr8989jg", "25f5kudpv5lbl4t8v5q1nmgavd62u1nrtlmljbkfcfua4a9rdsa37tpln6tua574i69nmhmc40g3e5k0fcs55mj46d2vfrjr7cot6no"),
("lrh3jkhcvefbe639vaujs9k8k3rc6tuik1a6l0ic01si3l31peq8in7ho08legk0d61qqk13hr34f0679ejf72259rsg35kbsm0t9n0", "pnuift233e7lh9tvvolps2raudob2vtea22vl1qbb24vps9ubj1uur7tgnkh2o1judemi1vs9q38si7t5ftppnjf711gjnmrv6j80s8"),
("msqdtcqdo0iv6d29nu26mnec03es80brhbluqfus8co36ajsourjgh33dutnks1u1jq20n97gfp269u2lp7nl7h5ga9lktlnvvqfet8", "qigfhdc97ip69ba8nanctl004mpke2gj6k0v1fnaakm015qf7abgbbl63qtbn9g0pljhicsnt1p3h4aff898f9894he59v9oknldau8"),
("n69kkcrdfoj2225mo81et9hb9ddlpkr1jfuvs3e0vgqvq2776v29jg20rlsvuro349budf7280cntd5r2nebc6aid96gulc7o476000", "gurdtvvq3erlau8ndrr1echqkvabu2a4drdjn3v3usti1n9rdt1tvtqppd43bbhigl516nkal3k9sibhte3a5e5dtps5ncmo1gu77uo"),
("ndaijfdhsrqqjd0llrpijdbj3ctci3419rcv3j1rl55cb03isj1flusma7p0ie0meufqmrr5rp8b4csafh730dlonsd83ggr2sqhvd8", "jmtf02604v4432vj64r4c7fc9gumik691gf9ffo7sbk11809dv3hi29cav6ktf83h5g1a8fkvthvi27u7mge9s4tcv8i3tg0lcnju20"),
("ntj94e82lhbgfe6q9r2kplutme1a7bb47rin9ru9m7hks91cgcn070i1jj7g8nq1rn2i0umi1iq48218e3mjelphd2h68ketaps87i8", "cjgr02bpgq18k4ggpd57rjsaecgkhu2aa7n1pa0fhsimju531nqnucqqafk3ooqakfl5m986pm7aqmodui99omg4rc36k6u25hk4r90"),
("ohj4j4l8k2ui5lfvmag0eg72aqtgmtr47qoobf5cr5fomhscvcd82p1oirndvhufg1gcedqamrq0tjq5s3iph0mpcumdss7i48suimo", "hl62t09s1pp8n3opddu7d6a6id3f3m9j58vtktk00nhbgldo8on73e4bcgudfcjbcdgmuuamc9p1c2j3nd7i73ubk7cgh2ubq6tieto"),
("ohuin0qp2vno2opnnh51gbmt7quu5si9ei9fefctor9m2gahcuuihh7l2a50e7ho15g9hf4j7arjm45d9jti4ab0b5b3j3jt0qhhppg", "ffkbk9ne9en485mcu5gvqcgftsh7tunrggp0eopgah13taq6dujq2inosknt7ljo19inb91klldg781mt3vn14hfecopbff4el2ifkg"),
("p9jhnq20u9912qruqn2tp27rvnh48g7d1tfb03tp8lsviihjekr89cpgngt36s0l4ragc4i3e4togs6813ai5vvs5afb82tc5400fho", "nlq0e08q889m4m1o1gvht4s4hdjcn6pcnud1qftfdddqbbrb09m85o32si75gamaa38mlcrmtnfk3pjvvpkjcu244ffju8ebd6q0dn0"),
("pc7ve88lqnc6ebgb8lflo7le18078re8jttcchl2ia06sd57v6nlaht65je4e96oi7esveoulrmgcbhp55eb9t1ep56eedk7ovrhstg", "hjr29m5o5v81mune9f50e59pdak0undh2j3qkdqrt8duaupk00dv992imergmf2ec9nd818me0894di5gf88adofufd4ub06tpasc1o"),
("pff99ieher0mcbstogstubb9kjos2b7lta5cvh91pb4hf8eg8ikd0vik0pkt0lsla67ik7i0iq9o7fjjeuof93t9c4l8cr9g3b15qgg", "0q4qltsrdvtgbgv6j9v0hujdmehiild2hlhm1hrj9f0g7bb138pvj7092plaf6acsdj3nuhco2aprn96u7ltvfue6d6iqlua37diir8"),
("psenm6j46817lhplfanuuvna9h5su7ogfhvi79epm49ptc6che5983ssvfqn7legjmadsju7roa0p8ujososh2kb0mkomc9gqqs4nk0", "lot58bu12f3eg0crntq8m7ip91a2d9gme53f8degclpinc03q0656f8rn6889qbmaah9j50h1hiilrgjt2cnelv5ko9idebtv6f8fh8"),
("q5j8kv34n5v8jfb1e61b1a446du3voemdp53v0nmf715sg9p1cd8ckqnd1ad2cepnvlv87roo2rjasj54jcb29cm0qr74pre8q2ub18", "48rahhqckr1j2aiathb7prsqkh5v6diishllp899pv01p6acd3auauab5mk98nu1turjghk6ll0ertjqm2c8ne7fs67456c8pro2vdo"),
("q865fr93lgnp877b0v66n6fusv75t4ecbvo5obr6o96778mv7rpf2ic2rfq57ov95prua5vma3rjeo10nn01d74rb51lpthncchb620", "etg4j8t9e9g4bt25gghl8ej38ccd8egm917ur4o0lkqb0pd1rngs9ns2cenq817pqgfi9nhkjpoo9un9ou1oupgu82hj103d66ku85o"),
("qdogo4feip1mdv92bblp3b61to8he4evksjp89mbsk9436fmnrvgfior52a6nobhidqnfkug1tuov88nv604i1t3hmgl8v8fc0pcnig", "mk7s2b3lcphhbj69vr2fnrq3bmac6dk8jk5k3tbmvncci0s07sk6a7sb7q8frnq8d1bfo07kbo04vkco2efb0ji6cefnlcggrffr2lo"),
("qesaev9h4bqdq3s1kctro1r1ll73jud27cn328qhua5jsi40burojsl4ic1deerneqn03h166nlnseo0jr58jauh0nj8p22lr3ppmho", "p45elpdig7n7pftlq1rnus4ntabtq4lfjrf3g3m5p5nrk1n7hc1dhskk3dghpnaiib3cb68i9bbudp0etnntngart1ulm8kn7uisqmg"),
("qo4r6dnh2hunlqasviummt73sk8u7f5v6vq3f94m6897jta6cvfk4t7q1cda21ga3vcndd1q5vhpdqn3ru3iango07e8261vrvuatao", "7pbakhn638951kk0bfo30bgdervefngd30s81ogk8r0qasb66krv8i9df3gpagv51oan672mctvqimrkek5rpkq83m3een0812m4v10"),
("qp5g0aigr71ctmni8hi8m8a6lms0hq2eenbq8aid8ohj6kmdu1lkoa2r0tajtvjt5jroeig0ivjhn94n10je6henmsfeh6ud0ndqq4g", "5h2oh89komirp2tifnsedmk2f8e0gvoplfr17kf5dse9dclorin752npg2n2fatbhavvvg7f4pt4mhpaqtd4pvlrue732hpln1vt608"),
("qrdbfdj5l15kelr77t42sv5d8d0u29kaath776ka77ieilkj1b4jqsnv2vtk3j0vr1h5bm7eg4baemv129k88rm4lto03kk6m5uk9eg", "d2kcusc6tlubr7nu8ritm45eab6momul5abjskq647pqd1ujrgfabntq1gq6ftk07qsq3gsfnq38gt89hn4c5grqvqfav3adp207nvo"),
("qrf3pihamrrc1puvs3tnrcoguo4j2c1gqr2mrgp7584g4pvfbokiqv7sc9s88o7025h5htvsbmki1bc4rlarofi66gjqecckiqp98l8", "c25mgrs2s78p63a0u0d9s6pqu55vrkv9a75m4gjmhj1orkdr7idfqd8lk5hl5k7h5leenotkvcq5ibirl1sit5il7gvf0jfvs0hiev0"),
("ri775mnka6soridkbqcmhm74ufmal9pj41hqsggps0f0mko86ngnpbmciq0ajsvnjib32ea0l3qaert270vcm4k1n63d2fhpmmnir2g", "8pooieohnt8j5qsol0daagjph8oi0ig96noatmp47n30obh6k93egc7c80ljofo168ovilff9blf4sitroh8dt48etr9oiamd8nj9c8"),
("rjtp304tcoauu560o4m6q3mns1l083l2nlveh524vrpi464qq2vr0isocdqh3voqu3igs2e669qkjq0ommptctvfd0cmoflp8s51290", "m7sglghrk5ikm6dog0vv5g6qe1en90vfcilelb7regpb8a1bepi5vdnlvguch0p1s8rotalegv6vntg6j5klbj72enlia018a8cpt1g"),
("rkqkpeihncrn50mv99a2mrtrk5h94e1en567il7oovpvosh8h7t8ocpr7ogpsdl6bh8q04t8170e52l276aqoekdcne70p31siiqui0", "3056jslm56dvd82rc0i71dv39gpdta78q19jnq72pveu1l584lvnt87hp2t7ughkiqmc5gl0ecm6513eg7bf1n79tldrr2kghuhem18"),
("rospkrku4cn77at8tbkkjdefnpoa4p867a0p79kp262ftv35anl2h3vb5uu70gq6cn6cpsfi1th9l1dcm09njjmgo9n046igmojhk00", "ciuk4h2f15sqnsmc9rnh8htusfpcdu5lpkrbjku1bgbr707vve50fe37p21tt1ahmat7f3q8nh7a3kjse8pi5jcmcpsss9peov37li8"),
("rvb8csi81lhf4cad2jp8ec7e9pmdd0299drsg9rbhf1ov7bckvq9uduer5jga40jc8bvoc00gge1etk88qcje4kgbhuch0hfp4t2fho", "4q4cec8lnovbubop6eenaqf5go49hp4tsbk05ote6ql4avgkeal8vdjvfcm1kb12et0soe0t5chn5ctpd0la0969r6lnd7a4luq68vo"),
("s77718qc0si32fhe8kc5bj0gc83pal923o144mbv6d8pbneaoasd4meadvauqad8matm0d6717et23dquu57fictpreclrorq9d39t0", "k89c04kcju8ftbm9qsrbhpn79r80esrmgjgf4mo38hk8s72j9o2pgumu7ctm4qcpu5rh5s9d14iipbqbuuq1f4d8k0p0845ju7oc3lg"),
("sib8b3lo8d0bg9na7rj2eq3ejikn8v5lktegdrc9ntvqdolgsucc14lm8un1ciq9665e7pa421ip9e9cihegg0ejrmleigri3hdlt18", "6paatmkfrceq6gd49tteobcgab1uuq1rudqt5vfok2k4fmh8dakdh39l5a0c2k3cspf4g796egkdh21lq5gr2lff7p17m7g9gfpqg0o"),
("sjb5tlu6btevoa7nooe8javv4lnebuk0oo8bk2jr09r8gmfidpqhdc90lr2nt81eutsjdk5l701372qbhvlgo0f5tnjesjk5mqtmcq8", "5m1mvp7eoe62osi03e3o1ulhneegcdrerpo6kr5g1u56angqsmu1v54dn2drlp0lrvgvim1n0bh9rkjls2vbajg4b8nd5ssq1f0g4tg"),
("sldmeehbat49okrmh83g95jv7d8c7dq817g4ehga5vkb86fc2v9lnd9t3kabnf66e2nhg4v2n7drc7csp50j641jfe6cl11s1lppu40", "idksta34i8n1k12auo5mer7lnkbvdq0rhe7lclkbvinvk26agpcdna15pg4t8mftpp31cl737h1aeanv91h0p67agpo2vldmfekcku8"),
("slr484921au0nfi51untjebhdllquir4ge5qfp1de0khl55clt8a8aiac31to00gtdr1hvi3g577fea3v1gagmbc8c1gql79m5med5o", "9m7hqphfvfkthb0lla1tdraa0g0a90pabfcqe8p8ps11vk8t2vi371dlb006q8ckf7p7mnn8soreudrht9k8og6crk3d33hvacoip8o"),
("tthuibl5msdjfcrgfvgdcl06mm5magft21ag59oduf0i01h5sru6armjj1v403bunc5tvsv09k0tkfrd9cor1d3qarvp3a66kkncrv0", "s37qk1fhfvffr11app6mick3j7qgb55v28b3q3dhbhdn1ir5765j99fr4qbsep7dbtqc03a1fp2g4hcgerf9qfoq301pqrbqqulldng"),
("u2pj2e7jafpj18u65p9r1qt28h897s5egtku4g9tj0fiamng9u6mks2gp4mvhbmlvi5sjnu0mhtlpcsqlhe1fs50go10mnostot4lqo", "j9rb1q0n0p2acvil7nk9gvacqd4frmcc982578nbiipqgha8iog0jmkcb0ukp2jhksa31esbkju3qimthd9sk1qao6cc9aejdjlp5i0"),
("uaoe2us2sqsngv1s978c4ndeejn7nv264k9a2q2vjmuidej4m00o2j7glrn8htuhcjrkccnh3c4ddpt61qpqmpajgl3p24ljdmu52cg", "nriftlrda1lpfdptclnnuk7f9nak8avgkp39v2ojqpd7v14t9hd41aciu9eh69nrdnc34o1sr99d1hge2e2vcveh5oabmlhuskl3t38"),
("umn2cbrivj68fems4qkbpi9hgjegrfvns7bb0c1riu713alp3v7d7dp44uerobi4elkl3671t1g6q98gcm5c87hhld1k7l0j9ufmc5o", "7mt5tego0h07a39e69p75gm2cno95s212n5vpklvcg7vf34ebf7e9jq149uajutbd7l4u90831o1q2gmpnmk8guefnst3uv7h6deon8"),
("uo8ft5fr5ik64142illckpt7fa0se1pnipn87vv0qcv8k4vjq8h9eprb4rvp55ohskv76888os1onuq2t4lpaogp2cpicot2gfhihrg", "0tjrkhtjcvhmvtso5up8kj9h20ftr1u93ebrlvdb7g25qk3cv9lljqf923to89f541rp2l2g4qdjobu2lii70cqnvamsnuet57p1j18"),
("uq1nlk350m8r4pegupin0bbflaapafcsvvnihe2lbvp2jbv4993khtk2rabv8dg499osdv671hv3te4023m6b2bjgvv5fk83mfm8ie8", "hkhahhcbaq5slmv9c1m6n53f92f85vvg6s370ru12g6df27ggk8uoqlevaflbca4oruh32u3pl6pj1jalpm6lvgmmdqga8g0ns8qa7o"),
("v5u6l75janqgfvv73mvmeq1kojl1aaoinkmmdokl6tcbuuh7gkm9auja82no1mb0fotdkbrl4apheteshrbo9c70r777jkcoa00vaq0", "t3cmqa9sc5oa42mdapfpi7je9d1h9pbugu2pbo6oh9msjrgmmtsva01g8v0r6q3b1rcmulonqk826gsv4cegae8aufng7mg6l8ffrdo"),
("ven5j3bd6b72k31gq6vd68itq6kfv6h920ddv8prcm0fhj1un5i0aj8rl85m7geclpg52u59savnea26ulceiurn86dq9cb6kk7b450", "dtf5vcq4q001rgv5nqgt1ehcmrn9nm0kq8mj92e1mnl9n5l5j1gr7ri4vaprdm3ab2efhuficgfeio35a7ro7j24h2ahjvqtm93jke8"),
("11se01mjqj583tmh0dedrkbn07vf4tko2siplk5hukj74kuin063p02aoub89nn5rlrqk3ukbtv29368pme7lhrb6rnjnmlg6vd18t0", "47eu9e0cplodd5ttgn2rf5l488lrll0s6fgbjonah0ea3pgk31ujv6v5mjjhj222kuao35i8jl2stprkpcc0mklpupb5knnm21lg1fg"),
("291j1n9ghs0i2b1r14tlu9054q21v34u2ema1lvmvri47oon2qta9bhak8gbmvcglljg3f8eedpek0jjqb5k9km9eb2a884f547ncug", "fmjavt8oc0dqfn5kaim3k0lukj9rd5ittgg4fuf5jhcdvvg8al7n76fdd6v43f4ejap0s9b4u9gebc3gtgaou8akaku1jbvalnsjcfo"),
("2ajhtf29l0849pk9rb9nr077vsq78hmfho2ruanrds943a1qh1hhcusf5qrdpjg2omc3e40o5uk9hiof4d463g0mcj22f4eehk33eg0", "jo8dde7i9gsq4nnul7dspnfm0bisps23kj1ggbjst8ookuvikbfg1vheppo7mq13vo51lvc4lmr9g91qj1nm5fr8u5r26g1r27ehnio"),
("5esf0fe80bopddso8om3dg5t27hlc17eimmg751b6j4tgbrfh99keo9btd14nok956d629trfh7tlasaf2k9uoaoslsv96ri4lr00fo", "sn6q5ehpqd407j31judrn6afi892vi1sl5g5f94t45b4o6etghvov25dhlks79tvcqopeb2g4a8egvvuun70tplgamqphl4ftam251o"),
("5i9akbq7ijj3vnc40cpg2d6sonrdjc2tv16l9g3kr1eb9vprmn1j3emiiqkgie3q81hrnlh3rv93mneeenafpap6dphdj1btg90deuo", "t2pra4iu1501sbrdaen2snng4sm188t2v7apgoj90pl0u2gut5v58fis8afa9ppgtsauajjro2fl0jfhkoomfm1ckvf0self6lkqu08"),
("63flsm2ia1hm09gojta67vo3pqg1gue1bjivtvrgn8f133u4krpk439ra4c1o4pp3piunljv3p2bguscochltkvmtm3h0gun56rur90", "qlv79as0ctvu0h9s1800d6a6s8u869hlu2qoq8fm0pvt5lqkj85bg5q28vttdlpbq0sipkebb1jm4b52nfvaqgcblt7pi5vrc4845ao"),
("6cv7nuk6jetardf741rflc54aj37s750n7ckh21elita8r4pjlue9ut2hdk8no29c848g79toun2c9hucfglfrltbe5uns97mhfggs8", "hp8unjm0stehf9fvl69u7khnm8q2mq8m3rifq5ckg517dtn5hg767n1fbfvq7dd7pg7jg76r8fc3d93nj25gqen7iuv9448u8ok9jv0"),
("6j8gb0eedqtiksi351ga6vnqe5n8tst530ubgsmkktdho24i9qj7ql6c33m5pmvv4th1526t9aqtu7pn5sdap2e0qp44vpbo56clt38", "mdijfqv95a6hhm9ko3ca272bpvte74octqkrlupgmfnsdn42dn321hpnk6m4d4lsi5mb62k90fuvujhcehlqbid9t93adtu72vgaqao"),
("6jk5kmaorraus8l84u98emsjhbb5getnjfaob0k135audbmgisgkgnkcv3rtrp8oumebr482m65o6h09vkiic2g80drr23mhaevok00", "v1s78emvrebpbo7hp1os3i914mmnse6lucq24hp1c3pof4pvf5851uonu6b8mljrl93q592q7368phdnuhh2d64cghds7onrt13i9k0"),
("6kten7l57l3lkthvabe0a658m2mbijpeucbhi35um837jq3pee26pj9i7mhkf25ugq4ee1e8p2d066bi5fmg7l0g9u73figipmag4v0", "edfr1pk4qfdd8cr9nke1mi7anu9beeqrnt4hauc4erm1rrlgitrdhd1uecheemgvegdu45r0rqaoagmpp498l2paime64d64uhab9vg"),
("7qlmikkr7dictp5eid28tnlkmqt0hlbf80qgcntpodev0v2d5eiushp53kempfs18l8cvdiesk2bd0rr20cbe1kj2v6l0n68d3o17j0", "d4mtbflb8tcmbvli7j5pqa5ir180ftjvg2o9qeqmft2avl04gb64rqpv3cn6tqmbhikrc4ob3j5ttq9goadhameebpni9bgjf399450"),
("99u91g0ra8o7o6bdu5eg7uhuvbjelhiu7n7ar1ag7kj4hoqllt1mo2sc38huhf7ffbtlvtbln53g7i79ieppngnhah9k2i8tab6r9bg", "pn5ddnk7eofsf3huab7uaa0g1250skejfb46oeqb20qafmltlplv8v5ue42cfg8ount3bdb5oagtrj804a0kchrus8khhgc41f1tpgo"),
("9c271kmmk35qjmfn58i7kht3q4706u4ookb7o18dsiod8d02s9efe04llkhcpsjihutfb3qn3jlmoarr93o9gc0pv0a14h4bsealqrg", "2ukp4p0tsbe70ei0a2r7jgrfup0mji4fefmplodc7knpvjfa1qjsi47pqcnm3qs6adod1bu90t0j1poq3bogsrvp6imbfn5hqhhm0fo"),
("9pv9ls7trmqbsis8hhbn3epn7j5vbjin97lf3asuckfquridoarc5tst8v60rmnchfe8555p7qj107lva38ic59l1d6ma2ackt4ver0", "44nba3n07u2e30fa9ee3hhb8immmgklq93at9npsqill0qf1s23t72b1agjum53m27fg1rit3i0b3hbgf313n6i059b9ae6lfn0ek6g"),
("a4ofdjb6lpnh44tqrorqa03be2ok2ukff5jipi8as1cvt7fq8m7ugkvedrplr4lk5pqq9or36u4i6i39gb91jsf0obkn9lamncbrkf0", "g7257qc7frnu3ck754r6e2jkdo79o9utrnlbsronk7gh0k6decvrb41ocgqtcu78n18f7ng85mrp5k6grukldc2iu30uuivnqjk56l0"),
("d9bsa320atbju3pokrchlqh3o4i8qkto7bi6ecjpq9k8a0r0pu1l8502hadibsgo8g30dcr27get07pmjkfm7ce6537n9qrbshb8ov0", "pi59htovmpuq0qnellunhdpbdg8h7fpqqrbmsb3got7vik5lds7rn3asu0k0v9c4uribpshlnrn0qlqtbrg32527778l26780rlntqo"),
("dq4308pcp0s69h62cidb0s0vbt59861rmkmbsbq5p6rmiifici3hig4bs326bp6vo5k162i264rkmu88ogr6d9cd0avnatt7eqlf2m8", "n6q11qk1n64d2dtsvbni0gjvl2p0qf9uf7lopfscg6974hs5m6ddf9ka90e9rjcsbqu7cs2voivs01jqhad3b936fiqfgr5h981flfg"),
("e90mqi0ggqd8jsacfo7c0ddjl2mg3slivopl2ml4ocvvoija59usoeg9qn66apkeo6gfif6vlhack4o3b9k8o7d243bhk87q70nesr8", "0n492tgukr104v1gd9vjhtt0rc335opcqodsdlb4ar4r74l8hptsr3mf5dvimne1uhcjuc2bkq90lp1tp85ra7mn04v2tb4i42emt9g"),
("esa4nsp05ep8665i6lg56t02m7mjcqt6h6e6jiv95viq806qgbam08b1bf9rfsrhrvok6fo7t2ejm9i4aqjobcnp7gthu9ost2f2vlg", "8ri6albnpm76jkauhp7ii98eklsqj73lf4f4cdikr577nk33rn8cl1mk7brrurminn5plik4cknab19vsc6lgdavsgp4hsdpkv7iefg"),
("fel6cfkjut055jvsd8vv5r3rrujjdnsngimhm2itnncoumugu5c7scl33pvld0vgpcs752vvk1jd23gs8r2u15ltfgpbcmvedsv7qvg", "4sgh9as400t9a14spmnrclie422haj1rgfef7v0h20ne59reh9l34tbjspo17a5gm5bji5l60pt8mfkh9vebsmqjrsru29t6eluuh8g"),
("flrcqnllakdfgog09bmuje5l4b9kftdh5ueu8ls3hddd7381fncjrruuuv087feohkhon9fvk92i336vh4grranlgale83kt3dmt3s0", "n951og78idps50cue9s84u0s9mrrijvn9cr8oa5ilk4vu008k030l1144s31u3sqchv30rc2odfrmv9cfrik130c0vsd9iosj4n7c68"),
("h8vcl2dhrl5hivpi7gj0qu2vfae8rlpvvlarcs2sfahcnl31p2bntg38qeeep923jt915h49ven056l4fq7b11dr55deghq1lpa7488", "bbv11dk7kgpf37akmfdbnh2mjg3bvfjoebgme3q54ou5no9rp1kmnsvd37icgstdcsnl9ua80mn80glhu1t5iefd3dd7s63c8ee00so"),
("hbfrobs8ht82n9tv02i29uqefl8elm4buq276e7jb1kvs9s4ijr8t29qto60v9o9sdtahj2v8gutv63jgmhn3009nqvc450ap7p4hag", "ijbs6ccseuiqcvvg8i1ama25ps21e2olqg7pgvubkas37cabfsb64eh0auhd9bfb8dks6h7iqjclg7928ukhka3t1sd6ea9jlpkcuao"),
("hov00mpubrkfuf43hnctn0kgdrrf7f51q90del6gbo310q78u1u5bjcrqkj2dnn488733r1v9p9kvl5dsc61ts5uobnm77mh20fpep8", "jckagjje7tbt6h41iihrtho956pb36r8i5i82c4kp9u836p2iqa2rnuq5e0mgnj8f6e2oarqfh81p038v1c8duqc6n7kehu6smknfp0"),
("ihsl4ig7v61fp7chnfti8bdbr4i665jo333mi2cteci00594r68je72nlftttlo8og932g5tfhmbqcf93m7bpign0ano8tmvk254thg", "e72eqvpaelpbudvt6os5hg9fp5ah5ostkguabkeru538qi0vglh24r1pnmmfs35mj97enlk9hmd0sjtrriv8nunrpr6g6h4e4f8o9t8"),
("j30567ba414i1h47eties19kvejej0phhdsn20klueu5meq0marq8emee2p6joguagv05r0qao5755fp5jcer1hb5she58mcbiagrg8", "voqqk3utcnbfhrjlnv58vphm5ro7bf0fa6tfuhlt9lnhda4166mb7hg8a8lta1gg9u0iogbm4lgc8ccg8lv4cfkhau21fmb5d2f6cdo"),
("jg12ht84usj2ipd9ki4h4aqpq14betjq8u9ns4sk4ne374d6l6foffodi959dd1s8vovfqqmgsep2len760laq23acdt8md3joqr9eo", "nulmkacgmugvtdj1ae45fdmgr882mva1ebti48cffrr0d8tcaqdo38v85mq0q7aqkp1784rhg8l1n0djpvf3aop6blm1imana1ssak0"),
("jvg0ju5gt6gju4ris1rbkllvoobvhb9ju1ng02rcu9d1d3addmd696m3lsp7e4co5bcafqs8sisr7hirthg79o5vld43kubd10g79bg", "m38g88098fmnufihe00m11p4ikhdenjitajjmj5fchdtdvhu655hi60q37ilgpnh4e739mdf927ocatu01ucdnbsn16243pi4i7ebho"),
("luqftph5u942l8niuffm4a2v1t3766bc6pl9ud8u6ert8dutjismcu6da1jo4vi5td84psuqkdqgpfr4sudl0vrlsndf8v4kv4s64pg", "14rccbkqgj698almlk3abb1v8tler43f87vc248qsr6lhrcd2e02n74fgi3ttqhlfuhonslg4krae8q97m3mh90850q5dr8qvv5hgh8"),
("mf3fairgfbbiqsf4f2ku29jdeevj3rb9fspicni3krs4i1cj7vlrotusjloco990ut2agi1pf6oibigobtcvr22itm9js13hmmhnoag", "c9pj9elsfe2dv96mf1f7ss2oo24eo5n0u23s20huscvkue4s7u92uis292b63gg75k80thsddmi2f5u6rh4gcdmrt4p7vgjmp9c6mjg"),
("mil81ef2mj36ejmvndficfn4kue15fit3295dkjjdnuvp4evel9dulsbdcpvrp0onplrec2ds6pra5mc2u8i2f3jpk06b14s74qtq78", "jvbqk3bv9m946dgtbiv0ljdhgmdibnpt20p5hh49ptklv2356adbbjmm2dcj6d389f6v8078vlno272ujmlhac1j3drfhiho2i5ccg8"),
("mo88m8rtndkrvru1slk41k5f0bcjsam8n3786ea5d2tjs78gt8asjq0eblbmhrhll6r2vo7jrsri4af31feii1vos7kqdt92gsvndn8", "15hii4lifsrqgqu567ipk2t2r3381c2oa18h397ulhh84f9mguqg74jlm5m4a7el23qi61g501dmpfducgeg6dvieo0m83lvkcr5jqg"),
("n2qd0t4mo3jrlauhoj24ae7ijt80vkt1efsh35aagkrvm2vurrr1fg66h7gip67amrtgivpgidqccfa8cr1rgl7tte90nr8n3uv6mq8", "6hd0lprklto0gbufrdgee94otg2hp7skidd3ovdfche8t0arfe7pmp17srgigg5gduqm3nmq8c7b62b88171ajeparcrrcdl0jpnumo"),
("n7ot2orhvskum0u6n9d5bq7c2f8gnt1jhorm42in4rkcnkk4t77febh158vkjle8ooe3p3bdoul881fhujd7amsdot72o1v0v2atvgg", "79ckacnve0sig5mah2235ge019b6nfr32euh8ep3m0d1stqbimftsh3gcrbs56ruvrc8d2dk7dlt42o95iuvpbk04h6dpjiqbtk41kg"),
("nre73vpb7v911qflbtbj5entpj81na4uomrrsau4bre1m3sm70mbek7r89rhrilkcthea4llijnlrhnm72q6pdh3tdjlfqnqal15rc0", "fle8tu7a87te6cucto610ccces63lnqu520fa4mqgfha0kjuano6emhl63ehoqbr5ae1036qq5np4ri3lsql5ime1rhj3sollfnt940"),
("ph7l55r3bm7hbv3q0v7qokg52315hfujahiveih2ba2i8gmuf5ghuifii038d8rmu89fsm012nkgaru4cn6tlt2600uhgf8ro9dchdg", "iuck0jtjs0vjtok03s8nvu14rqipo73sl78fjv4nvgp42b6bnh290fq86cfabhncg1756n9ctuv44grpasccekqntu07dhrsq8715sg"),
("q95fb8hps3gt1gs3qvfjt2soi45dbjdm0sjomhd3ghmdm3lcou9vcl143no04uq4knf8qm984vm626723gmpgaeietq8f6g0gsn76kg", "v2p9hlkr3k5libn0rriinulelhmajse5gfp28g1pllnsdnuikiq611933gthfbse5lmdh2f136g2m4nqbacdlaj6vg50hoea72nln20"),
("rpn7jo16d0btf9ju7u89dllepvbe9ukcgen8v1pdel5s0e1p8ht31lbgf7g6acfdad4gt0bubdalkk99ious0478h4oo9shalv628eg", "mgsfc3k8dglo1ub6luees8a1h05v5lmg3p3f5f1ecb56vs9fid3n3dqib9ou9qth34bbnbjd7ge5md35563dn1sfrqpsb53pscih558"),
("s84rjct8m4agtnb45tgbgrl2hpd0b4m5e5njv9vs2reihip8nnf7gdmdh8rikpthvletoibofdpuufunmd4ofbf2crcmhi8l6lmcfu0", "9552iq7lq8lbjqm2ff2hvvv52i9h2u6jfrphhdja9gu7tp2n5ea9ao1dkt6ne7g6b01s54dnhc4qj8j23nend5tnoeni6d3tvpjv1m0"),
("smg7gq794efaabj101355km2rnc064j7qjha0ldgbt9b6j0rj45m954nidfca9cnkeghcjjl7nchqm7pqu4l1r99bhv6o49hdq5jfm0", "ngson0k1fokfjah0eo0me32ocea2e6plvh8juvrfrobqbvbl7pdgm5qaurr9suthhrl9gsma6cgk7e5t6lm1k40uk6hpvu7qae7hmh0"),
("t6utrl2q1naocfao1f470616rkbs1cfv8r4l2i7rrnrksjleisf3p761ul2d4d6la71jmmls9il2l779k9ul0som7on4aeqp29ghgu8", "olkaf0ld4frt4egq635clrnp8u19oul52ie8dp4ko2fsn1npjjeonoog1qf9ssu24s0hkc6mjefe86r851pqn8ptu07uf7oc15prb78"),
("u2rmg2tq3e0mjjpc3ou3isffio2b7ja2lir2n7g9cd8jc30um9m06ufpp454lv6373bpr2f89u6iqah409auq3ut5jfsauu5clbt4gg", "o4rd02dp9d7huhqh26g1e1u0kah81vnf3r6op9otm9mpnjmnkcipnlv4r1350fifefh3ij59uji4sir5htn7adav2lharhutbifmc10"),
("uh92uohv9i940uri8po89as42vmvithsa9ookqn7i0vab55mrqd1rst0k75e80ao8sas2sv0jg1p58c8es5llvqccosbhcb6e5867pg", "u1vv1bv1pdpkjdqa429pgbpdptvpkelcgmcuun4slgjncphmuribp379jal2ob2rf7v1b7hf8ked579j43dmbphe8dsb1q5o1s1enbg"),
("v6bchcpseku2gqaal4pu7clceq021gkesk4fb7m23r5ck6dqnf989fa5msfd434hkjn0q4kcski41m311lhot4hr6u57b57dort4clo", "qfa3htt42po2oeb2sfp827ga0lgimhkplgdsep9fsu8bpgpof78gqg1up1e49m599co6j5jbugsfqq3c2o1ajin117t18agmgmtuqio"),
("2d4g7c7cvm1ptq309v2r8momvh4e0bsc0q65efovieldpqcvrlulqnrpn5k04kmcr6c74d1scud33fm45l6tis9nkgqpru7vvl08t48", "e7dpcitb5onit0a59gsbq1cji5p8nkeid9meoe55aougijvad4urjha6fjburrqnov01ep4ir1r8ie040kc1e4f76tvvb7cv0m8tjj0"),
("a27cq1169j6r8pqh73k31ep04h0ef4allhdtna6m5hoqdfka44kpm831ja8h6tbchcp3amo4jpu32r6j05dsq3rnuikrji8nv6c6pi0", "6q3qb3b5ht6ngclocisa95olneir43bugog28ve0aujjkujkd0aeic7vd7vi55tdrl03l3sf9job5k7v6ntsg6u1kfutguk1m9nuc40"),
("mq306husgfl9h34p13pq3llgukk30v28f37ff67835gpr7veolv0kbla7tabcgah76im3jcjv570d581rr45ldu8l2326llomv9rlg8", "mmo212ipvan6p5smivn234tppr5npslq6mbf59q40j91fkqcv5venanrsr6qthbpc14dim5kq78qpdlch8m643ek4683ddnu9mcmb8g"),
("sjpkt6bka1v93p3vb6vvcoolinavpkm6cbno1fr4mlsba2j1qb2v1gtq4kfb5cf35ps2okgbkqc98ohu1cb5umcr0e89lsm21thup1g", "p46fcqrd2qmsp6n14uvootelsj74k7hj4hpu7f5mb2t5pmel9ef3tpnnfod1b45e0kseb9hmgamt1cmhd2fgoa4lcrnrm619b6hfcdo"),
("4h5fi8ubl02p1k0t8o19fggf5i8i1o3g67bolpbh0oqemn1vhg731t3h6l19aged568o4t72vfb8ejslmdpng90iqqpq7e76rh4sgvo", "e07nsk3ur0f4v40q0ha9gu2td5qotlck410t73ad0ebrq3rseloloagf6ts04vn29m6cp8n93q8poc9vciisbg1oksaso7dkrc4i3u0"),
("o91ntd0l13rtgg4ti318g4e56q8sgmdvab52vs11ubi5asl1ch83qg5vdtv4u5o2m1piu1ehj5an46tlv40tfc8k7frdld0bpofhf5g", "gldct23ikpt66jlmkc7bpv8ahdq0kj3d3it7tbso37v0aarqe6tr40j7jvteoajj8jogbcmtmm0je4vfjb8pvut4vhmsc6gqm4phhf8"),
("ocrak0q8srvgd4idso6fuvv912ilf1r4641sjrronit3qs2cdqkgqrbdapbhtgdv1kgu2gjogei0bokqg6ejv827a63361vcpl7ll38", "kbc2906u5pd1ip1hrmsstkgj6im8bpku5f6kaoo4qd40fho2452t71hmsi2fmt96siv56rim9cv1hit44cbv7q0mtv5a6hf8alcc1p8"),
("nj64m87s3sr8mlvmbmfl6ou7nab5cckcka3tcil2rr4bed68v6b0cf2gda46pjs534bd1ee3p5hih3qmghb8tn1iplcg6tfqrn2kkso", "cci5piaddmv8phht8p3mkkbitkrm06ana63rslvlgqt0vfqs27c8qoulklb5ko6d739ijppcb07ico8dlcnv39uh3ksh31mgqsv06co"),
("tn3enmqnpffpfdlnqneuavhpr7ktludl7eshticcog2h9ng0nto602pd7o4etln7g8t5rrk8bo4tuc8jsr4chtmi99lend9m9m37j8g", "5e9vmep6hv18h8g6sitafllai8aisrqur244cqbh2uphl1cgp30nfkkb006ph3ph0j7ifinhhpb4au9augusrfovcq16vh0iq4u4hmg"),
("a8g1ab5hbotcdnb4vq71n6s9967riq2bmib9bboo0fc3i3vnrt7v6891lfrjmp3jnqeh87d445e4tm4r7hmeul65edou24o6m683v28", "2m6kvrgtfdb4ld9p1mtrc0h1fkhlq8jtluoj6h59iqj7ids0skqubjghjkkdgtrmmu8ltu5ok4vtvk1sr1036kcu3abkdjtfjfo3b6g"),
("0a57bkr1b3cr6r141ete8g7tmlvtahhmfumiicu46eklphohci8g4ki1555cjqj1tfups7mlkgq0b6htf619d6vncpgu3umt8cjg3ag", "9gin6aunfst331o2ap1i6p5hbee6v7hv0dakmabv5pcfooaufftej7g8uipejj8qvg37tbf2anrkacmal942g8h4pbcsn4m0cqtlo00"),
("b5p8dplpv6risb895b87d8qpp8gppjhdr6heagn3g0crbuvqap34f00hsenedngp4ed0uggqq9cqt160f1trdo67pmurm9pllnd9tr8", "897sfboju76buq7kinijrb1uq0o4vs07o8acjdu9o2c8kgcqr7jv0ts9ck2cqe4dgr0teg2ijgdo593te85ee1g5qnd8qtnhldhh2k0"),
("e464qo2hsdto3uea4rgjmllfltgor2kcvodvftep7735bfcq4pikg9glfj4f7qrp5c2j5ubrk79mrm7vdhue6vqcra97ufdgg22mji8", "jt5f38krdocpdpeskiq45oqbp8gfhbkvrh094osoq9fheb3et4iigjafktppenre7fasbnek3ck73a3ge5vc4a355kt9d179uc13en0"),
("jn2gmtgjmlllqnv649ngcnor0lb571clqcn6kqqbql1fi78jmbaocutjvqjp6f8cmssu8625eaksl6rlnagsndsl4c0cta2fit9dcto", "d0etssnn0ubp7jpe7373k1htd6goehv2fluo69or70trh7eo9rik2rpnsk05v05inviv07k1fdvmkbmmabqg9jo1mlddg5pp9bfss18"),
("rvpgb89fa6dn92tvf177lj6dh7bmn0fir07fsnurnv9j66pcs43642n6qm0i3vgc5avr6srtj3qq836o1vfneid4dpdbt1o6ie80ir0", "n3ng7lbf025f6289ojujb2fqu3agn7c2a2krraraarlhro2nl7ta6bse36584obdb18luesc2q0e48diu1202sdr2efcbu4uc9kfaa0"),
("fmv6e95597m4vh8e7rd5frbkve4nmfg74dcm61vlg9v6c1ga0im1n4u8jtrfqsakbqaijkj0teh4m1kjot2muo78jlvaab939d9bvl8", "aid3rhj1cno33lgt6vjt6m340vrj63u7oqncbj4deku40smo66jp29mn1h40jubvdjvje37plrsdfr77r83ldkjssiile3e9kup0pig"),
("kg7ed18m2lo9hgn26sf51v7f1n7ipnq45kruj3cp733bngjbgbdnp189r6lugpfgbcciihq5t8kogbvvef4p66m20fuotuchggb2fh0", "gvdjv6dh5fl9qa1e7daqifggd63hief3v0uivq9j2ofbjmbns92o4b61cvsfqpop041memg7pr5t7ll5evv36ic6nj3fqa5hit2cng0"),
("kp7etafhe633u9sc0ov2knm1po2kqrcoa389sqliug4dthdlqhdjm3c3rb2sacdcvjvbol8nro6dv8d8e30v4icfpq93ujkt6ce4nag", "em4nk2gih8feb1c6ecfd5f5p35dsgv3u4ugm4gbujs6is0cccbe96dn472gqomon2o50rclpqg6u1387p7n805p4cq08rrcr16tenh0"),
("9j8briv0j128i59qcufvclns3qvgoiho1oq6n0fa5fhm3n308k2d246qi5a1rff3js0cue03tc392mcvnn8hqcn09rq176rbpm5mgn8", "l6uqqrt6un47us7k0l883pfg7gluip1762nbr977tf8fpqgq666ah9b4g3f7oum64fios4i5is4bgrniirnlfeqheh4t8ekgr4ejbbo"),
("c9p6frkpkgujmuc364nmehc76eso020idssuvvkaalte7ou5qrtjjnbftuk4lahr4phpi225s04u080g46nfuvri1s1jimbte1vi2kg", "t39fo6pvdrncfuiefpqv44b6l3jmn7haeo95c2eneothjr3tbh9cv8eapuuc0ffb9krihbmtgb0dqqv6uvpjc7ff0b476pot53vt5m0"),
("gi8uvgojgkvdf2ka9hrqtng1naol1atnlf04g14i14q0820q8oagfmgpe94cr8405ps52ah9e2977cn1lrcsd4ufft6a90klpivu5jg", "bfl51kvuevs2bt633vashcp8ouvc0lept7vl7k76f6f9j9a8npjoql3tb4e9doma1ncp9bhce5cnmm4q22t6pqtr5jisgult2l0sr10"),
("o9ldnpcalh3q1bvrq64pr3tbhi50bt60no13igihrasreellkfc0iifm63u52h608hvtdlpbndmg10dni0boum0fnrjjo9cojg75k5o", "pk5mu0gs04r3tot0jh9tvaus5ei21vp021298n6lbj33n330psi77rdnn9714s07u5gjq92e2kjjvf4s3b67glo1nj6lla2h0db89n0"),
("sursujvsg0468s8a9gn11rtr0bdks9daqv36h94uhgp89977rifc6une8ufg20bidgo4p1dc8321j19mtbgpp9mftuu4do8n8tvg00g", "bbrktmce401br66spoe48kk6b2j33pc0q5fe4sba4c6g4agp27n8qq5m0n9glb3oc15evdkdttvfcrjbgtftj9qfd1fr7epm0tpdog8"),
("dgkv4ts2hmghefjthqotqnd8rqo2sn7qetgnrcnot1e9imgb978lsevuqfetrl8r9g93or7arndprq23v53tea33eib28rfgc1go7lg", "194329el5eaqe8sb5c6894oa912auagqrn83985mau6u2g74efdjn91dj53l9lsmcgb04unvkm0rlu81h8pr0v4hlm2b4ug8ouh25c8"),
("qq4t60c82o8dfic2nnriloqu7m7qhejm446dlf15paect3n95m5jcfquit808bg87tud66pvbur7n7bc85s9dohj9ne1d056isp3q3o", "f52fqh6k1hesk4ev35qpm69og0ph9gdggev0io1paku9o1qfoa1lo5udoe0t52gevmjm3go1keg65lc9t1r36nt65i3dnbj3csc2nvo"),
("330vds2bmg79kmdm1n50p1pv5ulhqf77imr1onsqgurn3d8t4b73j6ev78sfk4ghtkshai7laacuromip9jjkgqvcf0bnnvst7uh1v0", "8lh44n6ib5foap0q9cjju85l0go1c3u87n501fna8rcefhs3kk311i60t8cpkt2kljbdta49kgbf3uonglu84ne7v2943m0h8fgmh28"),
("6bg7aq93ultfbibjp2vmd2gpanognpgcvs9h5edr97kqaeehpsbder6ol0b2irgcdm9u3fi482p6qembl04049a720d4ek3vveeajj8", "ueo1bsivtf0ae533kpj5g4o9cmk39562mgl59nvtmg411pa96dat0u3kr0k4nvr3h6bu6l5o6juo9ag1bd1k4kl8iovp2qspakffvbg"),
("fb9oiu3sspt0vtlpggh5sh2a6rc4mmpmlt0cqbiis3jg6531nitqea76ktd62c1drv3hf61jfvd0rkps62hfvknaohhv7no21l93qng", "vcso8rleqfs0itgtclfbi02apos7pbgaiahvbp20vppqskr07ci1lb7nrqj3u3avkppr9ap166pgmni2at224sgobh9vt05e0fk4bq8"),
("hfaj3bm5lrun3giv843hc8der1r4obars3af4lk86gj6jf02g1i6spmm9ghgsn6kjj2r9ulfj2pp1fckvpk12mi3574t5eki3ushuio", "uu5glnuklimsmtnlo75i4otvqkib5pfo7oabf61hrbneob419u5jnvg2b834ihiom39pstpi75gafnh5jjg4qhn4itajvcp4mp5uhho"),
("r4cj1g20i1ehhhb023o64mt2b4ffaqavqrj40jjueug5tkiq67e8kmb57a2kebmcghtrikd7sapcdkqv01vj8eki21ih1mne6hpbe0g", "vsbb3e5ml2f9i818rc7t4cfj3jj1u887c5snkuh749t5odn2f3ob2qr886mnv0jd6gtqggfupk4lsfh90fgecjuf6755r69nencf7i8"),
("vcvo26v7u8ifpv32t9srculth7efb3sdiuicdkrsr564bkqt0k0ibv73foo11dcr6lpomfpcortvththnffkh5rnnpi62jq04vpgc8o", "2h42daj99t2ies7kdq6ldhmkrcrhcntcjq503q9trsisr9g34lgk5gj6gdn7mglpgb7nlnp7971shr0763gvg5opmjr4lca7am8nj58")
]
expectedCausalHashMismatches :: Map Hash32 Hash32
expectedCausalHashMismatches =
Map.fromList . map (\(nominalComponentHash, actualComponentHash) -> (UnsafeFromBase32Hex . Base32Hex.UnsafeFromText $ nominalComponentHash, UnsafeFromBase32Hex . Base32Hex.UnsafeFromText $ actualComponentHash)) $
[ ("2ka6lc5suqjp1j323hsqe0bbvg7pnk5bo3d7e5ek22uvpsivormtoj45fh70s2f9odl7d3bvaa5802pd7aai0kid0iit8218752fij8", "8nn80pp45l23i6hnko8uqushhggp32rrh2euf66dtrpqkesa7647sosgoj8ol8rand93sl1a3recdlm9rih9lcm8mmk6f1qm1iulbbo"),
("c311hak51uqhs9ouu7tu9ukjj5qfk1pfismucnq3njjkbbaf8im2bq79cn9ofe04l6j5bjcinuliulcqroav3mk2gvggobs2tj1juno", "1rr75t1svnp0likhj027ccolau8l56hnmk4lupt3lm4f5upajsfefbr53so8ldhi0uhsqh8mnjtkqs3d3bqfqk5nlgfkp1v6md2s87o")
]

View File

@ -61,6 +61,7 @@ import Unison.Debug qualified as Debug
import Unison.Hash32 (Hash32)
import Unison.Prelude
import Unison.Share.API.Hash qualified as Share
import Unison.Share.ExpectedHashMismatches (expectedCausalHashMismatches, expectedComponentHashMismatches)
import Unison.Share.Sync.Types
import Unison.Sqlite qualified as Sqlite
import Unison.Sync.API qualified as Share (API)
@ -80,7 +81,7 @@ maxSimultaneousPullDownloaders = 5
-- Share currently parallelizes on it's own in the backend, and any more than one push worker
-- just results in serialization conflicts which slow things down.
maxSimultaneousPushWorkers :: Int
maxSimultaneousPushWorkers = 5
maxSimultaneousPushWorkers = 1
------------------------------------------------------------------------------------------------------------------------
-- Push
@ -460,27 +461,38 @@ downloadEntities unisonShareUrl repoInfo hashJwt downloadedCallback = do
-- we'll try vacuuming again next pull.
_success <- liftIO (Codebase.withConnection codebase Sqlite.vacuum)
pure (Right ())
where
validateEntities :: NEMap Hash32 (Share.Entity Text Hash32 Share.HashJWT) -> Either Share.EntityValidationError ()
validateEntities entities =
when shouldValidateEntities $ do
ifor_ (NEMap.toMap entities) \hash entity -> do
let entityWithHashes = entity & Share.entityHashes_ %~ Share.hashJWTHash
case EV.validateEntity hash entityWithHashes of
Nothing -> pure ()
Just err -> Left err
-- | Only validate entities if this flag is set.
-- It defaults to disabled because there are terms in the wild that currently fail hash
-- validation.
-- | Validates the provided entities if and only if the environment variable `UNISON_ENTITY_VALIDATION` is set to "true".
validateEntities :: NEMap Hash32 (Share.Entity Text Hash32 Share.HashJWT) -> Either Share.EntityValidationError ()
validateEntities entities =
when shouldValidateEntities $ do
ifor_ (NEMap.toMap entities) \hash entity -> do
let entityWithHashes = entity & Share.entityHashes_ %~ Share.hashJWTHash
case EV.validateEntity hash entityWithHashes of
Nothing -> pure ()
Just err@(Share.EntityHashMismatch et (Share.HashMismatchForEntity {supplied, computed})) ->
let expectedMismatches = case et of
Share.TermComponentType -> expectedComponentHashMismatches
Share.DeclComponentType -> expectedComponentHashMismatches
Share.CausalType -> expectedCausalHashMismatches
_ -> mempty
in case Map.lookup supplied expectedMismatches of
Just expected
| expected == computed -> pure ()
_ -> do
Left err
Just err -> do
Left err
-- | Validate entities received from the server unless this flag is set to false.
validationEnvKey :: String
validationEnvKey = "UNISON_ENTITY_VALIDATION"
shouldValidateEntities :: Bool
shouldValidateEntities = unsafePerformIO $ do
lookupEnv validationEnvKey <&> \case
Just "true" -> True
_ -> False
Just "false" -> False
_ -> True
{-# NOINLINE shouldValidateEntities #-}
type WorkerCount =
@ -624,10 +636,13 @@ completeTempEntities httpClient unisonShareUrl connect repoInfo downloadedCallba
pure (Left (SyncError err))
Right (Share.DownloadEntitiesSuccess entities) -> do
downloadedCallback (NESet.size hashes)
atomically do
writeTQueue entitiesQueue (hashes, entities)
recordNotWorking workerCount
pure (Right ())
case validateEntities entities of
Left err -> pure . Left . SyncError . Share.DownloadEntitiesEntityValidationFailure $ err
Right () -> do
atomically do
writeTQueue entitiesQueue (hashes, entities)
recordNotWorking workerCount
pure (Right ())
-- Inserter thread: dequeue from `entitiesQueue`, insert entities, enqueue to `newTempEntitiesQueue`
inserter ::

View File

@ -129,6 +129,7 @@ library
Unison.LSP.UCMWorker
Unison.LSP.VFS
Unison.Share.Codeserver
Unison.Share.ExpectedHashMismatches
Unison.Share.Sync
Unison.Share.Sync.Types
Unison.Util.HTTP

View File

@ -1,18 +1,13 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
-- | This module handles parsing CLI arguments into 'Command's.
-- See the excellent documentation at https://hackage.haskell.org/package/optparse-applicative
module ArgParse where
import Control.Applicative (Alternative (many, (<|>)), Applicative (liftA2), optional)
import Data.Foldable (Foldable (fold))
import Data.Functor ((<&>))
import Data.List qualified as List
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as Text
import Options.Applicative
( CommandFields,
Mod,
@ -55,18 +50,18 @@ import Options.Applicative.Help (bold, (<+>))
import Options.Applicative.Help.Pretty qualified as P
import Stats
import System.Environment (lookupEnv)
import Text.Read (readMaybe)
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.Path.Parse qualified as Path
import Unison.CommandLine.Types (ShouldWatchFiles (..))
import Unison.LSP (LspFormattingConfig (..))
import Unison.Prelude
import Unison.PrettyTerminal qualified as PT
import Unison.Server.CodebaseServer (CodebaseServerOpts (..))
import Unison.Server.CodebaseServer qualified as Server
import Unison.Util.Pretty (Width (..))
-- The name of a symbol to execute.
type SymbolName = String
type SymbolName = Text
-- | Valid ways to provide source code to the run command
data RunSource
@ -455,7 +450,7 @@ readPath' :: ReadM Path.Path'
readPath' = do
strPath <- OptParse.str
case Path.parsePath' strPath of
Left err -> OptParse.readerError err
Left err -> OptParse.readerError (Text.unpack err)
Right path' -> pure path'
fileArgument :: String -> Parser FilePath

View File

@ -1,6 +1,5 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
@ -70,7 +69,6 @@ import Unison.CommandLine.Types qualified as CommandLine
import Unison.CommandLine.Welcome (CodebaseInitStatus (..))
import Unison.CommandLine.Welcome qualified as Welcome
import Unison.LSP qualified as LSP
import Unison.NameSegment qualified as NameSegment
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.PrettyTerminal qualified as PT
@ -278,7 +276,7 @@ main = do
Just startingPath -> pure startingPath
Nothing -> do
segments <- Codebase.runTransaction theCodebase Queries.expectMostRecentNamespace
pure (Path.Absolute (Path.fromList (map NameSegment.NameSegment segments)))
pure (Path.Absolute (Path.fromList segments))
Headless -> pure $ fromMaybe defaultInitialPath mayStartingPath
rootCausalHash <- Codebase.runTransaction theCodebase (Queries.expectNamespaceRoot >>= Queries.expectCausalHash)
rootCausalHashVar <- newTVarIO rootCausalHash

View File

@ -39,6 +39,8 @@ where
import Control.Lens (Iso', Lens', imap, iso, lens, over, _3)
import Control.Monad.State (evalState)
import Data.List.NonEmpty (pattern (:|))
import Data.List.NonEmpty qualified as List (NonEmpty)
import Data.Map qualified as Map
import Data.Set qualified as Set
import Unison.ABT qualified as ABT
@ -147,19 +149,20 @@ withEffectDeclM f = fmap EffectDeclaration . f . toDataDecl
-- propose to move this code to some very feature-specific module —AI
generateRecordAccessors ::
(Semigroup a, Var v) =>
(List.NonEmpty v -> v) ->
(a -> a) ->
[(v, a)] ->
v ->
Reference ->
[(v, a, Term v a)]
generateRecordAccessors generatedAnn fields typename typ =
generateRecordAccessors namespaced generatedAnn fields typename typ =
join [tm t i | (t, i) <- fields `zip` [(0 :: Int) ..]]
where
argname = Var.uncapitalize typename
tm (fname, fieldAnn) i =
[ (Var.namespaced [typename, fname], ann, get),
(Var.namespaced [typename, fname, Var.named "set"], ann, set),
(Var.namespaced [typename, fname, Var.named "modify"], ann, modify)
[ (namespaced (typename :| [fname]), ann, get),
(namespaced (typename :| [fname, Var.named "set"]), ann, set),
(namespaced (typename :| [fname, Var.named "modify"]), ann, modify)
]
where
ann = generatedAnn fieldAnn

View File

@ -37,7 +37,6 @@ module Unison.Name
-- * To organize later
commonPrefix,
libSegment,
preferShallowLibDepth,
searchByRankedSuffix,
searchBySuffix,
@ -67,7 +66,7 @@ import Data.Monoid (Sum (..))
import Data.RFC5051 qualified as RFC5051
import Data.Set qualified as Set
import Unison.Name.Internal
import Unison.NameSegment (NameSegment (NameSegment))
import Unison.NameSegment (NameSegment (..))
import Unison.NameSegment qualified as NameSegment
import Unison.Position (Position (..))
import Unison.Prelude
@ -361,16 +360,13 @@ preferShallowLibDepth = \case
[x] -> Set.singleton (snd x)
rs ->
let byDepth = List.multimap (map (first minLibs) rs)
libCount = length . filter (== libSegment) . toList . reverseSegments
libCount = length . filter (== NameSegment.libSegment) . toList . reverseSegments
minLibs [] = 0
minLibs ns = minimum (map libCount ns)
in case Map.lookup 0 byDepth <|> Map.lookup 1 byDepth of
Nothing -> Set.fromList (map snd rs)
Just rs -> Set.fromList rs
libSegment :: NameSegment
libSegment = NameSegment "lib"
sortByText :: (a -> Text) -> [a] -> [a]
sortByText by as =
let as' = [(a, by a) | a <- as]
@ -574,10 +570,5 @@ class Convert a b where
class Parse a b where
parse :: a -> Maybe b
instance Parse Text NameSegment where
parse txt = case NameSegment.segments' txt of
[n] -> Just (NameSegment.NameSegment n)
_ -> Nothing
instance (Parse a a2, Parse b b2) => Parse (a, b) (a2, b2) where
parse (a, b) = (,) <$> parse a <*> parse b

View File

@ -1,3 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UndecidableInstances #-}
-- | The private Unison.Name innards. Prefer importing Unison.Name instead, unless you need the data constructor of
-- Name.
module Unison.Name.Internal
@ -11,6 +14,8 @@ import Control.Lens as Lens
import Data.List.NonEmpty (pattern (:|))
import Data.List.NonEmpty qualified as List (NonEmpty)
import Data.List.NonEmpty qualified as List.NonEmpty
import GHC.TypeLits (TypeError)
import GHC.TypeLits qualified as TypeError (ErrorMessage (Text))
import Unison.NameSegment (NameSegment)
import Unison.Position (Position (..))
import Unison.Prelude
@ -42,6 +47,15 @@ instance Alphabetical Name where
(False, True) -> GT
_ -> compareAlphabetical (segments n1) (segments n2)
instance
TypeError
( 'TypeError.Text
"You cannot make a Name from a string literal because there may (some day) be more than one syntax"
) =>
IsString Name
where
fromString = undefined
instance Ord Name where
compare (Name p0 ss0) (Name p1 ss1) =
compare ss0 ss1 <> compare p0 p1

View File

@ -16,13 +16,11 @@ module Unison.Var
inferTypeConstructor,
inferTypeConstructorArg,
isAction,
joinDot,
missingResult,
name,
nameStr,
named,
nameds,
namespaced,
rawName,
reset,
uncapitalize,
@ -32,14 +30,12 @@ module Unison.Var
)
where
import Data.Char (isLower, toLower)
import Data.Char (isAlphaNum, isLower, toLower)
import Data.Text (pack)
import Data.Text qualified as Text
import Unison.ABT qualified as ABT
import Unison.NameSegment qualified as Name
import Unison.Prelude
import Unison.Reference qualified as Reference
import Unison.Util.Monoid (intercalateMap)
import Unison.WatchKind (WatchKind, pattern TestWatch)
-- | A class for variables. Variables may have auxiliary information which
@ -195,31 +191,14 @@ data InferenceType
reset :: (Var v) => v -> v
reset v = typed (typeOf v)
unqualifiedName :: (Var v) => v -> Text
unqualifiedName = fromMaybe "" . lastMay . Name.segments' . name
unqualified :: (Var v) => v -> v
unqualified v = case typeOf v of
User _ -> named . unqualifiedName $ v
_ -> v
namespaced :: (Var v) => [v] -> v
namespaced vs = named $ intercalateMap "." name vs
nameStr :: (Var v) => v -> String
nameStr = Text.unpack . name
nameds :: (Var v) => String -> v
nameds s = named (Text.pack s)
joinDot :: (Var v) => v -> v -> v
joinDot prefix v2 =
if name prefix == "."
then named (name prefix `mappend` name v2)
else named (name prefix `mappend` "." `mappend` name v2)
universallyQuantifyIfFree :: forall v. (Var v) => v -> Bool
universallyQuantifyIfFree v =
ok (name $ reset v) && unqualified v == v
Text.all isLower (Text.take 1 n) && Text.all isAlphaNum n
where
ok n = (all isLower . take 1 . Text.unpack) n
n = name $ reset v

View File

@ -25,6 +25,7 @@ data Branch = Branch
patches :: Map NameSegment Hash,
children :: Map NameSegment Hash -- the Causal Hash
}
deriving (Eq, Ord, Show)
instance ContentAddressable Branch where
contentHash = H.hashTokenizable

View File

@ -168,8 +168,9 @@ import Unison.Sqlite qualified as Sqlite
import Unison.Symbol (Symbol)
import Unison.Syntax.DeclPrinter qualified as DeclPrinter
import Unison.Syntax.HashQualified' qualified as HQ' (toText)
import Unison.Syntax.Name as Name (toText, unsafeFromText)
import Unison.Syntax.Name as Name (toText, unsafeParseText)
import Unison.Syntax.NamePrinter qualified as NP
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Syntax.TermPrinter qualified as TermPrinter
import Unison.Syntax.TypePrinter qualified as TypePrinter
import Unison.Term (Term)
@ -204,8 +205,8 @@ listEntryName :: ShallowListEntry v a -> Text
listEntryName = \case
ShallowTermEntry te -> termEntryDisplayName te
ShallowTypeEntry te -> typeEntryDisplayName te
ShallowBranchEntry n _ _ -> NameSegment.toText n
ShallowPatchEntry n -> NameSegment.toText n
ShallowBranchEntry n _ _ -> NameSegment.toEscapedText n
ShallowPatchEntry n -> NameSegment.toEscapedText n
data BackendError
= NoSuchNamespace Path.Absolute
@ -268,7 +269,7 @@ loadReferentType codebase = \case
data TermEntry v a = TermEntry
{ termEntryReferent :: V2Referent.Referent,
termEntryHash :: ShortHash,
termEntryName :: NameSegment,
termEntryName :: Name,
termEntryConflicted :: Bool,
termEntryType :: Maybe (Type v a),
termEntryTag :: TermTag
@ -287,9 +288,9 @@ termEntryLabeledDependencies TermEntry {termEntryType, termEntryReferent, termEn
_ -> error "termEntryLabeledDependencies: not a constructor, but one was required"
termEntryDisplayName :: TermEntry v a -> Text
termEntryDisplayName = HQ'.toTextWith NameSegment.toText . termEntryHQName
termEntryDisplayName = HQ'.toTextWith Name.toText . termEntryHQName
termEntryHQName :: TermEntry v a -> HQ'.HashQualified NameSegment
termEntryHQName :: TermEntry v a -> HQ'.HashQualified Name
termEntryHQName TermEntry {termEntryName, termEntryConflicted, termEntryHash} =
if termEntryConflicted
then HQ'.HashQualified termEntryName termEntryHash
@ -298,7 +299,7 @@ termEntryHQName TermEntry {termEntryName, termEntryConflicted, termEntryHash} =
data TypeEntry = TypeEntry
{ typeEntryReference :: Reference,
typeEntryHash :: ShortHash,
typeEntryName :: NameSegment,
typeEntryName :: Name,
typeEntryConflicted :: Bool,
typeEntryTag :: TypeTag
}
@ -309,9 +310,9 @@ typeEntryLabeledDependencies TypeEntry {typeEntryReference} =
Set.singleton (LD.TypeReference typeEntryReference)
typeEntryDisplayName :: TypeEntry -> Text
typeEntryDisplayName = HQ'.toTextWith NameSegment.toText . typeEntryHQName
typeEntryDisplayName = HQ'.toTextWith Name.toText . typeEntryHQName
typeEntryHQName :: TypeEntry -> HQ'.HashQualified NameSegment
typeEntryHQName :: TypeEntry -> HQ'.HashQualified Name
typeEntryHQName TypeEntry {typeEntryName, typeEntryConflicted, typeEntryReference} =
if typeEntryConflicted
then HQ'.HashQualified typeEntryName (Reference.toShortHash typeEntryReference)
@ -348,7 +349,7 @@ fuzzyFind printNames query =
-- Prefer shorter FQNs
rank (alignment, name, _) =
( Name.countSegments (Name.unsafeFromText name),
( Name.countSegments (Name.unsafeParseText name),
negate (FZF.score alignment)
)
@ -421,12 +422,9 @@ resultListType = Type.app mempty (Type.list mempty) (Type.ref mempty Decls.testR
termListEntry ::
(MonadIO m) =>
Codebase m Symbol Ann ->
-- | Optional branch to check if the term is conflicted.
-- If omitted, all terms are just listed as not conflicted.
Maybe (V2Branch.Branch n) ->
ExactName NameSegment V2Referent.Referent ->
ExactName Name V2Referent.Referent ->
m (TermEntry Symbol Ann)
termListEntry codebase mayBranch (ExactName nameSegment ref) = do
termListEntry codebase (ExactName name ref) = do
ot <- Codebase.runTransaction codebase $ do
v1Referent <- Cv.referent2to1 (Codebase.getDeclType codebase) ref
ot <- loadReferentType codebase v1Referent
@ -435,21 +433,13 @@ termListEntry codebase mayBranch (ExactName nameSegment ref) = do
pure $
TermEntry
{ termEntryReferent = ref,
termEntryName = nameSegment,
termEntryName = name,
termEntryType = ot,
termEntryTag = tag,
termEntryConflicted = isConflicted,
-- See typeEntryConflicted
termEntryConflicted = False,
termEntryHash = Cv.referent2toshorthash1 Nothing ref
}
where
isConflicted = case mayBranch of
Nothing -> False
Just branch ->
branch
& V2Branch.terms
& Map.lookup nameSegment
& maybe 0 Map.size
& (> 1)
getTermTag ::
(Var v, MonadIO m) =>
@ -493,31 +483,21 @@ getTypeTag codebase r = do
typeListEntry ::
(Var v) =>
Codebase m v Ann ->
-- | Optional branch to check if the term is conflicted.
-- If omitted, all terms are just listed as not conflicted.
Maybe (V2Branch.Branch n) ->
ExactName NameSegment Reference ->
ExactName Name Reference ->
Sqlite.Transaction TypeEntry
typeListEntry codebase mayBranch (ExactName nameSegment ref) = do
typeListEntry codebase (ExactName name ref) = do
hashLength <- Codebase.hashLength
tag <- getTypeTag codebase ref
pure $
TypeEntry
{ typeEntryReference = ref,
typeEntryName = nameSegment,
typeEntryConflicted = isConflicted,
typeEntryName = name,
-- Mitchell says: at one point this was implemented incorrectly, but fixing it seemed like more trouble than it
-- was worth, because we don't really care about conflicted things anymore. Ditto for termEntryConflicted.
typeEntryConflicted = False,
typeEntryTag = tag,
typeEntryHash = SH.shortenTo hashLength $ Reference.toShortHash ref
}
where
isConflicted = case mayBranch of
Nothing -> False
Just branch ->
branch
& V2Branch.types
& Map.lookup nameSegment
& maybe 0 Map.size
& (> 1)
typeDeclHeader ::
forall v m.
@ -579,13 +559,13 @@ lsBranch codebase b0 = do
(ns, refs) <- Map.toList m
r <- Map.keys refs
pure (r, ns)
termEntries <- for (flattenRefs $ V2Branch.terms b0) $ \(r, ns) -> do
ShallowTermEntry <$> termListEntry codebase (Just b0) (ExactName ns r)
termEntries <- for (flattenRefs $ V2Branch.terms b0) \(r, ns) -> do
ShallowTermEntry <$> termListEntry codebase (ExactName (Name.fromSegment ns) r)
typeEntries <-
Codebase.runTransaction codebase do
for (flattenRefs $ V2Branch.types b0) \(r, ns) -> do
let v1Ref = Cv.reference2to1 r
ShallowTypeEntry <$> typeListEntry codebase (Just b0) (ExactName ns v1Ref)
ShallowTypeEntry <$> typeListEntry codebase (ExactName (Name.fromSegment ns) v1Ref)
childrenWithStats <- Codebase.runTransaction codebase (V2Branch.childStats b0)
let branchEntries :: [ShallowListEntry Symbol Ann] = do
(ns, (h, stats)) <- Map.toList $ childrenWithStats
@ -748,8 +728,6 @@ mkTypeDefinition ::
MonadIO m =>
Codebase IO Symbol Ann ->
PPED.PrettyPrintEnvDecl ->
Path.Path ->
V2Branch.CausalBranch Sqlite.Transaction ->
Width ->
Reference ->
[(HashQualifiedName, UnisonHash, Doc.Doc)] ->
@ -757,13 +735,11 @@ mkTypeDefinition ::
(AnnotatedText (UST.Element Reference))
(AnnotatedText (UST.Element Reference)) ->
m TypeDefinition
mkTypeDefinition codebase pped namesRoot rootCausal width r docs tp = do
mkTypeDefinition codebase pped width r docs tp = do
let bn = bestNameForType @Symbol (PPED.suffixifiedPPE pped) width r
tag <-
liftIO $ Codebase.runTransaction codebase do
causalAtPath <- Codebase.getShallowCausalAtPath namesRoot (Just rootCausal)
branchAtPath <- V2Causal.value causalAtPath
typeEntryTag <$> typeListEntry codebase (Just branchAtPath) (ExactName (NameSegment bn) r)
typeEntryTag <$> typeListEntry codebase (ExactName (Name.unsafeParseText bn) r)
pure $
TypeDefinition
(HQ'.toText <$> PPE.allTypeNames fqnPPE r)
@ -777,8 +753,6 @@ mkTypeDefinition codebase pped namesRoot rootCausal width r docs tp = do
mkTermDefinition ::
Codebase IO Symbol Ann ->
PPED.PrettyPrintEnvDecl ->
Path.Path ->
V2Branch.CausalBranch Sqlite.Transaction ->
Width ->
Reference ->
[(HashQualifiedName, UnisonHash, Doc.Doc)] ->
@ -786,19 +760,11 @@ mkTermDefinition ::
(AnnotatedText (UST.Element Reference))
(AnnotatedText (UST.Element Reference)) ->
Backend IO TermDefinition
mkTermDefinition codebase termPPED namesRoot rootCausal width r docs tm = do
mkTermDefinition codebase termPPED width r docs tm = do
let referent = Referent.Ref r
(ts, branchAtPath) <- liftIO $ Codebase.runTransaction codebase do
ts <- Codebase.getTypeOfTerm codebase r
causalAtPath <- Codebase.getShallowCausalAtPath namesRoot (Just rootCausal)
branchAtPath <- V2Causal.value causalAtPath
pure (ts, branchAtPath)
ts <- liftIO (Codebase.runTransaction codebase (Codebase.getTypeOfTerm codebase r))
let bn = bestNameForTerm @Symbol (PPED.suffixifiedPPE termPPED) width (Referent.Ref r)
tag <-
lift
( termEntryTag
<$> termListEntry codebase (Just branchAtPath) (ExactName (NameSegment bn) (Cv.referent1to2 referent))
)
tag <- lift (termEntryTag <$> termListEntry codebase (ExactName (Name.unsafeParseText bn) (Cv.referent1to2 referent)))
mk ts bn tag
where
fqnTermPPE = PPED.unsuffixifiedPPE termPPED
@ -918,7 +884,7 @@ docsInBranchToHtmlFiles ::
docsInBranchToHtmlFiles runtime codebase currentBranch directory = do
let allTerms = (R.toList . Branch.deepTerms . Branch.head) currentBranch
-- ignores docs inside lib namespace, recursively
let notLib (_, name) = "lib" `notElem` Name.segments name
let notLib (_, name) = NameSegment.libSegment `notElem` Name.segments name
(docTermsWithNames, hqLength) <-
Codebase.runTransaction codebase do
docTermsWithNames <- filterM (isDoc codebase . fst) (filter notLib allTerms)
@ -948,7 +914,7 @@ docsInBranchToHtmlFiles runtime codebase currentBranch directory = do
docFilePath :: FilePath -> Name -> FilePath
docFilePath destination docFQN =
let (dir, fileName) =
case unsnoc . map NameSegment.toString . toList . Name.segments $ docFQN of
case unsnoc . map (Text.unpack . NameSegment.toUnescapedText) . toList . Name.segments $ docFQN of
Just (path, leafName) ->
(directoryPath path, docFileName leafName)
Nothing ->

View File

@ -1,5 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-orphans #-}
@ -91,7 +90,6 @@ import Unison.Codebase.Runtime qualified as Rt
import Unison.Codebase.ShortCausalHash (ShortCausalHash)
import Unison.HashQualified
import Unison.Name as Name (Name, segments)
import Unison.NameSegment qualified as NameSegment
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.Project (ProjectAndBranch (..), ProjectBranchName, ProjectName)
@ -111,6 +109,7 @@ import Unison.Server.Local.Endpoints.UCM (UCMAPI, ucmServer)
import Unison.Server.Types (mungeString, setCacheControl)
import Unison.ShortHash qualified as ShortHash
import Unison.Symbol (Symbol)
import Unison.Syntax.NameSegment qualified as NameSegment
-- HTML content type
data HTML = HTML
@ -256,7 +255,7 @@ urlFor service baseUrl =
namespacePath path =
if path == Path.empty
then []
else [DontEscape "namespaces"] <> (EscapeMe . NameSegment.toText <$> Path.toList path)
else [DontEscape "namespaces"] <> (EscapeMe . NameSegment.toEscapedText <$> Path.toList path)
definitionPath :: Maybe DefinitionReference -> Maybe [URISegment]
definitionPath def =
@ -274,11 +273,11 @@ urlFor service baseUrl =
refToUrlText r =
case r of
NameOnly n ->
n & Name.segments & fmap (EscapeMe . NameSegment.toText) & toList
n & Name.segments & fmap (EscapeMe . NameSegment.toEscapedText) & toList
HashOnly h ->
[EscapeMe $ ShortHash.toText h]
HashQualified n _ ->
n & Name.segments & fmap (EscapeMe . NameSegment.toText) & toList
n & Name.segments & fmap (EscapeMe . NameSegment.toEscapedText) & toList
toDefinitionPath :: DefinitionReference -> [URISegment]
toDefinitionPath d =

View File

@ -28,7 +28,7 @@ import Unison.Server.Types
mungeString,
)
import Unison.ShortHash qualified as SH
import Unison.Syntax.HashQualified qualified as HQ (toString)
import Unison.Syntax.HashQualified qualified as HQ (toText)
badHQN :: HashQualifiedName -> ServerError
badHQN hqn =
@ -108,7 +108,7 @@ noSuchDefinition :: HQ.HashQualified Name -> ServerError
noSuchDefinition hqName =
err404
{ errBody =
"Couldn't find a definition for " <> BSC.pack (HQ.toString hqName)
"Couldn't find a definition for " <> LazyByteString.fromStrict (Text.encodeUtf8 (HQ.toText hqName))
}
ambiguousHashForDefinition :: SH.ShortHash -> ServerError

View File

@ -13,7 +13,9 @@ import U.Codebase.Causal qualified as Causal
import Unison.Codebase.Path
import Unison.Codebase.Path qualified as Path
import Unison.HashQualified qualified as HQ
import Unison.Name (Name, libSegment)
import Unison.Name (Name)
import Unison.NameSegment (libSegment)
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Server.Backend
import Unison.Sqlite qualified as Sqlite
@ -59,7 +61,13 @@ inferNamesRoot p b
| otherwise = getLast <$> execWriterT (runReaderT (go p b) Path.empty)
where
findBaseProject :: Path -> Maybe Path
findBaseProject ("public" Cons.:< "base" Cons.:< release Cons.:< _rest) = Just (Path.fromList ["public", "base", release])
findBaseProject
( (NameSegment.toUnescapedText -> "public")
Cons.:< (NameSegment.toUnescapedText -> "base")
Cons.:< release
Cons.:< _rest
) =
Just (Path.fromList ["public", "base", release])
findBaseProject _ = Nothing
go :: Path -> Branch Sqlite.Transaction -> ReaderT Path (WriterT (Last Path) Sqlite.Transaction) ()
go p b = do

View File

@ -80,13 +80,13 @@ prettyDefinitionsForHQName perspective shallowRoot renderWidth suffixifyBindings
ifor (typesToSyntax suffixifyBindings width pped types) \ref tp -> do
let hqTypeName = PPE.typeNameOrHashOnly fqnPPE ref
docs <- liftIO $ (maybe (pure []) docResults (HQ.toName hqTypeName))
mkTypeDefinition codebase pped namesRoot shallowRoot width ref docs tp
mkTypeDefinition codebase pped width ref docs tp
termDefinitions <-
ifor (termsToSyntax suffixifyBindings width pped terms) \reference trm -> do
let referent = Referent.Ref reference
let hqTermName = PPE.termNameOrHashOnly fqnPPE referent
docs <- liftIO $ (maybe (pure []) docResults (HQ.toName hqTermName))
mkTermDefinition codebase pped namesRoot shallowRoot width reference docs trm
mkTermDefinition codebase pped width reference docs trm
let renderedDisplayTerms = Map.mapKeys Reference.toText termDefinitions
renderedDisplayTypes = Map.mapKeys Reference.toText typeDefinitions
renderedMisses = fmap HQ.toText misses

View File

@ -16,9 +16,9 @@ import Unison.Codebase (Codebase)
import Unison.Codebase qualified as Codebase
import Unison.Codebase.Path qualified as Path
import Unison.Core.Project (ProjectAndBranch (..), ProjectBranchName (..), ProjectName (..))
import Unison.NameSegment (NameSegment (..))
import Unison.NameSegment (NameSegment)
import Unison.Prelude
import Unison.Project.Util (pattern UUIDNameSegment)
import Unison.Project.Util (pattern BranchesNameSegment, pattern ProjectsNameSegment, pattern UUIDNameSegment)
import Unison.Server.Backend
import Unison.Server.Types (APIGet)
@ -40,7 +40,7 @@ instance ToSample Current where
Current
(Just $ UnsafeProjectName "@unison/base")
(Just $ UnsafeProjectBranchName "main")
(Path.Absolute $ Path.fromText ".__projects._53393e4b_1f61_467c_a488_b6068c727daa.branches._f0aec0e3_249f_4004_b836_572fea3981c1")
(Path.Absolute $ Path.unsafeParseText ".__projects._53393e4b_1f61_467c_a488_b6068c727daa.branches._f0aec0e3_249f_4004_b836_572fea3981c1")
)
]
@ -57,8 +57,7 @@ serveCurrent = lift . getCurrentProjectBranch
getCurrentProjectBranch :: MonadIO m => Codebase m v a -> m Current
getCurrentProjectBranch codebase = do
namespace <- Codebase.runTransaction codebase Queries.expectMostRecentNamespace
let segments = NameSegment <$> namespace
segments <- Codebase.runTransaction codebase Queries.expectMostRecentNamespace
let absolutePath = toPath segments
case toIds segments of
ProjectAndBranch (Just projectId) branchId ->
@ -72,9 +71,9 @@ getCurrentProjectBranch codebase = do
toIds :: [NameSegment] -> ProjectAndBranch (Maybe ProjectId) (Maybe ProjectBranchId)
toIds segments =
case segments of
"__projects" : UUIDNameSegment projectId : "branches" : UUIDNameSegment branchId : _ ->
ProjectsNameSegment : UUIDNameSegment projectId : BranchesNameSegment : UUIDNameSegment branchId : _ ->
ProjectAndBranch {project = Just $ ProjectId projectId, branch = Just $ ProjectBranchId branchId}
"__projects" : UUIDNameSegment projectId : _ ->
ProjectsNameSegment : UUIDNameSegment projectId : _ ->
ProjectAndBranch {project = Just $ ProjectId projectId, branch = Nothing}
_ ->
ProjectAndBranch {project = Nothing, branch = Nothing}

View File

@ -1,11 +1,5 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Unison.Server.Local.Endpoints.FuzzyFind where
@ -26,7 +20,6 @@ import Servant.Docs
)
import Servant.OpenApi ()
import Text.FuzzyFind qualified as FZF
import U.Codebase.Causal qualified as V2Causal
import U.Codebase.HashTags (CausalHash)
import Unison.Codebase (Codebase)
import Unison.Codebase qualified as Codebase
@ -34,7 +27,6 @@ import Unison.Codebase.Editor.DisplayObject
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.ShortCausalHash qualified as SCH
import Unison.Codebase.SqliteCodebase.Conversions qualified as Cv
import Unison.NameSegment
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.PrettyPrintEnvDecl qualified as PPE
@ -51,6 +43,7 @@ import Unison.Server.Types
)
import Unison.Symbol (Symbol)
import Unison.Util.Pretty (Width)
import qualified Unison.Syntax.Name as Name
type FuzzyFindAPI =
"find"
@ -161,10 +154,6 @@ serveFuzzyFind codebase mayRoot relativeTo limit typeWidth query = do
Backend.hoistBackend (Codebase.runTransaction codebase) do
Backend.normaliseRootCausalHash mayRoot
(localNamesOnly, ppe) <- Backend.namesAtPathFromRootBranchHash codebase (Just rootCausal) path
relativeToBranch <- do
(lift . Codebase.runTransaction codebase) do
relativeToCausal <- Codebase.getShallowCausalAtPath path (Just rootCausal)
V2Causal.value relativeToCausal
let alignments ::
( [ ( FZF.Alignment,
UnisonName,
@ -174,26 +163,25 @@ serveFuzzyFind codebase mayRoot relativeTo limit typeWidth query = do
)
alignments =
take (fromMaybe 10 limit) $ Backend.fuzzyFind localNamesOnly (fromMaybe "" query)
lift (join <$> traverse (loadEntry (Just relativeToBranch) (PPE.suffixifiedPPE ppe)) alignments)
lift (join <$> traverse (loadEntry (PPE.suffixifiedPPE ppe)) alignments)
where
loadEntry relativeToBranch ppe (a, n, refs) = do
for refs $
\case
Backend.FoundTermRef r ->
( \te ->
( a,
FoundTermResult
. FoundTerm
(Backend.bestNameForTerm @Symbol ppe (mayDefaultWidth typeWidth) r)
$ Backend.termEntryToNamedTerm ppe typeWidth te
)
)
<$> Backend.termListEntry codebase relativeToBranch (ExactName (NameSegment n) (Cv.referent1to2 r))
Backend.FoundTypeRef r ->
Codebase.runTransaction codebase do
te <- Backend.typeListEntry codebase relativeToBranch (ExactName (NameSegment n) r)
let namedType = Backend.typeEntryToNamedType te
let typeName = Backend.bestNameForType @Symbol ppe (mayDefaultWidth typeWidth) r
typeHeader <- Backend.typeDeclHeader codebase ppe r
let ft = FoundType typeName typeHeader namedType
pure (a, FoundTypeResult ft)
loadEntry ppe (a, n, refs) = do
for refs \case
Backend.FoundTermRef r ->
( \te ->
( a,
FoundTermResult
. FoundTerm
(Backend.bestNameForTerm @Symbol ppe (mayDefaultWidth typeWidth) r)
$ Backend.termEntryToNamedTerm ppe typeWidth te
)
)
<$> Backend.termListEntry codebase (ExactName (Name.unsafeParseText n) (Cv.referent1to2 r))
Backend.FoundTypeRef r ->
Codebase.runTransaction codebase do
te <- Backend.typeListEntry codebase (ExactName (Name.unsafeParseText n) r)
let namedType = Backend.typeEntryToNamedType te
let typeName = Backend.bestNameForType @Symbol ppe (mayDefaultWidth typeWidth) r
typeHeader <- Backend.typeDeclHeader codebase ppe r
let ft = FoundType typeName typeHeader namedType
pure (a, FoundTypeResult ft)

View File

@ -1,11 +1,5 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Unison.Server.Local.Endpoints.NamespaceDetails where
@ -78,4 +72,5 @@ namespaceDetails runtime codebase namespacePath mayRoot _mayWidth = do
pure $ NamespaceDetails namespacePath causalHash renderedReadme
pure $ namespaceDetails
where
readmeNames = Set.fromList ["README", "Readme", "ReadMe", "readme"]
readmeNames =
Set.fromList ["README", "Readme", "ReadMe", "readme"]

View File

@ -26,7 +26,6 @@ import Unison.Codebase qualified as Codebase
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.ShortCausalHash (ShortCausalHash)
import Unison.Hash qualified as Hash
import Unison.NameSegment qualified as NameSegment
import Unison.Parser.Ann (Ann)
import Unison.Prelude
import Unison.PrettyPrintEnv qualified as PPE
@ -42,6 +41,7 @@ import Unison.Server.Types
v2CausalBranchToUnisonHash,
)
import Unison.Symbol (Symbol)
import Unison.Syntax.NameSegment qualified as NameSegment
import Unison.Util.Pretty (Width)
import Unison.Var (Var)
@ -183,12 +183,12 @@ backendListEntryToNamespaceObject ppe typeWidth = \case
Backend.ShallowBranchEntry name hash (NamespaceStats {numContainedTerms, numContainedTypes, numContainedPatches}) ->
Subnamespace $
NamedNamespace
{ namespaceName = NameSegment.toText name,
{ namespaceName = NameSegment.toEscapedText name,
namespaceHash = "#" <> Hash.toBase32HexText (unCausalHash hash),
namespaceSize = numContainedTerms + numContainedTypes + numContainedPatches
}
Backend.ShallowPatchEntry name ->
PatchObject . NamedPatch $ NameSegment.toText name
PatchObject . NamedPatch $ NameSegment.toEscapedText name
serve ::
Codebase IO Symbol Ann ->
@ -215,10 +215,9 @@ serve codebase maySCH mayRelativeTo mayNamespaceName = do
let relativeToPath = fromMaybe Path.empty mayRelativeTo
let namespacePath = fromMaybe Path.empty mayNamespaceName
let path = relativeToPath <> namespacePath
let path' = Path.toPath' path
(listingCausal, listingBranch) <-
(lift . Codebase.runTransaction codebase) do
listingCausal <- Codebase.getShallowCausalAtPath (Path.fromPath' path') (Just rootCausal)
listingCausal <- Codebase.getShallowCausalAtPath path (Just rootCausal)
listingBranch <- V2Causal.value listingCausal
pure (listingCausal, listingBranch)
-- TODO: Currently the ppe is just used to render the types returned from the namespace
@ -226,7 +225,7 @@ serve codebase maySCH mayRelativeTo mayNamespaceName = do
-- If we ever show types on hover we need to build and use a proper PPE here, but it's not
-- shallowPPE <- liftIO $ Backend.shallowPPE codebase listingBranch
let shallowPPE = PPE.empty
let listingFQN = Path.toText . Path.unabsolute . either id (Path.Absolute . Path.unrelative) $ Path.unPath' path'
let listingFQN = Path.toText path
let listingHash = v2CausalBranchToUnisonHash listingCausal
listingEntries <- lift (Backend.lsBranch codebase listingBranch)
makeNamespaceListing shallowPPE listingFQN listingHash listingEntries

View File

@ -18,9 +18,7 @@ import U.Codebase.HashTags
import Unison.Codebase.Editor.DisplayObject
import Unison.Codebase.Path qualified as Path
import Unison.Codebase.Path.Parse qualified as Path
import Unison.Codebase.ShortCausalHash
( ShortCausalHash (..),
)
import Unison.Codebase.ShortCausalHash (ShortCausalHash (..))
import Unison.Codebase.ShortCausalHash qualified as SCH
import Unison.ConstructorType (ConstructorType)
import Unison.ConstructorType qualified as CT
@ -32,16 +30,16 @@ import Unison.HashQualified' qualified as HQ'
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment (NameSegment (..))
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Project
import Unison.Reference qualified as Reference
import Unison.Referent qualified as Referent
import Unison.ShortHash (ShortHash)
import Unison.ShortHash qualified as SH
import Unison.Syntax.HashQualified qualified as HQ (fromText)
import Unison.Syntax.HashQualified' qualified as HQ' (fromText)
import Unison.Syntax.Name qualified as Name (fromTextEither, toText)
import Unison.Syntax.HashQualified qualified as HQ (parseText)
import Unison.Syntax.HashQualified' qualified as HQ' (parseText)
import Unison.Syntax.Name qualified as Name (parseTextEither, toText)
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Util.Pretty (Width (..))
instance ToJSON Hash where
@ -222,7 +220,7 @@ instance ToParam (QueryParam "name" Name) where
Normal
instance FromHttpApiData Name where
parseQueryParam = Name.fromTextEither
parseQueryParam = Name.parseTextEither
deriving via Int instance FromHttpApiData Width
@ -237,7 +235,7 @@ instance ToJSON ConstructorType where
instance FromHttpApiData Path.Relative where
parseUrlPiece txt = case Path.parsePath' (Text.unpack txt) of
Left s -> Left (Text.pack s)
Left s -> Left s
Right (Path.RelativePath' p) -> Right p
Right (Path.AbsolutePath' _) -> Left $ "Expected relative path, but " <> txt <> " was absolute."
@ -246,7 +244,7 @@ instance ToHttpApiData Path.Relative where
instance FromHttpApiData Path.Absolute where
parseUrlPiece txt = case Path.parsePath' (Text.unpack txt) of
Left s -> Left (Text.pack s)
Left s -> Left s
Right (Path.RelativePath' _) -> Left $ "Expected absolute path, but " <> txt <> " was relative."
Right (Path.AbsolutePath' p) -> Right p
@ -254,14 +252,14 @@ instance ToHttpApiData Path.Absolute where
toUrlPiece = tShow
instance FromHttpApiData Path.Path' where
parseUrlPiece txt = mapLeft Text.pack $ Path.parsePath' (Text.unpack txt)
parseUrlPiece txt = Path.parsePath' (Text.unpack txt)
instance ToHttpApiData Path.Path' where
toUrlPiece = tShow
instance FromHttpApiData Path.Path where
parseUrlPiece txt = case Path.parsePath' (Text.unpack txt) of
Left s -> Left (Text.pack s)
Left s -> Left s
Right (Path.RelativePath' p) -> Right (Path.unrelative p)
Right (Path.AbsolutePath' _) -> Left $ "Expected relative path, but " <> txt <> " was absolute."
@ -311,32 +309,32 @@ instance ToJSON (HQ.HashQualified Name) where
toJSON = Aeson.String . HQ.toTextWith Name.toText
instance ToJSON (HQ.HashQualified NameSegment) where
toJSON = Aeson.String . HQ.toTextWith NameSegment.toText
toJSON = Aeson.String . HQ.toTextWith NameSegment.toEscapedText
instance ToJSON (HQ'.HashQualified Name) where
toJSON = Aeson.String . HQ'.toTextWith Name.toText
instance ToJSON (HQ'.HashQualified NameSegment) where
toJSON = Aeson.String . HQ'.toTextWith NameSegment.toText
toJSON = Aeson.String . HQ'.toTextWith NameSegment.toEscapedText
instance FromJSON (HQ'.HashQualified Name) where
parseJSON = Aeson.withText "HashQualified'" \txt ->
maybe (fail "Invalid HashQualified' Name") pure $ HQ'.fromText txt
maybe (fail "Invalid HashQualified' Name") pure $ HQ'.parseText txt
instance FromJSON (HQ.HashQualified Name) where
parseJSON = Aeson.withText "HashQualified" \txt ->
maybe (fail "Invalid HashQualified Name") pure $ HQ.fromText txt
maybe (fail "Invalid HashQualified Name") pure $ HQ.parseText txt
instance FromJSON (HQ'.HashQualified NameSegment) where
parseJSON = Aeson.withText "HashQualified'" \txt -> do
hqName <- maybe (fail "Invalid HashQualified' NameSegment") pure $ HQ'.fromText txt
hqName <- maybe (fail "Invalid HashQualified' NameSegment") pure $ HQ'.parseText txt
for hqName \name -> case Name.segments name of
(ns :| []) -> pure ns
_ -> fail $ "Expected a single name segment but received several: " <> Text.unpack txt
instance FromJSON (HQ.HashQualified NameSegment) where
parseJSON = Aeson.withText "HashQualified" \txt -> do
hqName <- maybe (fail "Invalid HashQualified' NameSegment") pure $ HQ.fromText txt
hqName <- maybe (fail "Invalid HashQualified' NameSegment") pure $ HQ.parseText txt
for hqName \name -> case Name.segments name of
(ns :| []) -> pure ns
_ -> fail $ "Expected a single name segment but received several: " <> Text.unpack txt
@ -344,13 +342,13 @@ instance FromJSON (HQ.HashQualified NameSegment) where
instance FromHttpApiData (HQ.HashQualified Name) where
parseQueryParam txt =
Text.replace "@" "#" txt
& HQ.fromText
& HQ.parseText
& maybe (Left "Invalid Hash Qualified Name. Expected one of the following forms: name@hash, name, @hash") Right
instance FromHttpApiData (HQ'.HashQualified Name) where
parseQueryParam txt =
Text.replace "@" "#" txt
& HQ'.fromText
& HQ'.parseText
& maybe (Left "Invalid Hash Qualified Name. Expected one of the following forms: name@hash, name") Right
instance ToParamSchema (HQ.HashQualified n) where

View File

@ -1,8 +1,3 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-- | Duplicate of the Unison.Util.SyntaxText module, but we expect these to
@ -21,14 +16,14 @@ import Lucid
import Lucid qualified as L
import Unison.Name (Name)
import Unison.Name qualified as Name
import Unison.NameSegment qualified as NameSegment
import Unison.Pattern (SeqOp (..))
import Unison.Prelude
import Unison.Reference (Reference)
import Unison.Reference qualified as Reference
import Unison.Referent qualified as Referent
import Unison.Syntax.HashQualified qualified as HashQualified (toText)
import Unison.Syntax.Name qualified as Name (unsafeFromText)
import Unison.Syntax.Name qualified as Name (unsafeParseText)
import Unison.Syntax.NameSegment qualified as NameSegment (toEscapedText)
import Unison.Util.AnnotatedText
( AnnotatedText (..),
Segment (..),
@ -269,7 +264,7 @@ nameToHtml name =
span_ [class_ "fqn"] $ sequence_ parts
where
segments =
map (segment . L.toHtml . NameSegment.toText) $ List.NonEmpty.toList $ Name.segments name
map (segment . L.toHtml . NameSegment.toEscapedText) $ List.NonEmpty.toList $ Name.segments name
segment =
span_ [class_ "segment"]
@ -321,7 +316,7 @@ segmentToHtml (Segment segmentText element) =
content
| Text.isInfixOf "->" sText = span_ [class_ "arrow"] $ L.toHtml sText
| isFQN = nameToHtml (Name.unsafeFromText sText)
| isFQN = nameToHtml (Name.unsafeParseText sText)
| otherwise = L.toHtml sText
in case ref of
Just (r, refType) ->

View File

@ -42,15 +42,14 @@ import Unison.Hash qualified as Hash
import Unison.HashQualified qualified as HQ
import Unison.HashQualified' qualified as HQ'
import Unison.Name (Name)
import Unison.NameSegment (NameSegment)
import Unison.NameSegment qualified as NameSegment
import Unison.Prelude
import Unison.Project (ProjectAndBranch, ProjectBranchName, ProjectName)
import Unison.Server.Doc (Doc)
import Unison.Server.Orphans ()
import Unison.Server.Syntax (SyntaxText)
import Unison.ShortHash (ShortHash)
import Unison.Syntax.HashQualified qualified as HQ (fromText)
import Unison.Syntax.HashQualified qualified as HQ (parseText)
import Unison.Syntax.Name qualified as Name
import Unison.Util.Pretty (Width (..))
type APIHeaders x =
@ -146,7 +145,7 @@ instance FromHttpApiData (ExactName Name ShortHash) where
-- # is special in URLs, so we use @ for hash qualification instead;
-- e.g. ".base.List.map@abc"
-- e.g. ".base.Nat@@Nat"
case HQ.fromText (Text.replace "@" "#" txt) of
case HQ.parseText (Text.replace "@" "#" txt) of
Nothing -> Left "Invalid absolute name with Hash"
Just hq' -> case hq' of
HQ.NameOnly _ -> Left "A name and hash are required, but only a name was provided"
@ -246,7 +245,7 @@ unisonRefToText = \case
data NamedTerm = NamedTerm
{ -- The name of the term, should be hash qualified if conflicted, otherwise name only.
termName :: HQ'.HashQualified NameSegment,
termName :: HQ'.HashQualified Name,
termHash :: ShortHash,
termType :: Maybe SyntaxText,
termTag :: TermTag
@ -256,7 +255,7 @@ data NamedTerm = NamedTerm
instance ToJSON NamedTerm where
toJSON (NamedTerm n h typ tag) =
Aeson.object
[ "termName" .= HQ'.toTextWith NameSegment.toText n,
[ "termName" .= HQ'.toTextWith Name.toText n,
"termHash" .= h,
"termType" .= typ,
"termTag" .= tag
@ -273,7 +272,7 @@ instance FromJSON NamedTerm where
deriving instance ToSchema NamedTerm
data NamedType = NamedType
{ typeName :: HQ'.HashQualified NameSegment,
{ typeName :: HQ'.HashQualified Name,
typeHash :: ShortHash,
typeTag :: TypeTag
}
@ -282,7 +281,7 @@ data NamedType = NamedType
instance ToJSON NamedType where
toJSON (NamedType n h tag) =
Aeson.object
[ "typeName" .= HQ'.toTextWith NameSegment.toText n,
[ "typeName" .= HQ'.toTextWith Name.toText n,
"typeHash" .= h,
"typeTag" .= tag
]

Some files were not shown because too many files have changed in this diff Show More