{-# OPTIONS_GHC -Wno-orphans #-}
module Hum.Orphans where
import qualified Witherable as W
import Brick.Widgets.List
import Control.Lens
instance W.Filterable t => W.Filterable (GenericList n t) where
catMaybes :: GenericList n t (Maybe a) -> GenericList n t a
catMaybes GenericList n t (Maybe a)
l = GenericList n t (Maybe a)
l GenericList n t (Maybe a)
-> (GenericList n t (Maybe a) -> GenericList n t a)
-> GenericList n t a
forall a b. a -> (a -> b) -> b
& (t (Maybe a) -> Identity (t a))
-> GenericList n t (Maybe a) -> Identity (GenericList n t a)
forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
listElementsL ((t (Maybe a) -> Identity (t a))
-> GenericList n t (Maybe a) -> Identity (GenericList n t a))
-> (t (Maybe a) -> t a)
-> GenericList n t (Maybe a)
-> GenericList n t a
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ t (Maybe a) -> t a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
W.catMaybes
instance (Traversable t, W.Filterable t) => W.Witherable (GenericList n t) where