module Potato.Flow.OwlItem where



import Relude

import Potato.Flow.SElts
import Potato.Flow.DebugHelpers

data OwlInfo = OwlInfo {
    OwlInfo -> Text
_owlInfo_name :: Text
  } deriving (REltId -> OwlInfo -> ShowS
[OwlInfo] -> ShowS
OwlInfo -> String
forall a.
(REltId -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OwlInfo] -> ShowS
$cshowList :: [OwlInfo] -> ShowS
show :: OwlInfo -> String
$cshow :: OwlInfo -> String
showsPrec :: REltId -> OwlInfo -> ShowS
$cshowsPrec :: REltId -> OwlInfo -> ShowS
Show, OwlInfo -> OwlInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OwlInfo -> OwlInfo -> Bool
$c/= :: OwlInfo -> OwlInfo -> Bool
== :: OwlInfo -> OwlInfo -> Bool
$c== :: OwlInfo -> OwlInfo -> Bool
Eq, forall x. Rep OwlInfo x -> OwlInfo
forall x. OwlInfo -> Rep OwlInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OwlInfo x -> OwlInfo
$cfrom :: forall x. OwlInfo -> Rep OwlInfo x
Generic)

instance NFData OwlInfo

data OwlSubItem =
  OwlSubItemNone
  | OwlSubItemFolder (Seq REltId)
  | OwlSubItemBox SBox
  | OwlSubItemLine SAutoLine
  | OwlSubItemTextArea STextArea
  deriving (forall x. Rep OwlSubItem x -> OwlSubItem
forall x. OwlSubItem -> Rep OwlSubItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OwlSubItem x -> OwlSubItem
$cfrom :: forall x. OwlSubItem -> Rep OwlSubItem x
Generic, REltId -> OwlSubItem -> ShowS
[OwlSubItem] -> ShowS
OwlSubItem -> String
forall a.
(REltId -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OwlSubItem] -> ShowS
$cshowList :: [OwlSubItem] -> ShowS
show :: OwlSubItem -> String
$cshow :: OwlSubItem -> String
showsPrec :: REltId -> OwlSubItem -> ShowS
$cshowsPrec :: REltId -> OwlSubItem -> ShowS
Show, OwlSubItem -> OwlSubItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OwlSubItem -> OwlSubItem -> Bool
$c/= :: OwlSubItem -> OwlSubItem -> Bool
== :: OwlSubItem -> OwlSubItem -> Bool
$c== :: OwlSubItem -> OwlSubItem -> Bool
Eq)

instance NFData OwlSubItem

owlSubItem_equivalent :: OwlSubItem -> OwlSubItem -> Bool
owlSubItem_equivalent :: OwlSubItem -> OwlSubItem -> Bool
owlSubItem_equivalent (OwlSubItemLine SAutoLine
slinea) (OwlSubItemLine SAutoLine
slineb) = SAutoLine
slinea forall a. Eq a => a -> a -> Bool
== SAutoLine
slineb
owlSubItem_equivalent OwlSubItem
a OwlSubItem
b = OwlSubItem
a forall a. Eq a => a -> a -> Bool
== OwlSubItem
b

data OwlItem = OwlItem {
  OwlItem -> OwlInfo
_owlItem_info :: OwlInfo
  , OwlItem -> OwlSubItem
_owlItem_subItem :: OwlSubItem
} deriving (REltId -> OwlItem -> ShowS
[OwlItem] -> ShowS
OwlItem -> String
forall a.
(REltId -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OwlItem] -> ShowS
$cshowList :: [OwlItem] -> ShowS
show :: OwlItem -> String
$cshow :: OwlItem -> String
showsPrec :: REltId -> OwlItem -> ShowS
$cshowsPrec :: REltId -> OwlItem -> ShowS
Show, OwlItem -> OwlItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OwlItem -> OwlItem -> Bool
$c/= :: OwlItem -> OwlItem -> Bool
== :: OwlItem -> OwlItem -> Bool
$c== :: OwlItem -> OwlItem -> Bool
Eq, forall x. Rep OwlItem x -> OwlItem
forall x. OwlItem -> Rep OwlItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OwlItem x -> OwlItem
$cfrom :: forall x. OwlItem -> Rep OwlItem x
Generic)

