Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data Pane = Pane {}
- newtype Layout = Layout {}
- data View a = View {}
- type PaneView = View Pane
- type LayoutView = View Layout
- prettyView :: Doc a -> Ident -> ViewState -> ViewGeometry -> Doc a
- consPane :: Ident -> PaneView
- consLayoutAs :: Axis -> Ident -> LayoutView
- consLayout :: Ident -> LayoutView
- consLayoutVertical :: Ident -> LayoutView
- data Tree l p = Tree {}
- data TreeSub l p
- type ViewTree = Tree LayoutView PaneView
- type ViewTreeSub = TreeSub LayoutView PaneView
- treeTraversal :: Traversal' (Tree l p) (Tree l p)
- treeByIdentTraversal :: Identifiable l => Ident -> Traversal' (Tree l p) (Tree l p)
- treesIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Fold (Tree l p) (Tree l p)
- treeByIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Tree l p -> Maybe (Tree l p)
- treesByIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Tree l p -> [Tree l p]
- trees :: (Data l, Data p) => Fold (Tree l p) (Tree l p)
- leaves :: (Data l, Data p) => Fold (Tree l p) p
- nodes :: (Data l, Data p) => Fold (Tree l p) l
Documentation
Instances
Data Pane Source # | |
Defined in Chiasma.Ui.Data.View gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pane -> c Pane # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pane # dataTypeOf :: Pane -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pane) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pane) # gmapT :: (forall b. Data b => b -> b) -> Pane -> Pane # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pane -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pane -> r # gmapQ :: (forall d. Data d => d -> u) -> Pane -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pane -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pane -> m Pane # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pane -> m Pane # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pane -> m Pane # | |
Generic Pane Source # | |
Show Pane Source # | |
Default Pane Source # | |
Defined in Chiasma.Ui.Data.View | |
Eq Pane Source # | |
Pretty Pane Source # | |
Defined in Chiasma.Ui.Data.View | |
Pretty (View Pane) Source # | |
type Rep Pane Source # | |
Defined in Chiasma.Ui.Data.View type Rep Pane = D1 ('MetaData "Pane" "Chiasma.Ui.Data.View" "chiasma-0.10.1.0-Enq17vjYLUVFgBfc7msm0x" 'False) (C1 ('MetaCons "Pane" 'PrefixI 'True) (S1 ('MetaSel ('Just "open") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "pin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "cwd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) |
Instances
Data Layout Source # | |
Defined in Chiasma.Ui.Data.View gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Layout -> c Layout # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Layout # toConstr :: Layout -> Constr # dataTypeOf :: Layout -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Layout) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Layout) # gmapT :: (forall b. Data b => b -> b) -> Layout -> Layout # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Layout -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Layout -> r # gmapQ :: (forall d. Data d => d -> u) -> Layout -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Layout -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Layout -> m Layout # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Layout -> m Layout # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Layout -> m Layout # | |
Generic Layout Source # | |
Show Layout Source # | |
Default Layout Source # | |
Defined in Chiasma.Ui.Data.View | |
Eq Layout Source # | |
Pretty Layout Source # | |
Defined in Chiasma.Ui.Data.View | |
Pretty (View Layout) Source # | |
type Rep Layout Source # | |
Defined in Chiasma.Ui.Data.View |
Instances
Data a => Data (View a) Source # | |
Defined in Chiasma.Ui.Data.View gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> View a -> c (View a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (View a) # toConstr :: View a -> Constr # dataTypeOf :: View a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (View a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (View a)) # gmapT :: (forall b. Data b => b -> b) -> View a -> View a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> View a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> View a -> r # gmapQ :: (forall d. Data d => d -> u) -> View a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> View a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> View a -> m (View a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> View a -> m (View a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> View a -> m (View a) # | |
Generic (View a) Source # | |
Show a => Show (View a) Source # | |
Identifiable (View a) Source # | |
Default a => Default (View a) Source # | |
Defined in Chiasma.Ui.Data.View | |
Eq a => Eq (View a) Source # | |
Pretty (View Layout) Source # | |
Pretty (View Pane) Source # | |
type Rep (View a) Source # | |
Defined in Chiasma.Ui.Data.View type Rep (View a) = D1 ('MetaData "View" "Chiasma.Ui.Data.View" "chiasma-0.10.1.0-Enq17vjYLUVFgBfc7msm0x" 'False) (C1 ('MetaCons "View" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ident") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Just "state") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ViewState)) :*: (S1 ('MetaSel ('Just "geometry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ViewGeometry) :*: S1 ('MetaSel ('Just "extra") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
type LayoutView = View Layout Source #
prettyView :: Doc a -> Ident -> ViewState -> ViewGeometry -> Doc a Source #
consLayoutAs :: Axis -> Ident -> LayoutView Source #
consLayout :: Ident -> LayoutView Source #
consLayoutVertical :: Ident -> LayoutView Source #
Instances
Bifoldable Tree Source # | |
Bifunctor Tree Source # | |
(Data p, Data l) => Data (Tree l p) Source # | |
Defined in Chiasma.Ui.Data.View gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree l p -> c (Tree l p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree l p) # toConstr :: Tree l p -> Constr # dataTypeOf :: Tree l p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree l p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree l p)) # gmapT :: (forall b. Data b => b -> b) -> Tree l p -> Tree l p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree l p -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree l p -> r # gmapQ :: (forall d. Data d => d -> u) -> Tree l p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree l p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree l p -> m (Tree l p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree l p -> m (Tree l p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree l p -> m (Tree l p) # | |
Generic (Tree l p) Source # | |
(Show l, Show p) => Show (Tree l p) Source # | |
Identifiable l => Identifiable (Tree l p) Source # | |
(Eq l, Eq p) => Eq (Tree l p) Source # | |
Identifiable l => Ixed (Tree l p) Source # | |
Defined in Chiasma.Ui.Data.View | |
(Data l, Data p) => Plated (Tree l p) Source # | |
Defined in Chiasma.Ui.Data.View plate :: Traversal' (Tree l p) (Tree l p) # | |
(Pretty l, Pretty p) => Pretty (Tree l p) Source # | |
Defined in Chiasma.Ui.Data.View | |
type Rep (Tree l p) Source # | |
Defined in Chiasma.Ui.Data.View type Rep (Tree l p) = D1 ('MetaData "Tree" "Chiasma.Ui.Data.View" "chiasma-0.10.1.0-Enq17vjYLUVFgBfc7msm0x" 'False) (C1 ('MetaCons "Tree" 'PrefixI 'True) (S1 ('MetaSel ('Just "treeData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Just "treeSubs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TreeSub l p]))) | |
type Index (Tree _1 _2) Source # | |
Defined in Chiasma.Ui.Data.View | |
type IxValue (Tree l p) Source # | |
Defined in Chiasma.Ui.Data.View |
Instances
Bifoldable TreeSub Source # | |
Bifunctor TreeSub Source # | |
(Data l, Data p) => Data (TreeSub l p) Source # | |
Defined in Chiasma.Ui.Data.View gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TreeSub l p -> c (TreeSub l p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TreeSub l p) # toConstr :: TreeSub l p -> Constr # dataTypeOf :: TreeSub l p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TreeSub l p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TreeSub l p)) # gmapT :: (forall b. Data b => b -> b) -> TreeSub l p -> TreeSub l p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TreeSub l p -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TreeSub l p -> r # gmapQ :: (forall d. Data d => d -> u) -> TreeSub l p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TreeSub l p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TreeSub l p -> m (TreeSub l p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TreeSub l p -> m (TreeSub l p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TreeSub l p -> m (TreeSub l p) # | |
Generic (TreeSub l p) Source # | |
(Show l, Show p) => Show (TreeSub l p) Source # | |
(Eq l, Eq p) => Eq (TreeSub l p) Source # | |
(Pretty l, Pretty p) => Pretty (TreeSub l p) Source # | |
Defined in Chiasma.Ui.Data.View | |
type Rep (TreeSub l p) Source # | |
Defined in Chiasma.Ui.Data.View type Rep (TreeSub l p) = D1 ('MetaData "TreeSub" "Chiasma.Ui.Data.View" "chiasma-0.10.1.0-Enq17vjYLUVFgBfc7msm0x" 'False) (C1 ('MetaCons "TreeNode" 'PrefixI 'True) (S1 ('MetaSel ('Just "subTree") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Tree l p))) :+: C1 ('MetaCons "TreeLeaf" 'PrefixI 'True) (S1 ('MetaSel ('Just "leafData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 p))) |
type ViewTreeSub = TreeSub LayoutView PaneView Source #
treeTraversal :: Traversal' (Tree l p) (Tree l p) Source #
treeByIdentTraversal :: Identifiable l => Ident -> Traversal' (Tree l p) (Tree l p) Source #
treesIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Fold (Tree l p) (Tree l p) Source #
treeByIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Tree l p -> Maybe (Tree l p) Source #
treesByIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Tree l p -> [Tree l p] Source #