fix(grfn/xanthous): Fix build

Bunch of miscellaneous stuff due to breakages in dependencies

Change-Id: I807cfa875148e7e5b691f2be0b58dc0a08f3c3ad
Reviewed-on: https://cl.tvl.fyi/c/depot/+/9003
Autosubmit: grfn <grfn@gws.fyi>
Reviewed-by: grfn <grfn@gws.fyi>
Tested-by: BuildkiteCI
This commit is contained in:
Aspen Smith 2023-08-03 11:32:04 -04:00 committed by clbot
parent e40908d4aa
commit dbc17e8c4b
3 changed files with 12 additions and 6 deletions

View file

@ -55,7 +55,7 @@ handlePromptEvent _ (Prompt _ SConfirm _ _ _) (VtyEvent (EvKey (KChar 'n') []))
handlePromptEvent handlePromptEvent
msg msg
(Prompt c SStringPrompt (StringPromptState edit) pri cb) (Prompt c SStringPrompt (StringPromptState edit) pri cb)
ev (VtyEvent ev)
= do = do
edit' <- lift $ handleEditorEvent ev edit edit' <- lift $ handleEditorEvent ev edit
let prompt' = Prompt c SStringPrompt (StringPromptState edit') pri cb let prompt' = Prompt c SStringPrompt (StringPromptState edit') pri cb

View file

@ -191,7 +191,7 @@ y = lens (\(Position _ yy) -> yy) (\(Position xx _) yy -> Position xx yy)
type Position = Position' Int type Position = Position' Int
instance (Arg (Position' a) a, Arbitrary a) => Arbitrary (Position' a) where instance (Arbitrary a) => Arbitrary (Position' a) where
arbitrary = genericArbitrary arbitrary = genericArbitrary
shrink (Position px py) = Position <$> shrink px <*> shrink py shrink (Position px py) = Position <$> shrink px <*> shrink py
@ -434,7 +434,7 @@ data Neighbors a = Neighbors
deriving stock (Show, Eq, Ord, Functor, Foldable, Traversable, Generic) deriving stock (Show, Eq, Ord, Functor, Foldable, Traversable, Generic)
deriving anyclass (NFData, CoArbitrary, Function, MonoFoldable) deriving anyclass (NFData, CoArbitrary, Function, MonoFoldable)
deriving via (GenericArbitrary (Neighbors a)) instance (Arg (Neighbors a) a, Arbitrary a) => Arbitrary (Neighbors a) deriving via (GenericArbitrary (Neighbors a)) instance (Arbitrary a) => Arbitrary (Neighbors a)
type instance Element (Neighbors a) = a type instance Element (Neighbors a) = a
@ -774,7 +774,7 @@ makeFieldsNoPrefix ''Box
-- It seems to be necessary to have an `Arg (V2 a) a` constraint, as a is passed -- It seems to be necessary to have an `Arg (V2 a) a` constraint, as a is passed
-- to V2 internally, in order to make GHC figure out this deriving via correctly. -- to V2 internally, in order to make GHC figure out this deriving via correctly.
deriving via (GenericArbitrary (Box a)) instance (Arg (V2 a) a, Arbitrary a) => Arbitrary (Box a) deriving via (GenericArbitrary (Box a)) instance (Arbitrary a) => Arbitrary (Box a)
bottomRightCorner :: Num a => Box a -> V2 a bottomRightCorner :: Num a => Box a -> V2 a
bottomRightCorner box = bottomRightCorner box =

View file

@ -15,6 +15,7 @@ import Data.Aeson hiding (Key)
import qualified Data.Aeson.KeyMap as KM import qualified Data.Aeson.KeyMap as KM
import Data.Aeson.Types (typeMismatch) import Data.Aeson.Types (typeMismatch)
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
import qualified Graphics.Vty.Input
import Graphics.Vty.Attributes import Graphics.Vty.Attributes
import Brick.Widgets.Edit import Brick.Widgets.Edit
import Data.Text.Zipper.Generic (GenericTextZipper) import Data.Text.Zipper.Generic (GenericTextZipper)
@ -22,7 +23,7 @@ import Brick.Widgets.Core (getName)
import System.Random.Internal (StdGen (..)) import System.Random.Internal (StdGen (..))
import System.Random.SplitMix (SMGen ()) import System.Random.SplitMix (SMGen ())
import Test.QuickCheck import Test.QuickCheck
import Test.QuickCheck.Arbitrary.Generic (Arg ()) -- import Test.QuickCheck.Arbitrary.Generic (Arg ())
import "quickcheck-instances" Test.QuickCheck.Instances () import "quickcheck-instances" Test.QuickCheck.Instances ()
import Text.Megaparsec (errorBundlePretty) import Text.Megaparsec (errorBundlePretty)
import Text.Megaparsec.Pos import Text.Megaparsec.Pos
@ -373,7 +374,7 @@ deriving newtype instance (Arbitrary s, CoArbitrary (m (a, s)))
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
deriving via (GenericArbitrary (V2 a)) instance (Arg (V2 a) a, Arbitrary a) => Arbitrary (V2 a) deriving via (GenericArbitrary (V2 a)) instance (Arbitrary a) => Arbitrary (V2 a)
instance CoArbitrary a => CoArbitrary (V2 a) instance CoArbitrary a => CoArbitrary (V2 a)
instance Function a => Function (V2 a) instance Function a => Function (V2 a)
@ -487,3 +488,8 @@ instance forall a. (FromJSON a, Ord a) => FromJSON (Interval a) where
pure $ val <=..<= val pure $ val <=..<= val
checkLength arr = checkLength arr =
when (length arr /= 2) $ fail "Expected array of length 2" when (length arr /= 2) $ fail "Expected array of length 2"
--------------------------------------------------------------------------------
deriving anyclass instance NFData Graphics.Vty.Input.Key
deriving anyclass instance NFData Graphics.Vty.Input.Modifier