instance NFData OwlItem

instance PotatoShow OwlItem where
  potatoShow :: OwlItem -> Text
potatoShow = \case
    OwlItem OwlInfo
oinfo (OwlSubItemFolder Seq REltId
kiddos) -> Text
"folder: " forall a. Semigroup a => a -> a -> a
<> (OwlInfo -> Text
_owlInfo_name OwlInfo
oinfo) forall a. Semigroup a => a -> a -> a
<> Text
": " forall a. Semigroup a => a -> a -> a
<> forall b a. (Show a, IsString b) => a -> b
show Seq REltId
kiddos
    OwlItem OwlInfo
oinfo OwlSubItem
subitem -> Text
"elt: " forall a. Semigroup a => a -> a -> a
<> (OwlInfo -> Text
_owlInfo_name OwlInfo
oinfo) forall a. Semigroup a => a -> a -> a
<> Text
": " forall a. Semigroup a => a -> a -> a
<> case OwlSubItem
subitem of
        OwlSubItem
OwlSubItemNone -> Text
"none"
        OwlSubItemBox SBox
sbox -> forall b a. (Show a, IsString b) => a -> b
show SBox
sbox
        OwlSubItemLine SAutoLine
sline -> forall b a. (Show a, IsString b) => a -> b
show SAutoLine
sline
        OwlSubItemTextArea STextArea
stextarea -> forall b a. (Show a, IsString b) => a -> b
show STextArea
stextarea

class MommyOwl o where
  mommyOwl_kiddos :: o -> Maybe (Seq REltId)
  mommyOwl_hasKiddos :: o -> Bool
  mommyOwl_hasKiddos = forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o. MommyOwl o => o -> Maybe (Seq REltId)
mommyOwl_kiddos

class HasOwlItem o where
  hasOwlItem_owlItem :: o -> OwlItem
  hasOwlItem_name :: o -> Text
  hasOwlItem_name = forall o. HasOwlItem o => o -> Text
hasOwlItem_name forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o. HasOwlItem o => o -> OwlItem
hasOwlItem_owlItem
  hasOwlItem_isFolder :: o -> Bool
  hasOwlItem_isFolder = forall o. HasOwlItem o => o -> Bool
hasOwlItem_isFolder forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o. HasOwlItem o => o -> OwlItem
hasOwlItem_owlItem
  hasOwlItem_attachments :: o -> [Attachment]
  hasOwlItem_attachments = forall o. HasOwlItem o => o -> [Attachment]
hasOwlItem_attachments forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o. HasOwlItem o => o -> OwlItem
hasOwlItem_owlItem
  hasOwlItem_toSElt_hack :: o -> SElt
  hasOwlItem_toSElt_hack = forall o. HasOwlItem o => o -> SElt
hasOwlItem_toSElt_hack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o. HasOwlItem o => o -> OwlItem
hasOwlItem_owlItem
  hasOwlItem_toSEltLabel_hack :: o -> SEltLabel
  hasOwlItem_toSEltLabel_hack = forall o. HasOwlItem o => o -> SEltLabel
hasOwlItem_toSEltLabel_hack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o. HasOwlItem o => o -> OwlItem
hasOwlItem_owlItem
  hasOwlItem_toOwlSubItem :: o -> OwlSubItem
  hasOwlItem_toOwlSubItem = OwlItem -> OwlSubItem
_owlItem_subItem forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o. HasOwlItem o => o -> OwlItem
hasOwlItem_owlItem


owlItem_name :: OwlItem -> Text
owlItem_name :: OwlItem -> Text
owlItem_name = OwlInfo -> Text
_owlInfo_name forall b c a. (b -> c) -> (a -> b) -> a -> c
. OwlItem -> OwlInfo
_owlItem_info

owlItem_setName :: OwlItem -> Text -> OwlItem
owlItem_setName :: OwlItem -> Text -> OwlItem
owlItem_setName (OwlItem OwlInfo
oi OwlSubItem
x) Text
n = OwlInfo -> OwlSubItem -> OwlItem
OwlItem (OwlInfo
oi { _owlInfo_name :: Text
_owlInfo_name = Text
n}) OwlSubItem
x

instance MommyOwl OwlItem where
  mommyOwl_kiddos :: OwlItem -> Maybe (Seq REltId)
mommyOwl_kiddos OwlItem
o = case OwlItem -> OwlSubItem
_owlItem_subItem OwlItem
o of
    OwlSubItemFolder Seq REltId
kiddos -> forall a. a -> Maybe a
Just Seq REltId
kiddos
    OwlSubItem
_ -> forall a. Maybe a
Nothing



owlSubItem_to_sElt_hack :: OwlSubItem -> SElt
owlSubItem_to_sElt_hack :: OwlSubItem -> SElt
owlSubItem_to_sElt_hack = \case
  OwlSubItemFolder Seq REltId
_ -> SElt
SEltFolderStart
  OwlSubItemBox SBox
sbox -> SBox -> SElt
SEltBox SBox
sbox
  OwlSubItemLine SAutoLine
sline -> SAutoLine -> SElt
SEltLine SAutoLine
sline
  OwlSubItemTextArea STextArea
stextarea -> STextArea -> SElt
SEltTextArea STextArea
stextarea
  OwlSubItem
OwlSubItemNone -> SElt
SEltNone

instance HasOwlItem OwlItem where
  hasOwlItem_owlItem :: OwlItem -> OwlItem
hasOwlItem_owlItem = forall a. a -> a
id
  hasOwlItem_name :: OwlItem -> Text
hasOwlItem_name = OwlItem -> Text
owlItem_name
  hasOwlItem_isFolder :: OwlItem -> Bool
hasOwlItem_isFolder OwlItem
o = case OwlItem -> OwlSubItem
_owlItem_subItem OwlItem
o of
    OwlSubItemFolder Seq REltId
_ -> Bool
True
    OwlSubItem
_ -> Bool
False
  hasOwlItem_attachments :: OwlItem -> [Attachment]
hasOwlItem_attachments OwlItem
o = case OwlItem -> OwlSubItem
_owlItem_subItem OwlItem
o of
    OwlSubItemLine SAutoLine
sline -> forall a. [Maybe a] -> [a]
catMaybes [SAutoLine -> Maybe Attachment
_sAutoLine_attachStart SAutoLine
sline, SAutoLine -> Maybe Attachment
_sAutoLine_attachEnd SAutoLine
sline]
    OwlSubItem
_ -> []
  hasOwlItem_toSElt_hack :: OwlItem -> SElt
hasOwlItem_toSElt_hack = OwlSubItem -> SElt
owlSubItem_to_sElt_hack forall b c a. (b -> c) -> (a -> b) -> a -> c
. OwlItem -> OwlSubItem
_owlItem_subItem
  hasOwlItem_toSEltLabel_hack :: OwlItem -> SEltLabel
hasOwlItem_toSEltLabel_hack OwlItem
o = Text -> SElt -> SEltLabel
SEltLabel (forall o. HasOwlItem o => o -> Text
hasOwlItem_name OwlItem
o) (forall o. HasOwlItem o => o -> SElt
hasOwlItem_toSElt_hack OwlItem
o)

-- DELETE use hasOwlItem variant instead
owlItem_toSElt_hack :: OwlItem -> SElt
owlItem_toSElt_hack :: OwlItem -> SElt
owlItem_toSElt_hack = forall o. HasOwlItem o => o -> SElt
hasOwlItem_toSElt_hack

sElt_to_owlSubItem :: SElt -> OwlSubItem
sElt_to_owlSubItem :: SElt -> OwlSubItem
sElt_to_owlSubItem SElt
s = case SElt
s of
  SEltBox SBox
x -> SBox -> OwlSubItem
OwlSubItemBox SBox
x
  SEltLine SAutoLine
x -> SAutoLine -> OwlSubItem
OwlSubItemLine SAutoLine
x
  SEltTextArea STextArea
x -> STextArea -> OwlSubItem
OwlSubItemTextArea STextArea
x
  SElt
SEltNone -> OwlSubItem
OwlSubItemNone
  SElt
_ -> forall a t. (HasCallStack, IsText t) => t -> a
error forall a b. (a -> b) -> a -> b
$ Text
"cannot convert " forall a. Semigroup a => a -> a -> a
<> forall b a. (Show a, IsString b) => a -> b
show SElt
s