module Chiasma.Data.View where

import qualified Control.Lens as Lens (set)

import Chiasma.Data.Ident (Ident, Identifiable (..))

data View a =
  View {
    forall a. View a -> Ident
ident :: Ident,
    forall a. View a -> Maybe a
id :: Maybe a
  }
  deriving stock (View a -> View a -> Bool
(View a -> View a -> Bool)
-> (View a -> View a -> Bool) -> Eq (View a)
forall a. Eq a => View a -> View a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => View a -> View a -> Bool
== :: View a -> View a -> Bool
$c/= :: forall a. Eq a => View a -> View a -> Bool
/= :: View a -> View a -> Bool
Eq, Int -> View a -> ShowS
[View a] -> ShowS
View a -> String
(Int -> View a -> ShowS)
-> (View a -> String) -> ([View a] -> ShowS) -> Show (View a)
forall a. Show a => Int -> View a -> ShowS
forall a. Show a => [View a] -> ShowS
forall a. Show a => View a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> View a -> ShowS
showsPrec :: Int -> View a -> ShowS
$cshow :: forall a. Show a => View a -> String
show :: View a -> String
$cshowList :: forall a. Show a => [View a] -> ShowS
showList :: [View a] -> ShowS
Show, (forall x. View a -> Rep (View a) x)
-> (forall x. Rep (View a) x -> View a) -> Generic (View a)
forall x. Rep (View a) x -> View a
forall x. View a -> Rep (View a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (View a) x -> View a
forall a x. View a -> Rep (View a) x
$cfrom :: forall a x. View a -> Rep (View a) x
from :: forall x. View a -> Rep (View a) x
$cto :: forall a x. Rep (View a) x -> View a
to :: forall x. Rep (View a) x -> View a
Generic)

instance Identifiable (View a) where
  identify :: View a -> Ident
identify = (.ident)

setViewId :: a -> View a -> View a
setViewId :: forall a. a -> View a -> View a
setViewId =
  ASetter (View a) (View a) (Maybe a) (Maybe a)
-> Maybe a -> View a -> View a
forall s t a b. ASetter s t a b -> b -> s -> t
Lens.set ASetter (View a) (View a) (Maybe a) (Maybe a)
#id (Maybe a -> View a -> View a)
-> (a -> Maybe a) -> a -> View a -> View a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe a
forall a. a -> Maybe a
Just