Created
June 1, 2020 19:43
-
-
Save aryairani/90410cce8d5c132b9290329f4d326647 to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
2020-06-01 12:00:14.741795 [ThreadId 5] - | |
haskell-lsp:Starting up server ... | |
2020-06-01 12:00:14.750066 [ThreadId 5] - ---> {"jsonrpc":"2.0","id":0,"method":"initialize","params":{"processId":28616,"rootPath":"/Users/arya/unison/master/","rootUri":"file:///Users/arya/unison/master/","workspaceFolders":[],"capabilities":{"workspace":{"applyEdit":true,"configuration":false,"workspaceEdit":{"documentChanges":true},"workspaceFolders":false,"didChangeConfiguration":{"dynamicRegistration":false},"didChangeWatchedFiles":{"dynamicRegistration":false},"symbol":{"dynamicRegistration":false},"executeCommand":{"dynamicRegistration":false}},"textDocument":{"synchronization":{"dynamicRegistration":false,"willSave":true,"willSaveWaitUntil":true,"didSave":true},"completion":{"dynamicRegistration":false,"completionItem":{"snippetSupport":true,"commitCharactersSupport":false},"contextSupport":true},"hover":{"dynamicRegistration":false},"signatureHelp":{"dynamicRegistration":false},"references":{"dynamicRegistration":false},"documentHighlight":{"dynamicRegistration":false},"documentSymbol":{"dynamicRegistration":false,"hierarchicalDocumentSymbolSupport":true},"formatting":{"dynamicRegistration":false},"rangeFormatting":{"dynamicRegistration":false},"onTypeFormatting":{"dynamicRegistration":false},"definition":{"dynamicRegistration":false},"codeAction":{"dynamicRegistration":false},"codeLens":{"dynamicRegistration":false},"documentLink":{"dynamicRegistration":false},"rename":{"dynamicRegistration":false}},"experimental":{}}}} | |
2020-06-01 12:00:14.751537 [ThreadId 5] - haskell-lsp:initializeRequestHandler: setting current dir to project root:/Users/arya/unison/master/ | |
2020-06-01 12:00:14.767845 [ThreadId 5] - Warning: Client does not support watched files. Falling back to OS polling | |
2020-06-01 12:00:14.770957 [ThreadId 7] - <--2--{"result":{"capabilities":{"typeDefinitionProvider":true,"foldingRangeProvider":false,"textDocumentSync":{"openClose":true,"change":2,"save":{}},"workspace":{"workspaceFolders":{"supported":true,"changeNotifications":true}},"implementationProvider":true,"documentRangeFormattingProvider":true,"documentHighlightProvider":true,"executeCommandProvider":{"commands":["28710:ghcide:typesignature.add","28710:pragmas:addPragma"]},"renameProvider":true,"colorProvider":false,"definitionProvider":true,"hoverProvider":true,"codeActionProvider":true,"completionProvider":{"triggerCharacters":["."],"resolveProvider":false},"codeLensProvider":{},"documentSymbolProvider":true,"documentFormattingProvider":true}},"jsonrpc":"2.0","id":0} | |
2020-06-01 12:00:14.795078 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"initialized","params":{}} | |
2020-06-01 12:00:14.829916 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didOpen","params":{"textDocument":{"uri":"file:///Users/arya/unison/master/parser-typechecker/src/Unison/Codebase/Branch.hs","languageId":"haskell","version":1,"text":"{-# LANGUAGE LambdaCase #-}\n{-# LANGUAGE TemplateHaskell #-}\n{-# LANGUAGE RecordWildCards #-}\n{-# LANGUAGE PatternSynonyms #-}\n{-# LANGUAGE ViewPatterns #-}\n{-# LANGUAGE RankNTypes #-}\n\nmodule Unison.Codebase.Branch\n ( -- * Branch types\n Branch(..)\n , Branch0(..)\n , MergeMode(..)\n , Raw(..)\n , Star\n , Hash\n , EditHash\n , pattern Hash\n\n -- * Branch construction\n , empty\n , empty0\n , branch0\n , one\n , toCausalRaw\n , transform\n\n -- * Branch history\n -- ** History queries\n , isEmpty\n , isEmpty0\n , isOne\n , head\n , headHash\n , before\n , findHistoricalHQs\n , findHistoricalRefs\n , findHistoricalRefs'\n , namesDiff\n -- ** History updates\n , step\n , stepEverywhere\n , uncons\n , merge\n , merge'\n\n -- * Branch children\n -- ** Children lenses\n , children\n -- ** Children queries\n , toList0\n , getAt\n , getAt'\n , getAt0\n -- ** Children updates\n , setChildBranch\n , stepManyAt\n , stepManyAt0\n , stepManyAtM\n , modifyAtM\n\n -- * Branch terms/types\n -- ** Term/type lenses\n , terms\n , types\n -- ** Term/type queries\n , deepReferents\n , deepTypeReferences\n , toNames0\n -- ** Term/type updates\n , addTermName\n , addTypeName\n , deleteTermName\n , deleteTypeName\n\n\n -- * Branch patches\n -- ** Patch queries\n , deepEdits'\n , getPatch\n , getMaybePatch\n -- ** Patch updates\n , replacePatch\n , deletePatch\n , modifyPatches\n\n -- * Branch serialization\n , cachedRead\n , boundedCache\n , Cache\n , sync\n\n -- * Unused\n , childrenR\n , debugPaths\n , editedPatchRemoved\n , editsR\n , findHistoricalSHs\n , fork\n , lca\n , move\n , numHashChars\n , printDebugPaths\n , removedPatchEdited\n , stepAt\n , stepAtM\n , termsR\n , typesR\n ) where\n\nimport Unison.Prelude hiding (empty)\n\nimport Prelude hiding (head,read,subtract)\n\nimport Control.Lens hiding ( children, cons, transform, uncons )\nimport qualified Control.Monad.State as State\nimport Control.Monad.State ( StateT )\nimport Data.Bifunctor ( second )\nimport qualified Data.Map as Map\nimport qualified Data.Map.Merge.Lazy as Map\nimport qualified Data.Set as Set\nimport qualified Unison.Codebase.Patch as Patch\nimport Unison.Codebase.Patch ( Patch )\nimport qualified Unison.Codebase.Causal as Causal\nimport Unison.Codebase.Causal ( Causal\n , pattern RawOne\n , pattern RawCons\n , pattern RawMerge\n )\nimport Unison.Codebase.Path ( Path(..) )\nimport qualified Unison.Codebase.Path as Path\nimport Unison.NameSegment ( NameSegment )\nimport qualified Unison.NameSegment as NameSegment\nimport qualified Unison.Codebase.Metadata as Metadata\nimport qualified Unison.Hash as Hash\nimport Unison.Hashable ( Hashable )\nimport qualified Unison.Hashable as H\nimport Unison.Name ( Name(..) )\nimport qualified Unison.Name as Name\nimport qualified Unison.Names2 as Names\nimport qualified Unison.Names3 as Names\nimport Unison.Names2 ( Names'(Names), Names0 )\nimport Unison.Reference ( Reference )\nimport Unison.Referent ( Referent )\nimport qualified Unison.Referent as Referent\nimport qualified Unison.Reference as Reference\n\nimport qualified Unison.Util.Cache as Cache\nimport qualified Unison.Util.Relation as R\nimport Unison.Util.Relation ( Relation )\nimport qualified Unison.Util.Relation4 as R4\nimport qualified Unison.Util.List as List\nimport Unison.Util.Map ( unionWithM )\nimport qualified Unison.Util.Star3 as Star3\nimport Unison.ShortHash (ShortHash)\nimport qualified Unison.ShortHash as SH\nimport qualified Unison.HashQualified as HQ\nimport Unison.HashQualified (HashQualified)\nimport qualified Unison.LabeledDependency as LD\nimport Unison.LabeledDependency (LabeledDependency)\n\nnewtype Branch m = Branch { _history :: Causal m Raw (Branch0 m) }\n deriving (Eq, Ord)\n\ntype Hash = Causal.RawHash Raw\ntype EditHash = Hash.Hash\n\n-- Star3 r n Metadata.Type (Metadata.Type, Metadata.Value)\ntype Star r n = Metadata.Star r n\n\ndata Branch0 m = Branch0\n { _terms :: Star Referent NameSegment\n , _types :: Star Reference NameSegment\n , _children :: Map NameSegment (Branch m)\n , _edits :: Map NameSegment (EditHash, m Patch)\n -- names and metadata for this branch and its children\n -- (ref, (name, value)) iff ref has metadata `value` at name `name`\n , deepTerms :: Relation Referent Name\n , deepTypes :: Relation Reference Name\n , deepTermMetadata :: Metadata.R4 Referent Name\n , deepTypeMetadata :: Metadata.R4 Reference Name\n , deepPaths :: Set Path\n , deepEdits :: Map Name EditHash\n }\n\n-- Represents a shallow diff of a Branch0.\n-- Each of these `Star`s contain metadata as well, so an entry in\n-- `added` or `removed` could be an update to the metadata.\ndata BranchDiff = BranchDiff\n { addedTerms :: Star Referent NameSegment\n , removedTerms :: Star Referent NameSegment\n , addedTypes :: Star Reference NameSegment\n , removedTypes :: Star Reference NameSegment\n , changedPatches :: Map NameSegment Patch.PatchDiff\n } deriving (Eq, Ord, Show)\n\ninstance Semigroup BranchDiff where\n left <> right = BranchDiff\n { addedTerms = addedTerms left <> addedTerms right\n , removedTerms = removedTerms left <> removedTerms right\n , addedTypes = addedTypes left <> addedTypes right\n , removedTypes = removedTypes left <> removedTypes right\n , changedPatches =\n Map.unionWith (<>) (changedPatches left) (changedPatches right)\n }\n\ninstance Monoid BranchDiff where\n mappend = (<>)\n mempty = BranchDiff mempty mempty mempty mempty mempty\n\n-- The raw Branch\ndata Raw = Raw\n { _termsR :: Star Referent NameSegment\n , _typesR :: Star Reference NameSegment\n , _childrenR :: Map NameSegment Hash\n , _editsR :: Map NameSegment EditHash\n }\n\nmakeLenses ''Branch\nmakeLensesFor [(\"_edits\", \"edits\")] ''Branch0\nmakeLenses ''Raw\n\ntoNames0 :: Branch0 m -> Names0\ntoNames0 b = Names (R.swap . deepTerms $ b)\n (R.swap . deepTypes $ b)\n\n-- This stops searching for a given ShortHash once it encounters\n-- any term or type in any Branch0 that satisfies that ShortHash.\nfindHistoricalSHs\n :: Monad m => Set ShortHash -> Branch m -> m (Set ShortHash, Names0)\nfindHistoricalSHs = findInHistory\n (\\sh r _n -> sh `SH.isPrefixOf` Referent.toShortHash r)\n (\\sh r _n -> sh `SH.isPrefixOf` Reference.toShortHash r)\n\n-- This stops searching for a given HashQualified once it encounters\n-- any term or type in any Branch0 that satisfies that HashQualified.\nfindHistoricalHQs :: Monad m\n => Set HashQualified\n -> Branch m\n -> m (Set HashQualified, Names0)\nfindHistoricalHQs = findInHistory\n (\\hq r n -> HQ.matchesNamedReferent n r hq)\n (\\hq r n -> HQ.matchesNamedReference n r hq)\n\nfindHistoricalRefs :: Monad m => Set LabeledDependency -> Branch m\n -> m (Set LabeledDependency, Names0)\nfindHistoricalRefs = findInHistory\n (\\query r _n -> LD.fold (const False) (==r) query)\n (\\query r _n -> LD.fold (==r) (const False) query)\n\nfindHistoricalRefs' :: Monad m => Set Reference -> Branch m\n -> m (Set Reference, Names0)\nfindHistoricalRefs' = findInHistory\n (\\queryRef r _n -> r == Referent.Ref queryRef)\n (\\queryRef r _n -> r == queryRef)\n\nfindInHistory :: forall m q. (Monad m, Ord q)\n => (q -> Referent -> Name -> Bool)\n -> (q -> Reference -> Name -> Bool)\n -> Set q -> Branch m -> m (Set q, Names0)\nfindInHistory termMatches typeMatches queries b =\n (Causal.foldHistoryUntil f (queries, mempty) . _history) b <&> \\case\n -- could do something more sophisticated here later to report that some SH\n -- couldn't be found anywhere in the history. but for now, I assume that\n -- the normal thing will happen when it doesn't show up in the namespace.\n Causal.Satisfied (_, names) -> (mempty, names)\n Causal.Unsatisfied (missing, names) -> (missing, names)\n where\n -- in order to not favor terms over types, we iterate through the ShortHashes,\n -- for each `remainingQueries`, if we find a matching Referent or Reference,\n -- we remove `q` from the accumulated `remainingQueries`, and add the Ref* to\n -- the accumulated `names0`.\n f acc@(remainingQueries, _) b0 = (acc', null remainingQueries')\n where\n acc'@(remainingQueries', _) = foldl' findQ acc remainingQueries\n findQ :: (Set q, Names0) -> q -> (Set q, Names0)\n findQ acc sh =\n foldl' (doType sh) (foldl' (doTerm sh) acc\n (R.toList $ deepTerms b0))\n (R.toList $ deepTypes b0)\n doTerm q acc@(remainingSHs, names0) (r, n) = if termMatches q r n\n then (Set.delete q remainingSHs, Names.addTerm n r names0) else acc\n doType q acc@(remainingSHs, names0) (r, n) = if typeMatches q r n\n then (Set.delete q remainingSHs, Names.addType n r names0) else acc\n\ndeepReferents :: Branch0 m -> Set Referent\ndeepReferents = R.dom . deepTerms\n\ndeepTypeReferences :: Branch0 m -> Set Reference\ndeepTypeReferences = R.dom . deepTypes\n\nterms :: Lens' (Branch0 m) (Star Referent NameSegment)\nterms = lens _terms (\\Branch0{..} x -> branch0 x _types _children _edits)\n\ntypes :: Lens' (Branch0 m) (Star Reference NameSegment)\ntypes = lens _types (\\Branch0{..} x -> branch0 _terms x _children _edits)\n\nchildren :: Lens' (Branch0 m) (Map NameSegment (Branch m))\nchildren = lens _children (\\Branch0{..} x -> branch0 _terms _types x _edits)\n\n-- creates a Branch0 from the primary fields and derives the others.\nbranch0 :: Metadata.Star Referent NameSegment\n -> Metadata.Star Reference NameSegment\n -> Map NameSegment (Branch m)\n -> Map NameSegment (EditHash, m Patch)\n -> Branch0 m\nbranch0 terms types children edits =\n Branch0 terms types children edits\n deepTerms' deepTypes'\n deepTermMetadata' deepTypeMetadata'\n deepPaths' deepEdits'\n where\n nameSegToName = Name.unsafeFromText . NameSegment.toText\n deepTerms' = (R.mapRan nameSegToName . Star3.d1) terms\n <> foldMap go (Map.toList children)\n where\n go (nameSegToName -> n, b) =\n R.mapRan (Name.joinDot n) (deepTerms $ head b) -- could use mapKeysMonotonic\n deepTypes' = (R.mapRan nameSegToName . Star3.d1) types\n <> foldMap go (Map.toList children)\n where\n go (nameSegToName -> n, b) =\n R.mapRan (Name.joinDot n) (deepTypes $ head b) -- could use mapKeysMonotonic\n deepTermMetadata' = R4.mapD2 nameSegToName (Metadata.starToR4 terms)\n <> foldMap go (Map.toList children)\n where\n go (nameSegToName -> n, b) =\n R4.mapD2 (Name.joinDot n) (deepTermMetadata $ head b)\n deepTypeMetadata' = R4.mapD2 nameSegToName (Metadata.starToR4 types)\n <> foldMap go (Map.toList children)\n where\n go (nameSegToName -> n, b) =\n R4.mapD2 (Name.joinDot n) (deepTypeMetadata $ head b)\n deepPaths' = Set.map Path.singleton (Map.keysSet children)\n <> foldMap go (Map.toList children)\n where go (nameSeg, b) = Set.map (Path.cons nameSeg) (deepPaths $ head b)\n deepEdits' = Map.mapKeys nameSegToName (Map.map fst edits)\n <> foldMap go (Map.toList children)\n where\n go (nameSeg, b) =\n Map.mapKeys (nameSegToName nameSeg `Name.joinDot`) . deepEdits $ head b\n\nhead :: Branch m -> Branch0 m\nhead (Branch c) = Causal.head c\n\nheadHash :: Branch m -> Hash\nheadHash (Branch c) = Causal.currentHash c\n\ndeepEdits' :: Branch0 m -> Map Name (EditHash, m Patch)\ndeepEdits' b = go id b where\n -- can change this to an actual prefix once Name is a [NameSegment]\n go :: (Name -> Name) -> Branch0 m -> Map Name (EditHash, m Patch)\n go addPrefix Branch0{..} =\n Map.mapKeysMonotonic (addPrefix . Name.fromSegment) _edits\n <> foldMap f (Map.toList _children)\n where\n f :: (NameSegment, Branch m) -> Map Name (EditHash, m Patch)\n f (c, b) = go (addPrefix . Name.joinDot (Name.fromSegment c)) (head b)\n\ndata MergeMode = RegularMerge | SquashMerge deriving (Eq,Ord,Show)\n\nmerge :: forall m . Monad m => Branch m -> Branch m -> m (Branch m)\nmerge = merge' RegularMerge\n\n-- Discards the history of a Branch0's children, recursively\ndiscardHistory0 :: Applicative m => Branch0 m -> Branch0 m\ndiscardHistory0 = over children (fmap tweak) where\n tweak b = cons (discardHistory0 (head b)) empty\n\nmerge' :: forall m . Monad m => MergeMode -> Branch m -> Branch m -> m (Branch m)\nmerge' _ b1 b2 | isEmpty b1 = pure b2\nmerge' mode b1 b2 | isEmpty b2 = case mode of\n RegularMerge -> pure b1\n SquashMerge -> pure $ cons (discardHistory0 (head b1)) b2\nmerge' mode (Branch x) (Branch y) =\n Branch <$> case mode of\n RegularMerge -> Causal.threeWayMerge combine x y\n SquashMerge -> Causal.squashMerge combine x y\n where\n combine :: Maybe (Branch0 m) -> Branch0 m -> Branch0 m -> m (Branch0 m)\n combine Nothing l r = merge0 mode l r\n combine (Just ca) l r = do\n dl <- diff0 ca l\n dr <- diff0 ca r\n head0 <- apply ca (dl <> dr)\n children <- Map.mergeA\n (Map.traverseMaybeMissing $ combineMissing ca)\n (Map.traverseMaybeMissing $ combineMissing ca)\n (Map.zipWithAMatched $ const (merge' mode))\n (_children l) (_children r)\n pure $ branch0 (_terms head0) (_types head0) children (_edits head0)\n\n combineMissing ca k cur =\n case Map.lookup k (_children ca) of\n Nothing -> pure $ Just cur\n Just old -> do\n nw <- merge' mode (cons empty0 old) cur\n if isEmpty0 $ head nw\n then pure Nothing\n else pure $ Just nw\n\n apply :: Branch0 m -> BranchDiff -> m (Branch0 m)\n apply b0 BranchDiff {..} = do\n patches <- sequenceA\n $ Map.differenceWith patchMerge (pure @m <$> _edits b0) changedPatches\n let newPatches = makePatch <$> Map.difference changedPatches (_edits b0)\n makePatch Patch.PatchDiff {..} =\n let p = Patch.Patch _addedTermEdits _addedTypeEdits\n in (H.accumulate' p, pure p)\n pure $ branch0 (Star3.difference (_terms b0) removedTerms <> addedTerms)\n (Star3.difference (_types b0) removedTypes <> addedTypes)\n (_children b0)\n (patches <> newPatches)\n patchMerge mhp Patch.PatchDiff {..} = Just $ do\n (_, mp) <- mhp\n p <- mp\n let np = Patch.Patch\n { _termEdits = R.difference (Patch._termEdits p) _removedTermEdits\n <> _addedTermEdits\n , _typeEdits = R.difference (Patch._typeEdits p) _removedTypeEdits\n <> _addedTypeEdits\n }\n pure (H.accumulate' np, pure np)\n\n-- `before b1 b2` is true if `b2` incorporates all of `b1`\nbefore :: Monad m => Branch m -> Branch m -> m Bool\nbefore (Branch x) (Branch y) = Causal.before x y\n\nmerge0 :: forall m. Monad m => MergeMode -> Branch0 m -> Branch0 m -> m (Branch0 m)\nmerge0 mode b1 b2 = do\n c3 <- unionWithM (merge' mode) (_children b1) (_children b2)\n e3 <- unionWithM g (_edits b1) (_edits b2)\n pure $ branch0 (_terms b1 <> _terms b2)\n (_types b1 <> _types b2)\n c3\n e3\n where\n g :: (EditHash, m Patch) -> (EditHash, m Patch) -> m (EditHash, m Patch)\n g (h1, m1) (h2, _) | h1 == h2 = pure (h1, m1)\n g (_, m1) (_, m2) = do\n e1 <- m1\n e2 <- m2\n let e3 = e1 <> e2\n pure (H.accumulate' e3, pure e3)\n\npattern Hash h = Causal.RawHash h\n\ntoList0 :: Branch0 m -> [(Path, Branch0 m)]\ntoList0 = go Path.empty where\n go p b = (p, b) : (Map.toList (_children b) >>= (\\(seg, cb) ->\n go (Path.snoc p seg) (head cb) ))\n\nprintDebugPaths :: Branch m -> String\nprintDebugPaths = unlines . map show . Set.toList . debugPaths\n\ndebugPaths :: Branch m -> Set (Path, Hash)\ndebugPaths = go Path.empty where\n go p b = Set.insert (p, headHash b) . Set.unions $\n [ go (Path.snoc p seg) b | (seg, b) <- Map.toList $ _children (head b) ]\n\ndata Target = TargetType | TargetTerm | TargetBranch\n deriving (Eq, Ord, Show)\n\ninstance Eq (Branch0 m) where\n a == b = view terms a == view terms b\n && view types a == view types b\n && view children a == view children b\n && (fmap fst . view edits) a == (fmap fst . view edits) b\n\ndata ForkFailure = SrcNotFound | DestExists\n\n-- consider delegating to Names.numHashChars when ready to implement?\n-- are those enough?\n-- could move this to a read-only field in Branch0\n-- could move a Names0 to a read-only field in Branch0 until it gets too big\nnumHashChars :: Branch m -> Int\nnumHashChars _b = 3\n\n-- This type is a little ugly, so we wrap it up with a nice type alias for\n-- use outside this module.\ntype Cache m = Cache.Cache m (Causal.RawHash Raw) (Causal m Raw (Branch0 m))\n\nboundedCache :: MonadIO m => Word -> m (Cache m)\nboundedCache = Cache.semispaceCache\n\n-- Can use `Cache.nullCache` to disable caching if needed\ncachedRead :: forall m . Monad m\n => Cache m\n -> Causal.Deserialize m Raw Raw\n -> (EditHash -> m Patch)\n -> Hash\n -> m (Branch m)\ncachedRead cache deserializeRaw deserializeEdits h =\n Branch <$> Causal.cachedRead cache d h\n where\n fromRaw :: Raw -> m (Branch0 m)\n fromRaw Raw {..} = do\n children <- traverse go _childrenR\n edits <- for _editsR $ \\hash -> (hash,) . pure <$> deserializeEdits hash\n pure $ branch0 _termsR _typesR children edits\n go = cachedRead cache deserializeRaw deserializeEdits\n d :: Causal.Deserialize m Raw (Branch0 m)\n d h = deserializeRaw h >>= \\case\n RawOne raw -> RawOne <$> fromRaw raw\n RawCons raw h -> flip RawCons h <$> fromRaw raw\n RawMerge raw hs -> flip RawMerge hs <$> fromRaw raw\n\nsync\n :: Monad m\n => (Hash -> m Bool)\n -> Causal.Serialize m Raw Raw\n -> (EditHash -> m Patch -> m ())\n -> Branch m\n -> m ()\nsync exists serializeRaw serializeEdits b = do\n _written <- State.execStateT (sync' exists serializeRaw serializeEdits b) mempty\n -- traceM $ \"Branch.sync wrote \" <> show (Set.size written) <> \" namespace files.\"\n pure ()\n\n-- serialize a `Branch m` indexed by the hash of its corresponding Raw\nsync'\n :: forall m\n . Monad m\n => (Hash -> m Bool)\n -> Causal.Serialize m Raw Raw\n -> (EditHash -> m Patch -> m ())\n -> Branch m\n -> StateT (Set Hash) m ()\nsync' exists serializeRaw serializeEdits b = Causal.sync exists\n serialize0\n (view history b)\n where\n serialize0 :: Causal.Serialize (StateT (Set Hash) m) Raw (Branch0 m)\n serialize0 h b0 = case b0 of\n RawOne b0 -> do\n writeB0 b0\n lift $ serializeRaw h $ RawOne (toRaw b0)\n RawCons b0 ht -> do\n writeB0 b0\n lift $ serializeRaw h $ RawCons (toRaw b0) ht\n RawMerge b0 hs -> do\n writeB0 b0\n lift $ serializeRaw h $ RawMerge (toRaw b0) hs\n where\n writeB0 :: Branch0 m -> StateT (Set Hash) m ()\n writeB0 b0 = do\n for_ (view children b0) $ \\c -> do\n queued <- State.get\n when (Set.notMember (headHash c) queued) $\n sync' exists serializeRaw serializeEdits c\n for_ (view edits b0) (lift . uncurry serializeEdits)\n\n -- this has to serialize the branch0 and its descendants in the tree,\n -- and then serialize the rest of the history of the branch as well\n\ntoRaw :: Branch0 m -> Raw\ntoRaw Branch0 {..} =\n Raw _terms _types (headHash <$> _children) (fst <$> _edits)\n\ntoCausalRaw :: Branch m -> Causal.Raw Raw Raw\ntoCausalRaw = \\case\n Branch (Causal.One _h e) -> RawOne (toRaw e)\n Branch (Causal.Cons _h e (ht, _m)) -> RawCons (toRaw e) ht\n Branch (Causal.Merge _h e tls) -> RawMerge (toRaw e) (Map.keysSet tls)\n\n-- copy a path to another path\nfork\n :: Applicative m\n => Path\n -> Path\n -> Branch m\n -> Either ForkFailure (Branch m)\nfork src dest root = case getAt src root of\n Nothing -> Left SrcNotFound\n Just src' -> case setIfNotExists dest src' root of\n Nothing -> Left DestExists\n Just root' -> Right root'\n\n-- Move the node at src to dest.\n-- It's okay if `dest` is inside `src`, just create empty levels.\n-- Try not to `step` more than once at each node.\nmove :: Applicative m\n => Path\n -> Path\n -> Branch m\n -> Either ForkFailure (Branch m)\nmove src dest root = case getAt src root of\n Nothing -> Left SrcNotFound\n Just src' ->\n -- make sure dest doesn't already exist\n case getAt dest root of\n Just _destExists -> Left DestExists\n Nothing ->\n -- find and update common ancestor of `src` and `dest`:\n Right $ modifyAt ancestor go root\n where\n (ancestor, relSrc, relDest) = Path.relativeToAncestor src dest\n go = deleteAt relSrc . setAt relDest src'\n\nsetIfNotExists\n :: Applicative m => Path -> Branch m -> Branch m -> Maybe (Branch m)\nsetIfNotExists dest b root = case getAt dest root of\n Just _destExists -> Nothing\n Nothing -> Just $ setAt dest b root\n\nsetAt :: Applicative m => Path -> Branch m -> Branch m -> Branch m\nsetAt path b = modifyAt path (const b)\n\ndeleteAt :: Applicative m => Path -> Branch m -> Branch m\ndeleteAt path = setAt path empty\n\n-- returns `Nothing` if no Branch at `path` or if Branch is empty at `path`\ngetAt :: Path\n -> Branch m\n -> Maybe (Branch m)\ngetAt path root = case Path.uncons path of\n Nothing -> if isEmpty root then Nothing else Just root\n Just (seg, path) -> case Map.lookup seg (_children $ head root) of\n Just b -> getAt path b\n Nothing -> Nothing\n\ngetAt' :: Path -> Branch m -> Branch m\ngetAt' p b = fromMaybe empty $ getAt p b\n\ngetAt0 :: Path -> Branch0 m -> Branch0 m\ngetAt0 p b = case Path.uncons p of\n Nothing -> b\n Just (seg, path) -> case Map.lookup seg (_children b) of\n Just c -> getAt0 path (head c)\n Nothing -> empty0\n\nempty :: Branch m\nempty = Branch $ Causal.one empty0\n\none :: Branch0 m -> Branch m\none = Branch . Causal.one\n\nempty0 :: Branch0 m\nempty0 =\n Branch0 mempty mempty mempty mempty mempty mempty mempty mempty mempty mempty\n\nisEmpty0 :: Branch0 m -> Bool\nisEmpty0 = (== empty0)\n\nisEmpty :: Branch m -> Bool\nisEmpty = (== empty)\n\nstep :: Applicative m => (Branch0 m -> Branch0 m) -> Branch m -> Branch m\nstep f = over history (Causal.stepDistinct f)\n\nstepM :: (Monad m, Monad n) => (Branch0 m -> n (Branch0 m)) -> Branch m -> n (Branch m)\nstepM f = mapMOf history (Causal.stepDistinctM f)\n\ncons :: Applicative m => Branch0 m -> Branch m -> Branch m\ncons = step . const\n\nisOne :: Branch m -> Bool\nisOne (Branch Causal.One{}) = True\nisOne _ = False\n\nuncons :: Applicative m => Branch m -> m (Maybe (Branch0 m, Branch m))\nuncons (Branch b) = go <$> Causal.uncons b where\n go = over (_Just . _2) Branch\n\n-- Modify the branch0 at the head of at `path` with `f`,\n-- after creating it if necessary. Preserves history.\nstepAt :: forall m. Applicative m\n => Path\n -> (Branch0 m -> Branch0 m)\n -> Branch m -> Branch m\nstepAt p f = modifyAt p g where\n g :: Branch m -> Branch m\n g (Branch b) = Branch . Causal.consDistinct (f (Causal.head b)) $ b\n\nstepManyAt :: (Monad m, Foldable f)\n => f (Path, Branch0 m -> Branch0 m) -> Branch m -> Branch m\nstepManyAt actions = step (stepManyAt0 actions)\n\n-- Modify the branch0 at the head of at `path` with `f`,\n-- after creating it if necessary. Preserves history.\nstepAtM :: forall n m. (Functor n, Applicative m)\n => Path -> (Branch0 m -> n (Branch0 m)) -> Branch m -> n (Branch m)\nstepAtM p f = modifyAtM p g where\n g :: Branch m -> n (Branch m)\n g (Branch b) = do\n b0' <- f (Causal.head b)\n pure $ Branch . Causal.consDistinct b0' $ b\n\nstepManyAtM :: (Monad m, Monad n, Foldable f)\n => f (Path, Branch0 m -> n (Branch0 m)) -> Branch m -> n (Branch m)\nstepManyAtM actions = stepM (stepManyAt0M actions)\n\n-- starting at the leaves, apply `f` to every level of the branch.\nstepEverywhere\n :: Applicative m => (Branch0 m -> Branch0 m) -> (Branch0 m -> Branch0 m)\nstepEverywhere f Branch0 {..} = f (branch0 _terms _types children _edits)\n where children = fmap (step $ stepEverywhere f) _children\n\n-- Creates a function to fix up the children field._1\n-- If the action emptied a child, then remove the mapping,\n-- otherwise update it.\n-- Todo: Fix this in hashing & serialization instead of here?\ngetChildBranch :: NameSegment -> Branch0 m -> Branch m\ngetChildBranch seg b = fromMaybe empty $ Map.lookup seg (_children b)\n\nsetChildBranch :: NameSegment -> Branch m -> Branch0 m -> Branch0 m\nsetChildBranch seg b = over children (updateChildren seg b)\n\ngetPatch :: Applicative m => NameSegment -> Branch0 m -> m Patch\ngetPatch seg b = case Map.lookup seg (_edits b) of\n Nothing -> pure Patch.empty\n Just (_, p) -> p\n\ngetMaybePatch :: Applicative m => NameSegment -> Branch0 m -> m (Maybe Patch)\ngetMaybePatch seg b = case Map.lookup seg (_edits b) of\n Nothing -> pure Nothing\n Just (_, p) -> Just <$> p\n\nmodifyPatches\n :: Monad m => NameSegment -> (Patch -> Patch) -> Branch0 m -> m (Branch0 m)\nmodifyPatches seg f = mapMOf edits update\n where\n update m = do\n p' <- case Map.lookup seg m of\n Nothing -> pure $ f Patch.empty\n Just (_, p) -> f <$> p\n let h = H.accumulate' p'\n pure $ Map.insert seg (h, pure p') m\n\nreplacePatch :: Applicative m => NameSegment -> Patch -> Branch0 m -> Branch0 m\nreplacePatch n p = over edits (Map.insert n (H.accumulate' p, pure p))\n\ndeletePatch :: NameSegment -> Branch0 m -> Branch0 m\ndeletePatch n = over edits (Map.delete n)\n\nupdateChildren ::NameSegment\n -> Branch m\n -> Map NameSegment (Branch m)\n -> Map NameSegment (Branch m)\nupdateChildren seg updatedChild =\n if isEmpty updatedChild\n then Map.delete seg\n else Map.insert seg updatedChild\n\n-- Modify the Branch at `path` with `f`, after creating it if necessary.\n-- Because it's a `Branch`, it overwrites the history at `path`.\nmodifyAt :: Applicative m\n => Path -> (Branch m -> Branch m) -> Branch m -> Branch m\nmodifyAt path f = runIdentity . modifyAtM path (pure . f)\n\n-- Modify the Branch at `path` with `f`, after creating it if necessary.\n-- Because it's a `Branch`, it overwrites the history at `path`.\nmodifyAtM\n :: forall n m\n . Functor n\n => Applicative m -- because `Causal.cons` uses `pure`\n => Path\n -> (Branch m -> n (Branch m))\n -> Branch m\n -> n (Branch m)\nmodifyAtM path f b = case Path.uncons path of\n Nothing -> f b\n Just (seg, path) -> do -- Functor\n let child = getChildBranch seg (head b)\n child' <- modifyAtM path f child\n -- step the branch by updating its children according to fixup\n pure $ step (setChildBranch seg child') b\n\n-- stepManyAt0 consolidates several changes into a single step\nstepManyAt0 :: forall f m . (Monad m, Foldable f)\n => f (Path, Branch0 m -> Branch0 m)\n -> Branch0 m -> Branch0 m\nstepManyAt0 actions =\n runIdentity . stepManyAt0M [ (p, pure . f) | (p,f) <- toList actions ]\n\nstepManyAt0M :: forall m n f . (Monad m, Monad n, Foldable f)\n => f (Path, Branch0 m -> n (Branch0 m))\n -> Branch0 m -> n (Branch0 m)\nstepManyAt0M actions b = go (toList actions) b where\n go :: [(Path, Branch0 m -> n (Branch0 m))] -> Branch0 m -> n (Branch0 m)\n go actions b = let\n -- combines the functions that apply to this level of the tree\n currentAction b = foldM (\\b f -> f b) b [ f | (Path.Empty, f) <- actions ]\n\n -- groups the actions based on the child they apply to\n childActions :: Map NameSegment [(Path, Branch0 m -> n (Branch0 m))]\n childActions =\n List.multimap [ (seg, (rest,f)) | (seg :< rest, f) <- actions ]\n\n -- alters the children of `b` based on the `childActions` map\n stepChildren :: Map NameSegment (Branch m) -> n (Map NameSegment (Branch m))\n stepChildren children0 = foldM g children0 $ Map.toList childActions\n where\n g children (seg, actions) = do\n -- Recursively applies the relevant actions to the child branch\n -- The `findWithDefault` is important - it allows the stepManyAt\n -- to create new children at paths that don't previously exist.\n child <- stepM (go actions) (Map.findWithDefault empty seg children0)\n pure $ updateChildren seg child children\n in do\n c2 <- stepChildren (view children b)\n currentAction (set children c2 b)\n\ninstance Hashable (Branch0 m) where\n tokens b =\n [ H.accumulateToken (_terms b)\n , H.accumulateToken (_types b)\n , H.accumulateToken (headHash <$> _children b)\n ]\n\n-- getLocalBranch :: Hash -> IO Branch\n-- getGithubBranch :: RemotePath -> IO Branch\n-- getLocalEdit :: GUID -> IO Patch\n\n-- todo: consider inlining these into Actions2\naddTermName\n :: Referent -> NameSegment -> Metadata.Metadata -> Branch0 m -> Branch0 m\naddTermName r new md =\n over terms (Metadata.insertWithMetadata (r, md) . Star3.insertD1 (r, new))\n\naddTypeName\n :: Reference -> NameSegment -> Metadata.Metadata -> Branch0 m -> Branch0 m\naddTypeName r new md =\n over types (Metadata.insertWithMetadata (r, md) . Star3.insertD1 (r, new))\n\n-- addTermNameAt :: Path.Split -> Referent -> Branch0 m -> Branch0 m\n-- addTypeNameAt :: Path.Split -> Reference -> Branch0 m -> Branch0 m\n\ndeleteTermName :: Referent -> NameSegment -> Branch0 m -> Branch0 m\ndeleteTermName r n b | Star3.memberD1 (r,n) (view terms b)\n = over terms (Star3.deletePrimaryD1 (r,n)) b\ndeleteTermName _ _ b = b\n\ndeleteTypeName :: Reference -> NameSegment -> Branch0 m -> Branch0 m\ndeleteTypeName r n b | Star3.memberD1 (r,n) (view types b)\n = over types (Star3.deletePrimaryD1 (r,n)) b\ndeleteTypeName _ _ b = b\n\nnamesDiff :: Branch m -> Branch m -> Names.Diff\nnamesDiff b1 b2 = Names.diff0 (toNames0 (head b1)) (toNames0 (head b2))\n\nlca :: Monad m => Branch m -> Branch m -> m (Maybe (Branch m))\nlca (Branch a) (Branch b) = fmap Branch <$> Causal.lca a b\n\ndiff0 :: Monad m => Branch0 m -> Branch0 m -> m BranchDiff\ndiff0 old new = do\n newEdits <- sequenceA $ snd <$> _edits new\n oldEdits <- sequenceA $ snd <$> _edits old\n let diffEdits = Map.merge (Map.mapMissing $ \\_ p -> Patch.diff p mempty)\n (Map.mapMissing $ \\_ p -> Patch.diff mempty p)\n (Map.zipWithMatched (const Patch.diff))\n newEdits\n oldEdits\n pure $ BranchDiff\n { addedTerms = Star3.difference (_terms new) (_terms old)\n , removedTerms = Star3.difference (_terms old) (_terms new)\n , addedTypes = Star3.difference (_types new) (_types old)\n , removedTypes = Star3.difference (_types old) (_types new)\n , changedPatches = diffEdits\n }\n\ntransform :: Functor m => (forall a . m a -> n a) -> Branch m -> Branch n\ntransform f b = case _history b of\n causal -> Branch . Causal.transform f $ transformB0s f causal\n where\n transformB0 :: Functor m => (forall a . m a -> n a) -> Branch0 m -> Branch0 n\n transformB0 f b =\n b { _children = transform f <$> _children b\n , _edits = second f <$> _edits b\n }\n\n transformB0s :: Functor m => (forall a . m a -> n a)\n -> Causal m Raw (Branch0 m)\n -> Causal m Raw (Branch0 n)\n transformB0s f = Causal.unsafeMapHashPreserving (transformB0 f)\n\ndata BranchAttentions = BranchAttentions\n { -- Patches that were edited on the right but entirely removed on the left.\n removedPatchEdited :: [Name]\n -- Patches that were edited on the left but entirely removed on the right.\n , editedPatchRemoved :: [Name]\n }\n\ninstance Semigroup BranchAttentions where\n BranchAttentions edited1 removed1 <> BranchAttentions edited2 removed2\n = BranchAttentions (edited1 <> edited2) (removed1 <> removed2)\n\ninstance Monoid BranchAttentions where\n mempty = BranchAttentions [] []\n mappend = (<>)\n\ndata RefCollisions =\n RefCollisions { termCollisions :: Relation Name Name\n , typeCollisions :: Relation Name Name\n } deriving (Eq, Show)\n\ninstance Semigroup RefCollisions where\n (<>) = mappend\ninstance Monoid RefCollisions where\n mempty = RefCollisions mempty mempty\n mappend r1 r2 = RefCollisions (termCollisions r1 <> termCollisions r2)\n (typeCollisions r1 <> typeCollisions r2)\n"}}} | |
2020-06-01 12:00:14.844076 [ThreadId 5] - ---> {"jsonrpc":"2.0","id":1,"method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///Users/arya/unison/master/parser-typechecker/src/Unison/Codebase/Branch.hs"},"position":{"line":203,"character":5}}} | |
2020-06-01 12:00:14.846897 [ThreadId 14] - Set files of interest to: [NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/src/Unison/Codebase/Branch.hs"] | |
2020-06-01 12:00:14.847275 [ThreadId 14] - Opened text document: file:///Users/arya/unison/master/parser-typechecker/src/Unison/Codebase/Branch.hs | |
2020-06-01 12:00:14.847655 [ThreadId 16] - DocumentHighlight request at position 204:6 in file: /Users/arya/unison/master/parser-typechecker/src/Unison/Codebase/Branch.hs | |
2020-06-01 12:00:14.847959 [ThreadId 13] - Starting: (2,0):[DelayedAction: OfInterest,DelayedAction: FileStoreTC] | |
2020-06-01 12:00:14.849609 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":1} | |
2020-06-01 12:00:19.661629 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28730-0.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache","type":1}]}} | |
2020-06-01 12:00:19.66223 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28730-0.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/stack.sqlite3-journal",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache",True)] | |
2020-06-01 12:00:19.664925 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28730-0.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:27.013957 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28731-3.tmp","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28731-3.tmp","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config","type":1}]}} | |
2020-06-01 12:00:27.018338 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28731-3.tmp",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28731-3.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config",True)] | |
2020-06-01 12:00:27.024999 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28731-3.tmp"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28731-3.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:27.768124 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal","type":3}]}} | |
2020-06-01 12:00:27.769534 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/stack.sqlite3-journal",False)] | |
2020-06-01 12:00:27.77005 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal"}, _xtype = FcDeleted}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:27.924869 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/.stack-cabal-mod28712-0.tmp","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-build-caches/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/lib","type":2},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod","type":1}]}} | |
2020-06-01 12:00:27.925549 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/stack.sqlite3-journal",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/.stack-cabal-mod28712-0.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-build-caches/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/lib",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod",True)] | |
2020-06-01 12:00:27.927601 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/.stack-cabal-mod28712-0.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-build-caches/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/lib"}, _xtype = FcChanged},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:28.160442 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache.lock","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace","type":3}]}} | |
2020-06-01 12:00:28.160982 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache.lock",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace",False)] | |
2020-06-01 12:00:28.16272 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache.lock"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace"}, _xtype = FcDeleted}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:28.911412 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache.lock","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache28779-0.tmp","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache","type":1}]}} | |
2020-06-01 12:00:28.914628 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache.lock",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache28779-0.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache",True)] | |
2020-06-01 12:00:28.917735 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache.lock"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache28779-0.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:42.416509 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_hi","type":2}]}} | |
2020-06-01 12:00:42.416821 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_hi",True)] | |
2020-06-01 12:00:42.417351 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_hi"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:43.81976 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.o","type":2}]}} | |
2020-06-01 12:00:43.821087 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.o",True)] | |
2020-06-01 12:00:43.821622 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.o"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:44.300577 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.o","type":2}]}} | |
2020-06-01 12:00:44.300904 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.o",True)] | |
2020-06-01 12:00:44.301477 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.o"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:45.363196 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_o","type":2}]}} | |
2020-06-01 12:00:45.363634 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_o",True)] | |
2020-06-01 12:00:45.364186 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_o"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:45.569625 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_o","type":2}]}} | |
2020-06-01 12:00:45.569934 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_o",True)] | |
2020-06-01 12:00:45.570459 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/EasyTest.dyn_o"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:45.670986 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a","type":1}]}} | |
2020-06-01 12:00:45.671523 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a",True)] | |
2020-06-01 12:00:45.673246 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:45.773842 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a.izaWCa","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a","type":1}]}} | |
2020-06-01 12:00:45.775861 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a.izaWCa",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a",True)] | |
2020-06-01 12:00:45.792461 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a.izaWCa"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/objs-28776"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:47.617356 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib.ld_vWUAbh","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib","type":1}]}} | |
2020-06-01 12:00:47.618012 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib.ld_vWUAbh",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib",True)] | |
2020-06-01 12:00:47.619756 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib.ld_vWUAbh"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:47.719873 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28776-0.tmp","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf","type":1}]}} | |
2020-06-01 12:00:47.720246 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28776-0.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf",True)] | |
2020-06-01 12:00:47.721079 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28776-0.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:48.821152 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache28850-0.tmp","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache","type":1},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache","type":1}]}} | |
2020-06-01 12:00:48.821577 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache28850-0.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache",True),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache",True)] | |
2020-06-01 12:00:48.823195 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache28850-0.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/package.conf.inplace/package.cache"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:59.58637 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests.ld_AcQJmi","type":1}]}} | |
2020-06-01 12:00:59.586872 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests.ld_AcQJmi",True)] | |
2020-06-01 12:00:59.587888 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests.ld_AcQJmi"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:59.691422 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests.ld_AcQJmi","type":3},{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests","type":1}]}} | |
2020-06-01 12:00:59.691834 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests.ld_AcQJmi",False),(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests",True)] | |
2020-06-01 12:00:59.692598 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests.ld_AcQJmi"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/build/runtests/runtests"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:59.796646 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-build-caches/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/lib","type":2}]}} | |
2020-06-01 12:00:59.79697 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-build-caches/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/lib",True)] | |
2020-06-01 12:00:59.797705 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/yaks/easytest/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-build-caches/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/lib"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:00:59.95087 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/.copyFile28871-0.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/LICENSE","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/LICENSE","type":1}]}} | |
2020-06-01 12:00:59.951244 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/.copyFile28871-0.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/LICENSE",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/LICENSE",True)] | |
2020-06-01 12:00:59.952768 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/.copyFile28871-0.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/LICENSE"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/doc/easytest-0.1/LICENSE"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:00.146859 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-1.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.hi","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-2.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.dyn_hi","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-3.tmp","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.hi","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.dyn_hi","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-3.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/.copyFile28871-4.tmp","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/.copyFile28871-4.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/.copyFile28871-5.tmp","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib","type":1}]}} | |
2020-06-01 12:01:00.148009 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-1.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.hi",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-2.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.dyn_hi",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-3.tmp",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.hi",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.dyn_hi",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-3.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/.copyFile28871-4.tmp",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/.copyFile28871-4.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/.copyFile28871-5.tmp",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib",True)] | |
2020-06-01 12:01:00.156826 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-1.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.hi"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-2.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.dyn_hi"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-3.tmp"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.hi"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/EasyTest.dyn_hi"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/.copyFile28871-3.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/.copyFile28871-4.tmp"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU.a"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/.copyFile28871-4.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/.copyFile28871-5.tmp"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/lib/x86_64-osx-ghc-8.6.5/libHSeasytest-0.1-GHUNtMcGbspKNzFvNGkuQU-ghc8.6.5.dylib"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:00.218561 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/.copyFile28871-5.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests","type":2},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests","type":2}]}} | |
2020-06-01 12:01:00.218999 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/.copyFile28871-5.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests",True)] | |
2020-06-01 12:01:00.221007 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/.copyFile28871-5.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests"}, _xtype = FcChanged},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:00.316382 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests.strip","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests","type":1}]}} | |
2020-06-01 12:01:00.316876 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests.strip",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests",True)] | |
2020-06-01 12:01:00.318625 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests.strip"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/bin/runtests"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:01.987107 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28882-0.tmp","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28882-0.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28882-1.tmp","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28882-1.tmp","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache","type":1},{"uri":"file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache","type":1}]}} | |
2020-06-01 12:01:01.987841 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28882-0.tmp",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28882-0.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28882-1.tmp",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28882-1.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache",True),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache",True)] | |
2020-06-01 12:01:01.992848 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28882-0.tmp"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf28882-0.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28882-1.tmp"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/easytest-0.1-GHUNtMcGbspKNzFvNGkuQU.conf"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache28882-1.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/install/x86_64-osx/98c5c320d01fff2fa8b4023e473195d63b1dfd1f146602174ea52fc2c66bab77/8.6.5/pkgdb/package.cache"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:02.304815 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal","type":3},{"uri":"file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal","type":3}]}} | |
2020-06-01 12:01:02.305191 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/stack.sqlite3-journal",False),(NormalizedFilePath "/Users/arya/unison/master/.stack-work/stack.sqlite3-journal",False)] | |
2020-06-01 12:01:02.306103 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal"}, _xtype = FcDeleted}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:17.557904 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28886-3.tmp","type":1}]}} | |
2020-06-01 12:01:17.558197 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28886-3.tmp",True)] | |
2020-06-01 12:01:17.558697 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28886-3.tmp"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:17.698668 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28886-3.tmp","type":3},{"uri":"file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config","type":1},{"uri":"file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config","type":1}]}} | |
2020-06-01 12:01:17.699257 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28886-3.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config",True),(NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config",True)] | |
2020-06-01 12:01:17.700613 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config28886-3.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/setup-config"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:18.248634 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal","type":3},{"uri":"file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/.stack-cabal-mod28712-1.tmp","type":3},{"uri":"file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod","type":1},{"uri":"file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod","type":1}]}} | |
2020-06-01 12:01:18.249167 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/stack.sqlite3-journal",False),(NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/.stack-cabal-mod28712-1.tmp",False),(NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod",True),(NormalizedFilePath "/Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod",True)] | |
2020-06-01 12:01:18.251885 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/stack.sqlite3-journal"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/.stack-cabal-mod28712-1.tmp"}, _xtype = FcDeleted},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod"}, _xtype = FcCreated},FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/parser-typechecker/.stack-work/dist/x86_64-osx/Cabal-2.4.0.1/stack-cabal-mod"}, _xtype = FcCreated}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:21.21967 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeWatchedFiles","params":{"changes":[{"uri":"file:///Users/arya/unison/master/.stack-work/stack.sqlite3","type":2}]}} | |
2020-06-01 12:01:21.222285 [ThreadId 14] - Files created or deleted: [(NormalizedFilePath "/Users/arya/unison/master/.stack-work/stack.sqlite3",True)] | |
2020-06-01 12:01:21.222675 [ThreadId 14] - Unexpected exception on notification, please report! | |
Message: NotificationMessage {_jsonrpc = "2.0", _method = WorkspaceDidChangeWatchedFiles, _params = DidChangeWatchedFilesParams {_changes = List [FileEvent {_uri = Uri {getUri = "file:///Users/arya/unison/master/.stack-work/stack.sqlite3"}, _xtype = FcChanged}]}} | |
Exception: user error (Pattern match failure in do expression at src/Development/IDE/Core/Shake.hs:157:5-10) | |
2020-06-01 12:01:28.454211 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"uri":"file:///Users/arya/unison/master/parser-typechecker/src/Unison/Codebase/Causal.hs","diagnostics":[{"severity":1,"range":{"start":{"line":238,"character":6},"end":{"line":238,"character":38}},"source":"parser","message":"/Users/arya/unison/master/parser-typechecker/src/Unison/Codebase/Causal.hs:239:7: error:\n parse error on input ‘-- | lca == c2 -> pure $ done c1’"}]},"method":"textDocument/publishDiagnostics"} | |
2020-06-01 12:01:28.687591 [ThreadId 2862] - finish: OfInterest (took 1m14s) | |
2020-06-01 12:01:28.689127 [ThreadId 2864] - finish: FileStoreTC (took 1m14s) | |
2020-06-01 12:01:28.69293 [ThreadId 17] - finish shakeRun: batch (took 1m14s, completed) | |
2020-06-01 12:01:28.701337 [ThreadId 13] - Starting: (2,0):[DelayedAction: C:GetHieFile,DelayedAction: InitialLoad] | |
2020-06-01 12:01:33.513517 [ThreadId 8473] - finish: C:GetHieFile (took 4.81s) | |
2020-06-01 12:01:34.644567 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"uri":"file:///Users/arya/unison/master/parser-typechecker/src/Unison/TermPrinter.hs","diagnostics":[{"severity":1,"range":{"start":{"line":626,"character":0},"end":{"line":626,"character":1}},"source":"parser","message":"/Users/arya/unison/master/parser-typechecker/src/Unison/TermPrinter.hs:627:1: error:\n parse error on input ‘{’"}]},"method":"textDocument/publishDiagnostics"} | |
2020-06-01 12:01:36.440292 [ThreadId 9655] - finish: InitialLoad (took 7.74s) | |
2020-06-01 12:01:36.441194 [ThreadId 2866] - finish shakeRun: batch (took 7.74s, completed) | |
2020-06-01 12:16:44.592856 [ThreadId 5] - ---> {"jsonrpc":"2.0","id":2,"method":"shutdown","params":null} | |
2020-06-01 12:16:44.600199 [ThreadId 7] - <--2--{"result":null,"jsonrpc":"2.0","id":2} | |
2020-06-01 12:16:44.608543 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"exit"} | |
2020-06-01 12:16:44.609038 [ThreadId 5] - haskell-lsp:Got exit, exiting |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment