Skip to content

Instantly share code, notes, and snippets.

@glittershark
Created July 3, 2020 20:48
Show Gist options
  • Save glittershark/cd51ca7958de6d1410794b26a7cfc111 to your computer and use it in GitHub Desktop.
Save glittershark/cd51ca7958de6d1410794b26a7cfc111 to your computer and use it in GitHub Desktop.
2020-07-03 16:47:38.104119755 [ThreadId 5] -
haskell-lsp:Starting up server ...
2020-07-03 16:47:38.104424879 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"initialize","params":{"processId":null,"rootPath":"/home/grfn/code/depot","clientInfo":{"name":"emacs","version":"GNU Emacs 27.0.91 (build 1, x86_64-pc-linux-gnu, GTK+ Version 3.24.13)"},"rootUri":"file:///home/grfn/code/depot","capabilities":{"workspace":{"workspaceEdit":{"documentChanges":true,"resourceOperations":["create","rename","delete"]},"applyEdit":true,"symbol":{"symbolKind":{"valueSet":[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26]}},"executeCommand":{"dynamicRegistration":false},"workspaceFolders":true,"configuration":true},"textDocument":{"declaration":{"linkSupport":true},"definition":{"linkSupport":true},"implementation":{"linkSupport":true},"typeDefinition":{"linkSupport":true},"synchronization":{"willSave":true,"didSave":true,"willSaveWaitUntil":true},"documentSymbol":{"symbolKind":{"valueSet":[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26]},"hierarchicalDocumentSymbolSupport":true},"formatting":{"dynamicRegistration":true},"rangeFormatting":{"dynamicRegistration":true},"rename":{"dynamicRegistration":true,"prepareSupport":true},"codeAction":{"dynamicRegistration":true,"isPreferredSupport":true,"codeActionLiteralSupport":{"codeActionKind":{"valueSet":["","quickfix","refactor","refactor.extract","refactor.inline","refactor.rewrite","source","source.organizeImports"]}}},"completion":{"completionItem":{"snippetSupport":true,"documentationFormat":["markdown"]},"contextSupport":true},"signatureHelp":{"signatureInformation":{"parameterInformation":{"labelOffsetSupport":true}}},"documentLink":{"dynamicRegistration":true,"tooltipSupport":true},"hover":{"contentFormat":["markdown","plaintext"]},"foldingRange":null,"callHierarchy":{"dynamicRegistration":false},"publishDiagnostics":{"relatedInformation":true,"tagSupport":{"valueSet":[1,2]},"versionSupport":true}},"window":{"workDoneProgress":true}},"initializationOptions":null,"workDoneToken":"1"},"id":151}
2020-07-03 16:47:38.105107354 [ThreadId 5] - haskell-lsp:initializeRequestHandler: setting current dir to project root:/home/grfn/code/depot
2020-07-03 16:47:38.146929071 [ThreadId 5] - Warning: Client does not support watched files. Falling back to OS polling
2020-07-03 16:47:38.147362179 [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":["979:ghcide:typesignature.add","979: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":151}
2020-07-03 16:47:38.24537778 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"initialized","params":{}}
2020-07-03 16:47:38.246439455 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didOpen","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs","languageId":"haskell","version":12,"text":"{-# LANGUAGE UndecidableInstances #-}\n{-# LANGUAGE RecordWildCards #-}\n--------------------------------------------------------------------------------\nmodule Xanthous.App\n ( makeApp\n , RunType(..)\n ) where\n--------------------------------------------------------------------------------\nimport Xanthous.Prelude\nimport Brick hiding (App, halt, continue, raw)\nimport qualified Brick\nimport Graphics.Vty.Attributes (defAttr)\nimport Graphics.Vty.Input.Events (Event(EvKey))\nimport Control.Monad.State (get, gets)\nimport Control.Monad.State.Class (modify)\nimport Data.Aeson (object, ToJSON)\nimport qualified Data.Aeson as A\nimport qualified Data.Vector as V\nimport System.Exit\nimport System.Directory (doesFileExist)\nimport Data.List.NonEmpty (NonEmpty(..))\n--------------------------------------------------------------------------------\nimport Xanthous.App.Common\nimport Xanthous.App.Time\nimport Xanthous.App.Prompt\nimport Xanthous.App.Autocommands\nimport Xanthous.Command\nimport Xanthous.Data\n ( move\n , Dimensions'(Dimensions)\n , positioned\n , position\n , Position\n , (|*|)\n )\nimport Xanthous.Data.App (ResourceName, Panel(..), AppEvent(..))\nimport qualified Xanthous.Data.EntityMap as EntityMap\nimport Xanthous.Data.Levels (prevLevel, nextLevel)\nimport qualified Xanthous.Data.Levels as Levels\nimport Xanthous.Data.Entities (blocksObject)\nimport Xanthous.Game\nimport Xanthous.Game.State\nimport Xanthous.Game.Env\nimport Xanthous.Game.Draw (drawGame)\nimport Xanthous.Game.Prompt\nimport qualified Xanthous.Messages as Messages\nimport Xanthous.Random\nimport Xanthous.Util (removeVectorIndex)\nimport Xanthous.Util.Inflection (toSentence)\n--------------------------------------------------------------------------------\nimport qualified Xanthous.Entities.Character as Character\nimport Xanthous.Entities.Character hiding (pickUpItem)\nimport Xanthous.Entities.Item (Item)\nimport qualified Xanthous.Entities.Item as Item\nimport Xanthous.Entities.Creature (Creature)\nimport qualified Xanthous.Entities.Creature as Creature\nimport Xanthous.Entities.Environment\n (Door, open, closed, locked, GroundMessage(..), Staircase(..))\nimport Xanthous.Entities.RawTypes\n ( edible, eatMessage, hitpointsHealed\n , attackMessage\n )\nimport Xanthous.Generators\nimport qualified Xanthous.Generators.CaveAutomata as CaveAutomata\nimport qualified Xanthous.Generators.Dungeon as Dungeon\n--------------------------------------------------------------------------------\n\ntype App = Brick.App GameState AppEvent ResourceName\n\ndata RunType = NewGame | LoadGame\n deriving stock (Eq)\n\nmakeApp :: GameEnv -> RunType -> IO App\nmakeApp env rt = pure $ Brick.App\n { appDraw = drawGame\n , appChooseCursor = const headMay\n , appHandleEvent = \\game event -> runAppM (handleEvent event) env game\n , appStartEvent = case rt of\n NewGame -> runAppM (startEvent >> get) env\n LoadGame -> pure\n , appAttrMap = const $ attrMap defAttr []\n }\n\nrunAppM :: AppM a -> GameEnv -> GameState -> EventM ResourceName a\nrunAppM appm ge = fmap fst . runAppT appm ge\n\nstartEvent :: AppM ()\nstartEvent = do\n initLevel\n modify updateCharacterVision\n use (character . characterName) >>= \\case\n Nothing -> prompt_ @'StringPrompt [\"character\", \"namePrompt\"] Uncancellable\n $ \\(StringResult s) -> do\n character . characterName ?= s\n say [\"welcome\"] =<< use character\n Just n -> say [\"welcome\"] $ object [ \"characterName\" A..= n ]\n\ninitLevel :: AppM ()\ninitLevel = do\n level <- genLevel 0\n entities <>= levelToEntityMap level\n characterPosition .= level ^. levelCharacterPosition\n\n--------------------------------------------------------------------------------\n\nhandleEvent :: BrickEvent ResourceName AppEvent -> AppM (Next GameState)\nhandleEvent ev = use promptState >>= \\case\n NoPrompt -> handleNoPromptEvent ev\n WaitingPrompt msg pr -> handlePromptEvent msg pr ev\n\n\nhandleNoPromptEvent :: BrickEvent ResourceName AppEvent -> AppM (Next GameState)\nhandleNoPromptEvent (VtyEvent (EvKey k mods))\n | Just command <- commandFromKey k mods\n = do messageHistory %= nextTurn\n cancelAutocommand\n handleCommand command\nhandleNoPromptEvent (AppEvent AutoContinue) = do\n preuse (autocommand . _ActiveAutocommand . _1) >>= traverse_ autoStep\n continue\nhandleNoPromptEvent _ = continue\n\nhandleCommand :: Command -> AppM (Next GameState)\nhandleCommand Quit = confirm_ [\"quit\", \"confirm\"] (liftIO exitSuccess) >> continue\nhandleCommand (Move dir) = do\n newPos <- uses characterPosition $ move dir\n collisionAt newPos >>= \\case\n Nothing -> do\n characterPosition .= newPos\n stepGameBy =<< uses (character . speed) (|*| 1)\n describeEntitiesAt newPos\n Just Combat -> attackAt newPos\n Just Stop -> pure ()\n continue\n\nhandleCommand PickUp = do\n pos <- use characterPosition\n uses entities (entitiesAtPositionWithType @Item pos) >>= \\case\n [] -> say_ [\"pickUp\", \"nothingToPickUp\"]\n [item] -> pickUpItem item\n items' ->\n menu_ [\"pickUp\", \"menu\"] Cancellable (entityMenu_ items')\n $ \\(MenuResult item) -> pickUpItem item\n continue\n where\n pickUpItem (itemID, item) = do\n character %= Character.pickUpItem item\n entities . at itemID .= Nothing\n say [\"pickUp\", \"pickUp\"] $ object [ \"item\" A..= item ]\n stepGameBy 100 -- TODO\n\nhandleCommand Drop = do\n selectItemFromInventory_ [\"drop\", \"menu\"] Cancellable id\n (say_ [\"drop\", \"nothing\"])\n $ \\(MenuResult item) -> do\n entitiesAtCharacter %= (SomeEntity item <|)\n say [\"drop\", \"dropped\"] $ object [ \"item\" A..= item ]\n continue\n\nhandleCommand PreviousMessage = do\n messageHistory %= previousMessage\n continue\n\nhandleCommand Open = do\n prompt_ @'DirectionPrompt [\"open\", \"prompt\"] Cancellable\n $ \\(DirectionResult dir) -> do\n pos <- move dir <$> use characterPosition\n doors <- uses entities $ entitiesAtPositionWithType @Door pos\n if | null doors -> say_ [\"open\", \"nothingToOpen\"]\n | any (view $ _2 . locked) doors -> say_ [\"open\", \"locked\"]\n | all (view $ _2 . open) doors -> say_ [\"open\", \"alreadyOpen\"]\n | otherwise -> do\n for_ doors $ \\(eid, _) ->\n entities . ix eid . positioned . _SomeEntity . open .= True\n say_ [\"open\", \"success\"]\n pure ()\n stepGame -- TODO\n continue\n\nhandleCommand Close = do\n prompt_ @'DirectionPrompt [\"close\", \"prompt\"] Cancellable\n $ \\(DirectionResult dir) -> do\n pos <- move dir <$> use characterPosition\n (nonDoors, doors) <- uses entities\n $ partitionEithers\n . toList\n . map ( (matching . aside $ _SomeEntity @Door)\n . over _2 (view positioned)\n )\n . EntityMap.atPositionWithIDs pos\n if | null doors -> say_ [\"close\", \"nothingToClose\"]\n | all (view $ _2 . closed) doors -> say_ [\"close\", \"alreadyClosed\"]\n | any (view blocksObject . entityAttributes . snd) nonDoors ->\n say [\"close\", \"blocked\"]\n $ object [ \"entityDescriptions\"\n A..= ( toSentence\n . map description\n . filter (view blocksObject . entityAttributes)\n . map snd\n ) nonDoors\n , \"blockOrBlocks\"\n A..= ( if length nonDoors == 1\n then \"blocks\"\n else \"block\"\n :: Text)\n ]\n | otherwise -> do\n for_ doors $ \\(eid, _) ->\n entities . ix eid . positioned . _SomeEntity . closed .= True\n for_ nonDoors $ \\(eid, _) ->\n entities . ix eid . position %= move dir\n say_ [\"close\", \"success\"]\n pure ()\n stepGame -- TODO\n continue\n\nhandleCommand Look = do\n prompt_ @'PointOnMap [\"look\", \"prompt\"] Cancellable\n $ \\(PointOnMapResult pos) ->\n gets (revealedEntitiesAtPosition pos)\n >>= \\case\n Empty -> say_ [\"look\", \"nothing\"]\n ents -> describeEntities ents\n continue\n\nhandleCommand Wait = stepGame >> continue\n\nhandleCommand Eat = do\n uses (character . inventory . backpack)\n (V.mapMaybe (\\item -> (item,) <$> item ^. Item.itemType . edible))\n >>= \\case\n Empty -> say_ [\"eat\", \"noFood\"]\n food ->\n let foodMenuItem idx (item, edibleItem)\n = ( item ^. Item.itemType . char . char\n , MenuOption (description item) (idx, item, edibleItem))\n -- TODO refactor to use entityMenu_\n menuItems = mkMenuItems $ imap foodMenuItem food\n in menu_ [\"eat\", \"menuPrompt\"] Cancellable menuItems\n $ \\(MenuResult (idx, item, edibleItem)) -> do\n character . inventory . backpack %= removeVectorIndex idx\n let msg = fromMaybe (Messages.lookup [\"eat\", \"eat\"])\n $ edibleItem ^. eatMessage\n character . characterHitpoints' +=\n edibleItem ^. hitpointsHealed . to fromIntegral\n message msg $ object [\"item\" A..= item]\n stepGame -- TODO\n continue\n\nhandleCommand Read = do\n -- TODO allow reading things in the inventory (combo direction+menu prompt?)\n prompt_ @'DirectionPrompt [\"read\", \"prompt\"] Cancellable\n $ \\(DirectionResult dir) -> do\n pos <- uses characterPosition $ move dir\n uses entities\n (fmap snd . entitiesAtPositionWithType @GroundMessage pos) >>= \\case\n Empty -> say_ [\"read\", \"nothing\"]\n GroundMessage msg :< Empty ->\n say [\"read\", \"result\"] $ object [\"message\" A..= msg]\n msgs ->\n let readAndContinue Empty = pure ()\n readAndContinue (msg :< msgs') =\n prompt @'Continue\n [\"read\", \"result\"]\n (object [\"message\" A..= msg])\n Cancellable\n . const\n $ readAndContinue msgs'\n readAndContinue _ = error \"this is total\"\n in readAndContinue msgs\n continue\n\nhandleCommand ShowInventory = showPanel InventoryPanel >> continue\n\nhandleCommand Wield = do\n selectItemFromInventory_ [\"wield\", \"menu\"] Cancellable asWieldedItem\n (say_ [\"wield\", \"nothing\"])\n $ \\(MenuResult item) -> do\n prevItems <- character . inventory . wielded <<.= inRightHand item\n character . inventory . backpack\n <>= fromList (prevItems ^.. wieldedItems . wieldedItem)\n say [\"wield\", \"wielded\"] item\n continue\n\nhandleCommand Save = do\n -- TODO default save locations / config file?\n prompt_ @'StringPrompt [\"save\", \"location\"] Cancellable\n $ \\(StringResult filename) -> do\n exists <- liftIO . doesFileExist $ unpack filename\n if exists\n then confirm [\"save\", \"overwrite\"] (object [\"filename\" A..= filename])\n $ doSave filename\n else doSave filename\n continue\n where\n doSave filename = do\n src <- gets saveGame\n lift . liftIO $ do\n writeFile (unpack filename) $ toStrict src\n exitSuccess\n\nhandleCommand GoUp = do\n hasStairs <- uses entitiesAtCharacter $ elem (SomeEntity UpStaircase)\n if hasStairs\n then uses levels prevLevel >>= \\case\n Just levs' -> levels .= levs'\n Nothing ->\n -- TODO in nethack, this leaves the game. Maybe something similar here?\n say_ [\"cant\", \"goUp\"]\n else say_ [\"cant\", \"goUp\"]\n\n continue\n\nhandleCommand GoDown = do\n hasStairs <- uses entitiesAtCharacter $ elem (SomeEntity DownStaircase)\n\n if hasStairs\n then do\n levs <- use levels\n let newLevelNum = Levels.pos levs + 1\n levs' <- nextLevel (levelToGameLevel <$> genLevel newLevelNum) levs\n cEID <- use characterEntityID\n pCharacter <- entities . at cEID <<.= Nothing\n levels .= levs'\n entities . at cEID .= pCharacter\n characterPosition .= extract levs' ^. upStaircasePosition\n else say_ [\"cant\", \"goDown\"]\n\n continue\n\nhandleCommand (StartAutoMove dir) = do\n runAutocommand $ AutoMove dir\n continue\n\n--\n\nhandleCommand ToggleRevealAll = do\n val <- debugState . allRevealed <%= not\n say [\"debug\", \"toggleRevealAll\"] $ object [ \"revealAll\" A..= val ]\n continue\n\n--------------------------------------------------------------------------------\nattackAt :: Position -> AppM ()\nattackAt pos =\n uses entities (entitiesAtPositionWithType @Creature pos) >>= \\case\n Empty -> say_ [\"combat\", \"nothingToAttack\"]\n (creature :< Empty) -> attackCreature creature\n creatures ->\n menu_ [\"combat\", \"menu\"] Cancellable (entityMenu_ creatures)\n $ \\(MenuResult creature) -> attackCreature creature\n where\n attackCreature (creatureID, creature) = do\n charDamage <- uses character characterDamage\n let creature' = Creature.damage charDamage creature\n msgParams = object [\"creature\" A..= creature']\n if Creature.isDead creature'\n then do\n say [\"combat\", \"killed\"] msgParams\n entities . at creatureID .= Nothing\n else do\n msg <- uses character getAttackMessage\n message msg msgParams\n entities . ix creatureID . positioned .= SomeEntity creature'\n\n whenM (uses character $ isNothing . weapon)\n $ whenM (chance (0.08 :: Float)) $ do\n say_ [\"combat\", \"fistSelfDamage\"]\n character %= Character.damage 1\n\n stepGame -- TODO\n weapon chr = chr ^? inventory . wielded . wieldedItems . wieldableItem\n getAttackMessage chr =\n case weapon chr of\n Just wi ->\n fromMaybe (Messages.lookup [\"combat\", \"hit\", \"generic\"])\n $ wi ^. attackMessage\n Nothing ->\n Messages.lookup [\"combat\", \"hit\", \"fists\"]\n\nentityMenu_\n :: (Comonad w, Entity entity)\n => [w entity]\n -> Map Char (MenuOption (w entity))\nentityMenu_ = mkMenuItems @[_] . map entityMenuItem\n where\n entityMenuItem wentity\n = let entity = extract wentity\n in (entityMenuChar entity, MenuOption (description entity) wentity)\n\n\nentityMenuChar :: Entity a => a -> Char\nentityMenuChar entity\n = let ec = entityChar entity ^. char\n in if ec `elem` (['a'..'z'] ++ ['A'..'Z'])\n then ec\n else 'a'\n\n-- | Prompt with an item to select out of the inventory, remove it from the\n-- inventory, and call callback with it\nselectItemFromInventory\n :: forall item params.\n (ToJSON params)\n => [Text] -- ^ Menu message\n -> params -- ^ Menu message params\n -> PromptCancellable -- ^ Is the menu cancellable?\n -> Prism' Item item -- ^ Attach some extra information to the item, in a\n -- recoverable fashion. Prism vs iso so we can discard\n -- items.\n -> AppM () -- ^ Action to take if there are no items matching\n -> (PromptResult ('Menu item) -> AppM ())\n -> AppM ()\nselectItemFromInventory msgPath msgParams cancellable extraInfo onEmpty cb =\n uses (character . inventory . backpack)\n (V.mapMaybe $ preview extraInfo)\n >>= \\case\n Empty -> onEmpty\n items' ->\n menu msgPath msgParams cancellable (itemMenu items')\n $ \\(MenuResult (idx, item)) -> do\n character . inventory . backpack %= removeVectorIndex idx\n cb $ MenuResult item\n where\n itemMenu = mkMenuItems . imap itemMenuItem\n itemMenuItem idx extraInfoItem =\n let item = extraInfo # extraInfoItem\n in ( entityMenuChar item\n , MenuOption (description item) (idx, extraInfoItem))\n\nselectItemFromInventory_\n :: forall item.\n [Text] -- ^ Menu message\n -> PromptCancellable -- ^ Is the menu cancellable?\n -> Prism' Item item -- ^ Attach some extra information to the item, in a\n -- recoverable fashion. Prism vs iso so we can discard\n -- items.\n -> AppM () -- ^ Action to take if there are no items matching\n -> (PromptResult ('Menu item) -> AppM ())\n -> AppM ()\nselectItemFromInventory_ msgPath = selectItemFromInventory msgPath ()\n\n-- entityMenu :: Entity entity => [entity] -> Map Char (MenuOption entity)\n-- entityMenu = map (map runIdentity) . entityMenu_ . fmap Identity\n\nshowPanel :: Panel -> AppM ()\nshowPanel panel = do\n activePanel ?= panel\n prompt_ @'Continue [\"generic\", \"continue\"] Uncancellable\n . const\n $ activePanel .= Nothing\n\n--------------------------------------------------------------------------------\n\ngenLevel\n :: Int -- ^ level number\n -> AppM Level\ngenLevel _num = do\n let dims = Dimensions 80 80\n generator <- choose $ CaveAutomata :| [Dungeon]\n level <- case generator of\n CaveAutomata -> generateLevel SCaveAutomata CaveAutomata.defaultParams dims\n Dungeon -> generateLevel SDungeon Dungeon.defaultParams dims\n pure $!! level\n\nlevelToGameLevel :: Level -> GameLevel\nlevelToGameLevel level =\n let _levelEntities = levelToEntityMap level\n _upStaircasePosition = level ^. levelCharacterPosition\n _levelRevealedPositions = mempty\n in GameLevel {..}\n"}}}
2020-07-03 16:47:38.250556119 [ThreadId 26] - Set files of interest to: [NormalizedFilePath "/home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"]
2020-07-03 16:47:38.250296426 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didOpen","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs","languageId":"haskell","version":0,"text":"{-# LANGUAGE PartialTypeSignatures #-}\n{-# LANGUAGE StandaloneDeriving #-}\n{-# LANGUAGE RoleAnnotations #-}\n{-# LANGUAGE RecordWildCards #-}\n{-# LANGUAGE DeriveTraversable #-}\n{-# LANGUAGE DeriveFoldable #-}\n{-# LANGUAGE DeriveFunctor #-}\n{-# LANGUAGE TemplateHaskell #-}\n{-# LANGUAGE NoTypeSynonymInstances #-}\n{-# LANGUAGE DuplicateRecordFields #-}\n--------------------------------------------------------------------------------\n-- | Common data types for Xanthous\n--------------------------------------------------------------------------------\nmodule Xanthous.Data\n ( Opposite(..)\n\n -- *\n , Position'(..)\n , Position\n , x\n , y\n\n -- **\n , Positioned(..)\n , _Positioned\n , position\n , positioned\n , loc\n , _Position\n , positionFromPair\n , addPositions\n , diffPositions\n , stepTowards\n , isUnit\n\n -- * Boxes\n , Box(..)\n , topLeftCorner\n , bottomRightCorner\n , setBottomRightCorner\n , dimensions\n , inBox\n , boxIntersects\n , boxCenter\n , boxEdge\n , module Linear.V2\n\n -- *\n , Per(..)\n , invertRate\n , invertedRate\n , (|*|)\n , Ticks(..)\n , Tiles(..)\n , TicksPerTile\n , TilesPerTick\n , timesTiles\n\n -- *\n , Dimensions'(..)\n , Dimensions\n , HasWidth(..)\n , HasHeight(..)\n\n -- *\n , Direction(..)\n , move\n , asPosition\n , directionOf\n , Cardinal(..)\n\n -- *\n , Corner(..)\n , Edge(..)\n , cornerEdges\n\n -- *\n , Neighbors(..)\n , edges\n , neighborDirections\n , neighborPositions\n , neighborCells\n , arrayNeighbors\n , rotations\n , HasTopLeft(..)\n , HasTop(..)\n , HasTopRight(..)\n , HasLeft(..)\n , HasRight(..)\n , HasBottomLeft(..)\n , HasBottom(..)\n , HasBottomRight(..)\n\n -- *\n , Hitpoints(..)\n ) where\n--------------------------------------------------------------------------------\nimport Xanthous.Prelude hiding (Left, Down, Right, (.=), elements)\n--------------------------------------------------------------------------------\nimport Linear.V2 hiding (_x, _y)\nimport qualified Linear.V2 as L\nimport Linear.V4 hiding (_x, _y)\nimport Test.QuickCheck (CoArbitrary, Function, elements)\nimport Test.QuickCheck.Arbitrary.Generic\nimport Data.Group\nimport Brick (Location(Location), Edges(..))\nimport Data.Monoid (Product(..), Sum(..))\nimport Data.Array.IArray\nimport Data.Aeson.Generic.DerivingVia\nimport Data.Aeson\n ( ToJSON(..), FromJSON(..), object, (.=), (.:), withObject)\n--------------------------------------------------------------------------------\nimport Xanthous.Util (EqEqProp(..), EqProp, between)\nimport Xanthous.Util.QuickCheck (GenericArbitrary(..))\nimport Xanthous.Orphans ()\nimport Xanthous.Util.Graphics\n--------------------------------------------------------------------------------\n\n-- | opposite ∘ opposite ≡ id\nclass Opposite x where\n opposite :: x -> x\n\n--------------------------------------------------------------------------------\n\n-- fromScalar ∘ scalar ≡ id\nclass Scalar a where\n scalar :: a -> Double\n fromScalar :: Double -> a\n\ninstance Scalar Double where\n scalar = id\n fromScalar = id\n\nnewtype ScalarIntegral a = ScalarIntegral a\n deriving newtype (Eq, Ord, Num, Enum, Real, Integral)\ninstance Integral a => Scalar (ScalarIntegral a) where\n scalar = fromIntegral\n fromScalar = floor\n\nderiving via (ScalarIntegral Integer) instance Scalar Integer\nderiving via (ScalarIntegral Word) instance Scalar Word\n\n--------------------------------------------------------------------------------\n\ndata Position' a where\n Position :: { _x :: a\n , _y :: a\n } -> (Position' a)\n deriving stock (Show, Eq, Generic, Ord, Functor, Foldable, Traversable)\n deriving anyclass (NFData, Hashable, CoArbitrary, Function)\n deriving EqProp via EqEqProp (Position' a)\n deriving (ToJSON, FromJSON)\n via WithOptions '[ FieldLabelModifier '[Drop 1] ]\n (Position' a)\n\nx, y :: Lens' (Position' a) a\nx = lens (\\(Position xx _) -> xx) (\\(Position _ yy) xx -> Position xx yy)\ny = lens (\\(Position _ yy) -> yy) (\\(Position xx _) yy -> Position xx yy)\n\ntype Position = Position' Int\n\ninstance Arbitrary a => Arbitrary (Position' a) where\n arbitrary = genericArbitrary\n shrink (Position px py) = Position <$> shrink px <*> shrink py\n\n\ninstance Num a => Semigroup (Position' a) where\n (Position x₁ y₁) <> (Position x₂ y₂) = Position (x₁ + x₂) (y₁ + y₂)\n\ninstance Num a => Monoid (Position' a) where\n mempty = Position 0 0\n\ninstance Num a => Group (Position' a) where\n invert (Position px py) = Position (negate px) (negate py)\n\n-- | Positions convert to scalars by discarding their orientation and just\n-- measuring the length from the origin\ninstance (Ord a, Num a, Scalar a) => Scalar (Position' a) where\n scalar = fromIntegral . length . line (0, 0) . view _Position\n fromScalar n = Position (fromScalar n) (fromScalar n)\n\ndata Positioned a where\n Positioned :: Position -> a -> Positioned a\n deriving stock (Show, Eq, Ord, Functor, Foldable, Traversable, Generic)\n deriving anyclass (NFData, CoArbitrary, Function)\ntype role Positioned representational\n\n_Positioned :: Iso (Position, a) (Position, b) (Positioned a) (Positioned b)\n_Positioned = iso hither yon\n where\n hither (pos, a) = Positioned pos a\n yon (Positioned pos b) = (pos, b)\n\ninstance Arbitrary a => Arbitrary (Positioned a) where\n arbitrary = Positioned <$> arbitrary <*> arbitrary\n\ninstance ToJSON a => ToJSON (Positioned a) where\n toJSON (Positioned pos val) = object\n [ \"position\" .= pos\n , \"data\" .= val\n ]\n\ninstance FromJSON a => FromJSON (Positioned a) where\n parseJSON = withObject \"Positioned\" $ \\obj ->\n Positioned <$> obj .: \"position\" <*> obj .: \"data\"\n\nposition :: Lens' (Positioned a) Position\nposition = lens\n (\\(Positioned pos _) -> pos)\n (\\(Positioned _ a) pos -> Positioned pos a)\n\npositioned :: Lens (Positioned a) (Positioned b) a b\npositioned = lens\n (\\(Positioned _ x') -> x')\n (\\(Positioned pos _) x' -> Positioned pos x')\n\nloc :: Iso' Position Location\nloc = iso hither yon\n where\n hither (Position px py) = Location (px, py)\n yon (Location (lx, ly)) = Position lx ly\n\n_Position :: Iso' (Position' a) (a, a)\n_Position = iso hither yon\n where\n hither (Position px py) = (px, py)\n yon (lx, ly) = Position lx ly\n\npositionFromPair :: (Num a, Integral i, Integral j) => (i, j) -> Position' a\npositionFromPair (i, j) = Position (fromIntegral i) (fromIntegral j)\n\n-- | Add two positions\n--\n-- Operation for the additive group on positions\naddPositions :: Num a => Position' a -> Position' a -> Position' a\naddPositions = (<>)\n\n-- | Subtract two positions.\n--\n-- diffPositions pos₁ pos₂ = pos₁ `addPositions` (invert pos₂)\ndiffPositions :: Num a => Position' a -> Position' a -> Position' a\ndiffPositions (Position x₁ y₁) (Position x₂ y₂) = Position (x₁ - x₂) (y₁ - y₂)\n\n-- | Is this position a unit position? or: When taken as a difference, does this\n-- position represent a step of one tile?\n--\n-- ∀ dir :: Direction. isUnit ('asPosition' dir)\nisUnit :: (Eq a, Num a) => Position' a -> Bool\nisUnit (Position px py) =\n abs px `elem` [0,1] && abs py `elem` [0, 1] && (px, py) /= (0, 0)\n\n--------------------------------------------------------------------------------\n\ndata Dimensions' a = Dimensions\n { _width :: a\n , _height :: a\n }\n deriving stock (Show, Eq, Functor, Generic)\n deriving anyclass (CoArbitrary, Function)\nmakeFieldsNoPrefix ''Dimensions'\n\ninstance Arbitrary a => Arbitrary (Dimensions' a) where\n arbitrary = Dimensions <$> arbitrary <*> arbitrary\n\ntype Dimensions = Dimensions' Word\n\n--------------------------------------------------------------------------------\n\ndata Direction where\n Up :: Direction\n Down :: Direction\n Left :: Direction\n Right :: Direction\n UpLeft :: Direction\n UpRight :: Direction\n DownLeft :: Direction\n DownRight :: Direction\n Here :: Direction\n deriving stock (Show, Eq, Ord, Generic)\n deriving anyclass (CoArbitrary, Function, NFData, ToJSON, FromJSON, Hashable)\n deriving Arbitrary via GenericArbitrary Direction\n\ninstance Opposite Direction where\n opposite Up = Down\n opposite Down = Up\n opposite Left = Right\n opposite Right = Left\n opposite UpLeft = DownRight\n opposite UpRight = DownLeft\n opposite DownLeft = UpRight\n opposite DownRight = UpLeft\n opposite Here = Here\n\nmove :: Num a => Direction -> Position' a -> Position' a\nmove Up = y -~ 1\nmove Down = y +~ 1\nmove Left = x -~ 1\nmove Right = x +~ 1\nmove UpLeft = move Up . move Left\nmove UpRight = move Up . move Right\nmove DownLeft = move Down . move Left\nmove DownRight = move Down . move Right\nmove Here = id\n\nasPosition :: Direction -> Position\nasPosition dir = move dir mempty\n\n-- | Returns the direction that a given position is from a given source position\ndirectionOf\n :: Position -- ^ Source\n -> Position -- ^ Target\n -> Direction\ndirectionOf (Position x₁ y₁) (Position x₂ y₂) =\n case (x₁ `compare` x₂, y₁ `compare` y₂) of\n (EQ, EQ) -> Here\n (EQ, LT) -> Down\n (EQ, GT) -> Up\n (LT, EQ) -> Right\n (GT, EQ) -> Left\n\n (LT, LT) -> DownRight\n (GT, LT) -> DownLeft\n\n (LT, GT) -> UpRight\n (GT, GT) -> UpLeft\n\n-- | Take one (potentially diagonal) step towards the given position\n--\n-- ∀ src tgt. isUnit (src `diffPositions` (src `stepTowards tgt`))\nstepTowards\n :: Position -- ^ Source\n -> Position -- ^ Target\n -> Position\nstepTowards (view _Position -> p₁) (view _Position -> p₂)\n | p₁ == p₂ = _Position # p₁\n | otherwise =\n let (_:p:_) = line p₁ p₂\n in _Position # p\n\n-- | Newtype controlling arbitrary generation to only include cardinal\n-- directions ('Up', 'Down', 'Left', 'Right')\nnewtype Cardinal = Cardinal { getCardinal :: Direction }\n deriving stock (Eq, Show, Ord, Generic)\n deriving anyclass (NFData, Function, CoArbitrary)\n deriving newtype (Opposite)\n\ninstance Arbitrary Cardinal where\n arbitrary = Cardinal <$> elements [Up, Down, Left, Right]\n\n--------------------------------------------------------------------------------\n\ndata Corner\n = TopLeft\n | TopRight\n | BottomLeft\n | BottomRight\n deriving stock (Show, Eq, Ord, Enum, Bounded, Generic)\n deriving Arbitrary via GenericArbitrary Corner\n\ninstance Opposite Corner where\n opposite TopLeft = BottomRight\n opposite TopRight = BottomLeft\n opposite BottomLeft = TopRight\n opposite BottomRight = TopLeft\n\ndata Edge\n = TopEdge\n | LeftEdge\n | RightEdge\n | BottomEdge\n deriving stock (Show, Eq, Ord, Enum, Bounded, Generic)\n deriving Arbitrary via GenericArbitrary Edge\n\ninstance Opposite Edge where\n opposite TopEdge = BottomEdge\n opposite BottomEdge = TopEdge\n opposite LeftEdge = RightEdge\n opposite RightEdge = LeftEdge\n\ncornerEdges :: Corner -> (Edge, Edge)\ncornerEdges TopLeft = (TopEdge, LeftEdge)\ncornerEdges TopRight = (TopEdge, RightEdge)\ncornerEdges BottomLeft = (BottomEdge, LeftEdge)\ncornerEdges BottomRight = (BottomEdge, RightEdge)\n\n--------------------------------------------------------------------------------\n\ndata Neighbors a = Neighbors\n { _topLeft\n , _top\n , _topRight\n , _left\n , _right\n , _bottomLeft\n , _bottom\n , _bottomRight :: a\n }\n deriving stock (Show, Eq, Ord, Functor, Foldable, Traversable, Generic)\n deriving anyclass (NFData, CoArbitrary, Function, MonoFoldable)\n deriving Arbitrary via GenericArbitrary (Neighbors a)\n\ntype instance Element (Neighbors a) = a\n\nmakeFieldsNoPrefix ''Neighbors\n\ninstance Applicative Neighbors where\n pure α = Neighbors\n { _topLeft = α\n , _top = α\n , _topRight = α\n , _left = α\n , _right = α\n , _bottomLeft = α\n , _bottom = α\n , _bottomRight = α\n }\n nf <*> nx = Neighbors\n { _topLeft = nf ^. topLeft $ nx ^. topLeft\n , _top = nf ^. top $ nx ^. top\n , _topRight = nf ^. topRight $ nx ^. topRight\n , _left = nf ^. left $ nx ^. left\n , _right = nf ^. right $ nx ^. right\n , _bottomLeft = nf ^. bottomLeft $ nx ^. bottomLeft\n , _bottom = nf ^. bottom $ nx ^. bottom\n , _bottomRight = nf ^. bottomRight $ nx ^. bottomRight\n }\n\nedges :: Neighbors a -> Edges a\nedges neighs = Edges\n { eTop = neighs ^. top\n , eBottom = neighs ^. bottom\n , eLeft = neighs ^. left\n , eRight = neighs ^. right\n }\n\nneighborDirections :: Neighbors Direction\nneighborDirections = Neighbors\n { _topLeft = UpLeft\n , _top = Up\n , _topRight = UpRight\n , _left = Left\n , _right = Right\n , _bottomLeft = DownLeft\n , _bottom = Down\n , _bottomRight = DownRight\n }\n\nneighborPositions :: Num a => Position' a -> Neighbors (Position' a)\nneighborPositions pos = (`move` pos) <$> neighborDirections\n\nneighborCells :: Num a => (a, a) -> Neighbors (a, a)\nneighborCells = map (view _Position) . neighborPositions . review _Position\n\narrayNeighbors\n :: (IArray a e, Ix i, Num i)\n => a (i, i) e\n -> (i, i)\n -> Neighbors (Maybe e)\narrayNeighbors arr center = arrLookup <$> neighborPositions (_Position # center)\n where\n arrLookup (view _Position -> pos)\n | inRange (bounds arr) pos = Just $ arr ! pos\n | otherwise = Nothing\n\n-- | Returns a list of all 4 90-degree rotations of the given neighbors\nrotations :: Neighbors a -> V4 (Neighbors a)\nrotations orig@(Neighbors tl t tr l r bl b br) = V4\n orig -- tl t tr\n -- l r\n -- bl b br\n\n (Neighbors bl l tl b t br r tr) -- bl l tl\n -- b t\n -- br r tr\n\n (Neighbors br b bl r l tr t tl) -- br b bl\n -- r l\n -- tr t tl\n\n (Neighbors tr r br t b tl l bl) -- tr r br\n -- t b\n -- tl l bl\n\n--------------------------------------------------------------------------------\n\nnewtype Per a b = Rate Double\n deriving stock (Show, Eq, Generic)\n deriving anyclass (NFData, CoArbitrary, Function)\n deriving (Num, Ord, Enum, Real, Fractional, ToJSON, FromJSON) via Double\n deriving (Semigroup, Monoid) via Product Double\ninstance Arbitrary (Per a b) where arbitrary = genericArbitrary\n\ninvertRate :: a `Per` b -> b `Per` a\ninvertRate (Rate p) = Rate $ 1 / p\n\ninvertedRate :: Iso (a `Per` b) (b' `Per` a') (b `Per` a) (a' `Per` b')\ninvertedRate = iso invertRate invertRate\n\ninfixl 7 |*|\n(|*|) :: (Scalar a, Scalar b) => a `Per` b -> b -> a\n(|*|) (Rate rate) b = fromScalar $ rate * scalar b\n\nnewtype Ticks = Ticks Word\n deriving stock (Show, Eq, Generic)\n deriving anyclass (NFData, CoArbitrary, Function)\n deriving (Num, Ord, Bounded, Enum, Integral, Real, ToJSON, FromJSON) via Word\n deriving (Semigroup, Monoid) via (Sum Word)\n deriving Scalar via ScalarIntegral Ticks\ninstance Arbitrary Ticks where arbitrary = genericArbitrary\n\nnewtype Tiles = Tiles Double\n deriving stock (Show, Eq, Generic)\n deriving anyclass (NFData, CoArbitrary, Function)\n deriving (Num, Ord, Enum, Real, ToJSON, FromJSON, Scalar) via Double\n deriving (Semigroup, Monoid) via (Sum Double)\ninstance Arbitrary Tiles where arbitrary = genericArbitrary\n\ntype TicksPerTile = Ticks `Per` Tiles\ntype TilesPerTick = Tiles `Per` Ticks\n\ntimesTiles :: TicksPerTile -> Tiles -> Ticks\ntimesTiles = (|*|)\n\n--------------------------------------------------------------------------------\n\nnewtype Hitpoints = Hitpoints Word\n deriving stock (Show, Eq, Generic)\n deriving anyclass (NFData, CoArbitrary, Function)\n deriving (Arbitrary, Num, Ord, Bounded, Enum, Integral, Real, ToJSON, FromJSON)\n via Word\n deriving (Semigroup, Monoid) via Sum Word\n\n--------------------------------------------------------------------------------\n\ndata Box a = Box\n { _topLeftCorner :: V2 a\n , _dimensions :: V2 a\n }\n deriving stock (Show, Eq, Ord, Functor, Generic)\n deriving Arbitrary via GenericArbitrary (Box a)\nmakeFieldsNoPrefix ''Box\n\nbottomRightCorner :: Num a => Box a -> V2 a\nbottomRightCorner box =\n V2 (box ^. topLeftCorner . L._x + box ^. dimensions . L._x)\n (box ^. topLeftCorner . L._y + box ^. dimensions . L._y)\n\nsetBottomRightCorner :: (Num a, Ord a) => Box a -> V2 a -> Box a\nsetBottomRightCorner box br@(V2 brx bry)\n | brx < box ^. topLeftCorner . L._x || bry < box ^. topLeftCorner . L._y\n = box & topLeftCorner .~ br\n & dimensions . L._x .~ ((box ^. topLeftCorner . L._x) - brx)\n & dimensions . L._y .~ ((box ^. topLeftCorner . L._y) - bry)\n | otherwise\n = box & dimensions . L._x .~ (brx - (box ^. topLeftCorner . L._x))\n & dimensions . L._y .~ (bry - (box ^. topLeftCorner . L._y))\n\ninBox :: (Ord a, Num a) => Box a -> V2 a -> Bool\ninBox box pt = flip all [L._x, L._y] $ \\component ->\n between (box ^. topLeftCorner . component)\n (box ^. to bottomRightCorner . component)\n (pt ^. component)\n\nboxIntersects :: (Ord a, Num a) => Box a -> Box a -> Bool\nboxIntersects box₁ box₂\n = any (inBox box₁) [box₂ ^. topLeftCorner, bottomRightCorner box₂]\n\nboxCenter :: (Fractional a) => Box a -> V2 a\nboxCenter box = V2 cx cy\n where\n cx = box ^. topLeftCorner . L._x + (box ^. dimensions . L._x / 2)\n cy = box ^. topLeftCorner . L._y + (box ^. dimensions . L._y / 2)\n\nboxEdge :: (Enum a, Num a) => Box a -> Edge -> [V2 a]\nboxEdge box LeftEdge =\n V2 (box ^. topLeftCorner . L._x)\n <$> [box ^. topLeftCorner . L._y .. box ^. to bottomRightCorner . L._y]\nboxEdge box RightEdge =\n V2 (box ^. to bottomRightCorner . L._x)\n <$> [box ^. to bottomRightCorner . L._y .. box ^. to bottomRightCorner . L._y]\nboxEdge box TopEdge =\n flip V2 (box ^. topLeftCorner . L._y)\n <$> [box ^. topLeftCorner . L._x .. box ^. to bottomRightCorner . L._x]\nboxEdge box BottomEdge =\n flip V2 (box ^. to bottomRightCorner . L._y)\n <$> [box ^. topLeftCorner . L._x .. box ^. to bottomRightCorner . L._x]\n"}}}
2020-07-03 16:47:38.252139234 [ThreadId 26] - Restarting build session (aborting the previous one took 0.00s)
2020-07-03 16:47:38.252209318 [ThreadId 25] - Finishing build session(exception: AsyncCancelled)
2020-07-03 16:47:38.252998785 [ThreadId 26] - Opened text document: file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:38.25345605 [ThreadId 26] - Set files of interest to: [NormalizedFilePath "/home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs",NormalizedFilePath "/home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"]
2020-07-03 16:47:38.253602066 [ThreadId 45] - Finishing build session(exception: AsyncCancelled)
2020-07-03 16:47:38.253661166 [ThreadId 26] - Restarting build session (aborting the previous one took 0.00s)
2020-07-03 16:47:38.253756282 [ThreadId 26] - Opened text document: file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs
2020-07-03 16:47:38.255110683 [ThreadId 97] - Consulting the cradle for "/home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"
2020-07-03 16:47:38.25544659 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"token":0},"method":"window/workDoneProgress/create","id":0}
2020-07-03 16:47:38.255526512 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"begin","cancellable":false,"title":"Setting up project xanthous"},"token":0},"method":"$/progress"}
2020-07-03 16:47:38.27400237 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"position":{"line":505,"character":42}},"id":152}
2020-07-03 16:47:38.274275334 [ThreadId 101] - DocumentHighlight request at position 506:43 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs
2020-07-03 16:47:38.274333708 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"range":{"start":{"line":505,"character":42},"end":{"line":505,"character":42}},"context":{"diagnostics":[]}},"id":153}
2020-07-03 16:47:38.274528644 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"$/cancelRequest","params":{"id":152}}
2020-07-03 16:47:38.274549263 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":152}
2020-07-03 16:47:38.274606044 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":107,"character":35}},"id":154}
2020-07-03 16:47:38.274669899 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"$/cancelRequest","params":{"id":153}}
2020-07-03 16:47:38.274763565 [ThreadId 26] - Cancelled request IdInt 153
2020-07-03 16:47:38.274742633 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":35},"end":{"line":107,"character":35}},"context":{"diagnostics":[]}},"id":155}
2020-07-03 16:47:38.274857839 [ThreadId 7] - <--2--{"error":{"code":-32800,"message":""},"jsonrpc":"2.0","id":153}
2020-07-03 16:47:38.27491423 [ThreadId 108] - DocumentHighlight request at position 108:36 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:38.275115756 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":154}
2020-07-03 16:47:38.298335388 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"range":{"start":{"line":505,"character":42},"end":{"line":505,"character":42}},"context":{"diagnostics":[]}},"id":156}
2020-07-03 16:47:38.322338342 [ThreadId 5] - ---> {"jsonrpc":"2.0","id":0,"result":null}
2020-07-03 16:47:38.322507732 [ThreadId 5] - haskell-lsp:Got reply message:"{\"jsonrpc\":\"2.0\",\"id\":0,\"result\":null}\n"
2020-07-03 16:47:38.542915044 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"position":{"line":505,"character":42}},"id":157}
2020-07-03 16:47:38.543126106 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"$/cancelRequest","params":{"id":155}}
2020-07-03 16:47:38.543274547 [ThreadId 26] - Cancelled request IdInt 155
2020-07-03 16:47:38.543240617 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"range":{"start":{"line":505,"character":42},"end":{"line":505,"character":42}},"context":{"diagnostics":[]}},"id":158}
2020-07-03 16:47:38.543556114 [ThreadId 7] - <--2--{"error":{"code":-32800,"message":""},"jsonrpc":"2.0","id":155}
2020-07-03 16:47:40.484245265 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"end"},"token":0},"method":"$/progress"}
2020-07-03 16:47:40.484173514 [ThreadId 97] - Session loading result: Right (ComponentOptions {componentOptions = ["-fbuilding-cabal-package","-O0","-outputdir","/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build","-odir","/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build","-hidir","/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build","-stubdir","/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build","-i","-i/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build","-isrc","-i/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build/autogen","-i/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build/global-autogen","-I/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build/autogen","-I/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build/global-autogen","-I/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build","-optP-include","-optP/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/build/autogen/cabal_macros.h","-this-unit-id","xanthous-0.1.0.0-inplace","-hide-all-packages","-Wmissing-home-modules","-no-user-package-db","-package-db","/home/grfn/.cabal/store/ghc-8.8.3/package.db","-package-db","/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/packagedb/ghc-8.8.3","-package-db","/home/grfn/code/depot/users/glittershark/xanthous/dist-newstyle/build/x86_64-linux/ghc-8.8.3/xanthous-0.1.0.0/opt/package.conf.inplace","-package-id","JuicyPixels-3.3.5-2agTN1eLbb42JtWAWSxH2w","-package-id","MonadRandom-0.5.1.2-CJYGjs2grhnIGVYLkfUk5Q","-package-id","QuickCheck-2.13.2-7Gdq6n6V0PBHdK79OO662y","-package-id","Rasterific-0.7.5.2-EQoZcUJEbJKEWrsZJ4179Z","-package-id","aeson-1.4.7.1-5lFE4NI0VYBHwz75Ema9FX","-package-id","array-0.5.4.0","-package-id","async-2.2.2-9roCKOC3ShkBtv3iqrylfJ","-package-id","base-4.13.0.0","-package-id","bifunctors-5.5.7-1PLDiC6nz7O33RIEtINbSS","-package-id","brick-0.52.1-364BGnH2raWBCAIlcXbGTT","-package-id","checkers-0.5.5-Fl08a8BQ8T2IK8xxcoI7ew","-package-id","classy-prelude-1.5.0-IV7voSHMP7oHWiAAUTvYbS","-package-id","comonad-5.0.6-EweAwk1BSchF3acvlDwJDV","-package-id","comonad-extras-5.0-FyMvxBQ9UeyGeUa52xAa9R","-package-id","constraints-0.11.2-JBXqssnikL1F6dKuEmbSAv","-package-id","containers-0.6.2.1","-package-id","data-default-0.7.1.1-5cjrhz8y8DG881Qqkxq9GB","-package-id","deepseq-1.4.4.0","-package-id","directory-1.3.6.0","-package-id","fgl-5.7.0.2-2Q7b5F4c74NLU7g5NTYKkr","-package-id","fgl-arbitrary-0.2.0.5-HSKE9z9iYNa1yxfB9W9Na5","-package-id","file-embed-0.0.12.0-6m1AWlBcZCeB1357XiAyKS","-package-id","filepath-1.4.2.1","-package-id","generic-arbitrary-0.1.0-1H3aQeEQlpBA4tTFtNMwjN","-package-id","generic-lens-1.2.0.1-LCaaPnNeTl9HoiCUjqmGOs","-package-id","generic-monoid-0.1.0.0-BPk8KsZJcdKH3MUDd2zuvj","-package-id","groups-0.4.1.0-1IbGa9NMq347ZnxfKU1rQq","-package-id","hgeometry-0.9.0.0-3Eu4VuzQPOSA15AwDDRM06","-package-id","hgeometry-combinatorial-0.9.0.0-AcSzBzQ4gUGI7WEYWnPW0j","-package-id","lens-4.18.1-Kkpj25wFiGf1r9wIWwSTLz","-package-id","lifted-async-0.10.0.6-CA2uDhfaDG88DdTJhW3VEy","-package-id","linear-1.20.9-LWUPgk7PymCBxFM4ksXuk9","-package-id","megaparsec-8.0.0-Itz7sNO6UUPG6Ap7NB5bV6","-package-id","mmorph-1.1.3-JCMpsrUvhnr1NOPkDZRyaY","-package-id","monad-control-1.0.2.3-AJnt25pd6QaH774qJ90WDm","-package-id","mtl-2.2.2","-package-id","optparse-applicative-0.15.1.0-AJGcenxfA2SBbRiQT4rIZE","-package-id","parallel-3.2.2.0-JZ47W1IFrQUHBkshKV2j85","-package-id","parser-combinators-1.2.1-KFbv2djhJYDIX4OK1EDf6j","-package-id","pointed-5.0.1-HanYfhIAsNKKikrvFDIOj9","-package-id","quickcheck-instances-0.3.22-78e1LdRRFzJJ8tacsdcfK5","-package-id","quickcheck-text-0.1.2.1-84WP8kgtx4g5c6J9GY099G","-package-id","random-1.1-CUqV1zxrwrE4K5XCdTZSYy","-package-id","random-extras-0.19-DPkt3FniGyzHsT2H4DFbS3","-package-id","random-fu-0.2.7.4-2o3XkV7Bb189TlXraMDvui","-package-id","random-source-0.3.0.8-GLzkk4LUT4KI9r7fmc9jXh","-package-id","raw-strings-qq-1.1-ABOIqodJfZP7nHVHWpQA5w","-package-id","reflection-2.1.5-6rCQJ19CEG4G2R0hPApono","-package-id","semigroupoids-5.3.4-BDPq5bYXNbEHh6SArfelAg","-package-id","stache-2.1.1-DEhZDryskPJ5R2bhLI4WAw","-package-id","streams-3.3-Fn3qrKUniWK6ZcXewNqbSO","-package-id","text-1.2.4.0","-package-id","text-zipper-0.10.1-FCGT3swpim1L2LwJHrXetI","-package-id","tomland-1.2.1.0-L3SFeRiyvDYGbaymrtxZMD","-package-id","transformers-0.5.6.2","-package-id","vector-0.12.1.2-C2W44iPdAFeHo4yLU081Gd","-package-id","vty-5.26-DCEVdHZqfl65j3x2zA02pD","-package-id","witherable-0.3.5-3AWavT72a1EFnmjJ4D85ZK","-package-id","yaml-0.11.4.0-IhZDlnQXpOS6SWxlyS4iff","-package-id","zlib-0.6.2.1-HNly9B6JPkSJIRw1U2dqvo","-XHaskell2010","-XBlockArguments","-XConstraintKinds","-XDataKinds","-XDeriveAnyClass","-XDeriveGeneric","-XDerivingStrategies","-XDerivingVia","-XFlexibleContexts","-XFlexibleInstances","-XFunctionalDependencies","-XGADTSyntax","-XGeneralizedNewtypeDeriving","-XKindSignatures","-XLambdaCase","-XMultiWayIf","-XNoImplicitPrelude","-XNoStarIsType","-XOverloadedStrings","-XPolyKinds","-XRankNTypes","-XScopedTypeVariables","-XTupleSections","-XTypeApplications","-XTypeFamilies","-XTypeOperators","-XViewPatterns","Data.Aeson.Generic.DerivingVia","Main","Xanthous.AI.Gormlak","Xanthous.App","Xanthous.App.Autocommands","Xanthous.App.Common","Xanthous.App.Prompt","Xanthous.App.Time","Xanthous.Command","Xanthous.Data","Xanthous.Data.App","Xanthous.Data.Entities","Xanthous.Data.EntityChar","Xanthous.Data.EntityMap","Xanthous.Data.EntityMap.Graphics","Xanthous.Data.Levels","Xanthous.Data.NestedMap","Xanthous.Data.VectorBag","Xanthous.Entities.Character","Xanthous.Entities.Creature","Xanthous.Entities.Creature.Hippocampus","Xanthous.Entities.Draw.Util","Xanthous.Entities.Entities","Xanthous.Entities.Environment","Xanthous.Entities.Item","Xanthous.Entities.Marker","Xanthous.Entities.Raws","Xanthous.Entities.RawTypes","Xanthous.Game","Xanthous.Game.Arbitrary","Xanthous.Game.Draw","Xanthous.Game.Env","Xanthous.Game.Lenses","Xanthous.Game.Prompt","Xanthous.Game.State","Xanthous.Generators","Xanthous.Generators.CaveAutomata","Xanthous.Generators.Dungeon","Xanthous.Generators.LevelContents","Xanthous.Generators.Util","Xanthous.Generators.Village","Xanthous.Messages","Xanthous.Messages.Template","Xanthous.Monad","Xanthous.Orphans","Xanthous.Prelude","Xanthous.Random","Xanthous.Util","Xanthous.Util.Comonad","Xanthous.Util.Graph","Xanthous.Util.Graphics","Xanthous.Util.Inflection","Xanthous.Util.JSON","Xanthous.Util.Optparse","Xanthous.Util.QuickCheck","Paths_xanthous","-Wall","-hide-all-packages"], componentRoot = "/home/grfn/code/depot/users/glittershark/xanthous", componentDependencies = ["xanthous.cabal","cabal.project","cabal.project.local"]})
2020-07-03 16:47:40.524841002 [ThreadId 97] - Using interface files cache dir: /home/grfn/.cache/ghcide/xanthous-0.1.0.0-inplace-1e68eb9b7b3ad0f0c42293e510f2c508c77c73e8
2020-07-03 16:47:40.525297356 [ThreadId 97] - Making new HscEnv[xanthous-0.1.0.0-inplace]
2020-07-03 16:47:40.540250084 [ThreadId 97] - New Component Cache HscEnvEq: (([],Just HscEnvEq 13),fromList [("/home/grfn/code/depot/users/glittershark/xanthous/hie.yaml",Just 2020-07-03 20:27:34.460004665 UTC),("cabal.project",Nothing),("cabal.project.local",Nothing),("xanthous.cabal",Nothing)])
2020-07-03 16:47:40.598323565 [ThreadId 60] - Finishing build session(exception: AsyncCancelled)
2020-07-03 16:47:40.59841344 [ThreadId 97] - Restarting build session (aborting the previous one took 0.00s)
2020-07-03 16:47:40.699236319 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"token":"76"},"method":"window/workDoneProgress/create","id":1}
2020-07-03 16:47:40.699393789 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"begin","title":"Processing"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:40.699711958 [ThreadId 5] - ---> {"jsonrpc":"2.0","id":1,"result":null}
2020-07-03 16:47:40.69985518 [ThreadId 5] - haskell-lsp:Got reply message:"{\"jsonrpc\":\"2.0\",\"id\":1,\"result\":null}\n"
2020-07-03 16:47:40.799702738 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"8/11"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:40.899931615 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"11/21"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:41.002277918 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"21/30"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:41.102342805 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"33/42"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:41.203107556 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"54/59"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:41.501751595 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"22/70"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:41.60181738 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"25/70"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:41.701866786 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"29/71"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:41.80229549 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"35/75"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:42.542168926 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Messages.hs","diagnostics":[{"severity":1,"range":{"start":{"line":79,"character":14},"end":{"line":79,"character":55}},"source":"typecheck","message":"• Exception when trying to run compile-time code:\n src/Xanthous/messages.yaml: openBinaryFile: does not exist (No such file or directory)\n Code: embedFile \"src/Xanthous/messages.yaml\"\n• In the untyped splice: $(embedFile \"src/Xanthous/messages.yaml\")"}]},"method":"textDocument/publishDiagnostics"}
2020-07-03 16:47:42.544002702 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"$/cancelRequest","params":{"id":157}}
2020-07-03 16:47:42.54426598 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"position":{"line":505,"character":42}},"id":159}
2020-07-03 16:47:42.544529714 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"$/cancelRequest","params":{"id":158}}
2020-07-03 16:47:42.544674665 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"range":{"start":{"line":505,"character":42},"end":{"line":505,"character":42}},"context":{"diagnostics":[]}},"id":160}
2020-07-03 16:47:42.58713928 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"$/cancelRequest","params":{"id":156}}
2020-07-03 16:47:42.58727591 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs"},"range":{"start":{"line":505,"character":42},"end":{"line":505,"character":42}},"context":{"diagnostics":[]}},"id":161}
2020-07-03 16:47:42.587393303 [ThreadId 26] - Cancelled request IdInt 156
2020-07-03 16:47:42.587565116 [ThreadId 26] - Cancelled request IdInt 157
2020-07-03 16:47:42.587573756 [ThreadId 7] - <--2--{"error":{"code":-32800,"message":""},"jsonrpc":"2.0","id":156}
2020-07-03 16:47:42.587665403 [ThreadId 26] - Cancelled request IdInt 158
2020-07-03 16:47:42.58768614 [ThreadId 7] - <--2--{"error":{"code":-32800,"message":""},"jsonrpc":"2.0","id":157}
2020-07-03 16:47:42.587795772 [ThreadId 7] - <--2--{"error":{"code":-32800,"message":""},"jsonrpc":"2.0","id":158}
2020-07-03 16:47:42.587902005 [ThreadId 4340] - DocumentHighlight request at position 506:43 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/Data.hs
2020-07-03 16:47:42.588207151 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":159}
2020-07-03 16:47:42.607631504 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"40/75"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:42.70801906 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"42/75"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:43.381977241 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"47/78"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:43.411370363 [ThreadId 4458] - finish: C:GetHieFile (took 2.81s)
2020-07-03 16:47:43.411590366 [ThreadId 4458] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:43.483301093 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"49/78"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:43.68638384 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"54/82"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:43.924907433 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"57/82"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:44.02512767 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"53/82"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:44.125796936 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"54/82"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:44.225947753 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"57/82"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:44.326343372 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"59/83"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:44.627075181 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"72/86"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:45.262718265 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"report","message":"74/87"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:45.269608211 [ThreadId 7] - <--2--{"jsonrpc":"2.0","params":{"value":{"kind":"end"},"token":"76"},"method":"$/progress"}
2020-07-03 16:47:45.269577153 [ThreadId 4770] - finish: C:GetHieFile (took 1.86s)
2020-07-03 16:47:45.269878341 [ThreadId 4770] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:45.269997116 [ThreadId 4770] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:45.27012446 [ThreadId 4770] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:45.270183353 [ThreadId 4770] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:45.270296993 [ThreadId 4770] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:45.663680184 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.39s)
2020-07-03 16:47:45.663792296 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":160}
2020-07-03 16:47:45.66395219 [ThreadId 4773] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:45.664035201 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:45.66415801 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":161}
2020-07-03 16:47:46.774355113 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":35},"end":{"line":107,"character":35}},"context":{"diagnostics":[]}},"id":162}
2020-07-03 16:47:46.774624341 [ThreadId 4773] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:46.774692246 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:46.774839789 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":162}
2020-07-03 16:47:47.068201499 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":35},"end":{"line":107,"character":35}},"context":{"diagnostics":[]}},"id":163}
2020-07-03 16:47:47.068467434 [ThreadId 4773] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:47.068544134 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:47.068648954 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":163}
2020-07-03 16:47:47.074269575 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":107,"character":35}},"id":164}
2020-07-03 16:47:47.074394545 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":35},"end":{"line":107,"character":35}},"context":{"diagnostics":[]}},"id":165}
2020-07-03 16:47:47.074454061 [ThreadId 4785] - DocumentHighlight request at position 108:36 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:47.074610072 [ThreadId 4773] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:47.074646681 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":164}
2020-07-03 16:47:47.074743012 [ThreadId 4773] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:47.074801266 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:47.074846709 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":165}
2020-07-03 16:47:49.048519914 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":108,"character":35},"end":{"line":108,"character":35}},"context":{"diagnostics":[]}},"id":166}
2020-07-03 16:47:49.048776194 [ThreadId 4773] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:49.048844948 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:49.048910331 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":166}
2020-07-03 16:47:49.348701154 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/hover","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":108,"character":35}},"id":167}
2020-07-03 16:47:49.348864302 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":108,"character":35}},"id":168}
2020-07-03 16:47:49.348902097 [ThreadId 4794] - GhcIde.hover entered (ideLogger)
2020-07-03 16:47:49.348970341 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":108,"character":35},"end":{"line":108,"character":35}},"context":{"diagnostics":[]}},"id":169}
2020-07-03 16:47:49.349100773 [ThreadId 4794] - Hover request at position 109:36 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:49.3493134 [ThreadId 4773] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:49.34937417 [ThreadId 7] - <--2--{"result":null,"jsonrpc":"2.0","id":167}
2020-07-03 16:47:49.349411344 [ThreadId 4797] - DocumentHighlight request at position 109:36 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:49.349592878 [ThreadId 4773] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:49.349654601 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":168}
2020-07-03 16:47:49.349810233 [ThreadId 4773] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:49.349904571 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:49.349956086 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":169}
2020-07-03 16:47:50.54832315 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":36},"end":{"line":107,"character":36}},"context":{"diagnostics":[]}},"id":170}
2020-07-03 16:47:50.548637174 [ThreadId 4773] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:50.548716854 [ThreadId 4773] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:50.54882344 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":170}
2020-07-03 16:47:50.596545877 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didChange","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs","version":13},"contentChanges":[{"range":{"start":{"line":107,"character":36},"end":{"line":107,"character":36}},"rangeLength":0,"text":" "}]}}
2020-07-03 16:47:50.597121022 [ThreadId 123] - Finishing build session(exception: AsyncCancelled)
2020-07-03 16:47:50.597181805 [ThreadId 26] - Restarting build session (aborting the previous one took 0.00s)
2020-07-03 16:47:50.5973218 [ThreadId 26] - Modified text document: file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:50.995429989 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didChange","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs","version":14},"contentChanges":[{"range":{"start":{"line":107,"character":37},"end":{"line":107,"character":37}},"rangeLength":0,"text":"1"}]}}
2020-07-03 16:47:50.995809326 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/completion","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":107,"character":38},"context":{"triggerKind":1}},"id":171}
2020-07-03 16:47:50.995958392 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":38},"end":{"line":107,"character":38}},"context":{"diagnostics":[]}},"id":172}
2020-07-03 16:47:50.996591439 [ThreadId 4808] - Finishing build session(exception: AsyncCancelled)
2020-07-03 16:47:50.996702752 [ThreadId 26] - Restarting build session (aborting the previous one took 0.00s)
2020-07-03 16:47:50.996808708 [ThreadId 26] - Modified text document: file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:50.997292756 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":171}
2020-07-03 16:47:51.615793605 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didSave","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs","version":14}}}
2020-07-03 16:47:52.205140821 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"$/cancelRequest","params":{"id":172}}
2020-07-03 16:47:52.20526033 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":37},"end":{"line":107,"character":37}},"context":{"diagnostics":[]}},"id":173}
2020-07-03 16:47:52.205320458 [ThreadId 26] - Cancelled request IdInt 172
2020-07-03 16:47:52.205332021 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":107,"character":37}},"id":174}
2020-07-03 16:47:52.205424959 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":37},"end":{"line":107,"character":37}},"context":{"diagnostics":[]}},"id":175}
2020-07-03 16:47:52.205441296 [ThreadId 7] - <--2--{"error":{"code":-32800,"message":""},"jsonrpc":"2.0","id":172}
2020-07-03 16:47:52.205730123 [ThreadId 7115] - Finishing build session(exception: AsyncCancelled)
2020-07-03 16:47:52.205788795 [ThreadId 26] - Restarting build session (aborting the previous one took 0.00s)
2020-07-03 16:47:52.20588751 [ThreadId 26] - Saved text document: file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:52.947397301 [ThreadId 12136] - finish: C:ProduceCompletions (took 0.74s)
2020-07-03 16:47:52.947487319 [ThreadId 12136] - finish: C:GetParsedModule (took 0.00s)
2020-07-03 16:47:52.947649745 [ThreadId 12136] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:52.947747916 [ThreadId 12136] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:52.947839831 [ThreadId 12140] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:52.947896198 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":173}
2020-07-03 16:47:52.947910004 [ThreadId 12143] - DocumentHighlight request at position 108:38 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:52.948097626 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":174}
2020-07-03 16:47:52.948190482 [ThreadId 12149] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:52.948334458 [ThreadId 12149] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:52.948400229 [ThreadId 12149] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:52.948443446 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":175}
2020-07-03 16:47:57.648245151 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":106,"character":36},"end":{"line":106,"character":36}},"context":{"diagnostics":[]}},"id":176}
2020-07-03 16:47:57.648524668 [ThreadId 12149] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:57.648592198 [ThreadId 12149] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:57.648721403 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":176}
2020-07-03 16:47:57.948185629 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":106,"character":36},"end":{"line":106,"character":36}},"context":{"diagnostics":[]}},"id":177}
2020-07-03 16:47:57.948459014 [ThreadId 12149] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:57.948531087 [ThreadId 12149] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:57.948616663 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":177}
2020-07-03 16:47:58.168446194 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":37},"end":{"line":107,"character":37}},"context":{"diagnostics":[]}},"id":178}
2020-07-03 16:47:58.168740098 [ThreadId 12149] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:58.168814926 [ThreadId 12149] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:58.168868977 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":178}
2020-07-03 16:47:58.468563103 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/hover","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":107,"character":37}},"id":179}
2020-07-03 16:47:58.468688167 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":107,"character":37}},"id":180}
2020-07-03 16:47:58.468756099 [ThreadId 12161] - GhcIde.hover entered (ideLogger)
2020-07-03 16:47:58.468842207 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":107,"character":37},"end":{"line":107,"character":37}},"context":{"diagnostics":[]}},"id":181}
2020-07-03 16:47:58.468909891 [ThreadId 12161] - Hover request at position 108:38 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:58.469024506 [ThreadId 12149] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:58.46908099 [ThreadId 7] - <--2--{"result":null,"jsonrpc":"2.0","id":179}
2020-07-03 16:47:58.469121435 [ThreadId 12164] - DocumentHighlight request at position 108:38 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:58.4692574 [ThreadId 12149] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:58.469341619 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":180}
2020-07-03 16:47:58.469479571 [ThreadId 12149] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:58.469575826 [ThreadId 12149] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:58.469621354 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":181}
2020-07-03 16:47:59.264098764 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":108,"character":37},"end":{"line":108,"character":37}},"context":{"diagnostics":[]}},"id":182}
2020-07-03 16:47:59.264350174 [ThreadId 12149] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:59.264419789 [ThreadId 12149] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:59.264529353 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":182}
2020-07-03 16:47:59.564249315 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/hover","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":108,"character":37}},"id":183}
2020-07-03 16:47:59.564400308 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/documentHighlight","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"position":{"line":108,"character":37}},"id":184}
2020-07-03 16:47:59.564454061 [ThreadId 12173] - GhcIde.hover entered (ideLogger)
2020-07-03 16:47:59.564521056 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/codeAction","params":{"textDocument":{"uri":"file:///home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs"},"range":{"start":{"line":108,"character":37},"end":{"line":108,"character":37}},"context":{"diagnostics":[]}},"id":185}
2020-07-03 16:47:59.564619496 [ThreadId 12173] - Hover request at position 109:38 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:59.564785054 [ThreadId 12149] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:59.564825597 [ThreadId 7] - <--2--{"result":null,"jsonrpc":"2.0","id":183}
2020-07-03 16:47:59.56484162 [ThreadId 12176] - DocumentHighlight request at position 109:38 in file: /home/grfn/code/depot/users/glittershark/xanthous/src/Xanthous/App.hs
2020-07-03 16:47:59.56504575 [ThreadId 12149] - finish: C:GetHieFile (took 0.00s)
2020-07-03 16:47:59.565075527 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":184}
2020-07-03 16:47:59.56528311 [ThreadId 12149] - finish: CodeAction (took 0.00s)
2020-07-03 16:47:59.565369257 [ThreadId 12149] - finish: CodeAction:PackageExports (took 0.00s)
2020-07-03 16:47:59.565409862 [ThreadId 7] - <--2--{"result":[],"jsonrpc":"2.0","id":185}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment