Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- errorMsg_owlTree_lookupFail :: OwlTree -> REltId -> Text
- errorMsg_owlMapping_lookupFail :: OwlMapping -> REltId -> Text
- type OwlMapping = REltIdMap (OwlItemMeta, OwlItem)
- owlItem_updateAttachments :: Bool -> REltIdMap REltId -> OwlItem -> OwlItem
- type SiblingPosition = Int
- locateLeftSiblingIdFromSiblingPosition :: OwlMapping -> Seq REltId -> SiblingPosition -> Maybe REltId
- isDescendentOf :: HasCallStack => OwlMapping -> REltId -> REltId -> Bool
- data OwlItemMeta = OwlItemMeta {}
- data OwlSpot = OwlSpot {}
- topSpot :: OwlSpot
- data SuperOwl = SuperOwl {}
- type SuperOwlChanges = REltIdMap (Maybe SuperOwl)
- attachmentMap_addSuperOwls' :: Foldable f => (Attachment -> Bool) -> f SuperOwl -> AttachmentMap -> AttachmentMap
- attachmentMap_addSuperOwls :: Foldable f => f SuperOwl -> AttachmentMap -> AttachmentMap
- updateAttachmentMapFromSuperOwlChanges :: SuperOwlChanges -> AttachmentMap -> AttachmentMap
- getChangesFromAttachmentMap :: OwlTree -> AttachmentMap -> SuperOwlChanges -> SuperOwlChanges
- superOwl_id :: Functor f => (REltId -> f REltId) -> SuperOwl -> f SuperOwl
- superOwl_isTopOwl :: SuperOwl -> Bool
- superOwl_isTopOwlSurely :: SuperOwl -> Bool
- noOwl :: REltId
- superOwl_parentId :: SuperOwl -> REltId
- superOwl_depth :: SuperOwl -> Int
- superOwl_owlSubItem :: SuperOwl -> OwlSubItem
- owlTree_superOwlNthParentId :: OwlTree -> SuperOwl -> Int -> REltId
- newtype OwlParliament = OwlParliament {}
- newtype SuperOwlParliament = SuperOwlParliament {}
- class IsParliament a where
- isParliament_disjointUnion :: a -> a -> a
- isParliament_null :: a -> Bool
- isParliament_empty :: a
- isParliament_length :: a -> Int
- disjointUnion :: Eq a => [a] -> [a] -> [a]
- owlParliament_toSuperOwlParliament :: OwlTree -> OwlParliament -> SuperOwlParliament
- superOwlParliament_toOwlParliament :: SuperOwlParliament -> OwlParliament
- partitionN :: (a -> Int) -> Seq a -> IntMap (Seq a)
- makeSortedSuperOwlParliament :: OwlTree -> Seq SuperOwl -> SuperOwlParliament
- superOwlParliament_disjointUnionAndCorrect :: OwlTree -> SuperOwlParliament -> SuperOwlParliament -> SuperOwlParliament
- superOwlParliament_isValid :: OwlTree -> SuperOwlParliament -> Bool
- superOwlParliament_toSEltTree :: OwlTree -> SuperOwlParliament -> SEltTree
- newtype CanvasSelection = CanvasSelection {}
- superOwlParliament_convertToCanvasSelection :: OwlTree -> (SuperOwl -> Bool) -> SuperOwlParliament -> CanvasSelection
- superOwlParliament_convertToSeqWithChildren :: OwlTree -> SuperOwlParliament -> Seq SuperOwl
- owlParliament_convertToMiniOwltree :: OwlTree -> OwlParliament -> MiniOwlTree
- type OwlParliamentSet = IntSet
- superOwlParliament_toOwlParliamentSet :: SuperOwlParliament -> OwlParliamentSet
- owlParliamentSet_member :: REltId -> OwlParliamentSet -> Bool
- owlParliamentSet_descendent :: OwlTree -> REltId -> OwlParliamentSet -> Bool
- owlParliamentSet_findParents :: OwlTree -> OwlParliamentSet -> OwlParliamentSet
- data OwlTree = OwlTree {}
- type MiniOwlTree = OwlTree
- owlTree_equivalent :: OwlTree -> OwlTree -> Bool
- owlTree_validate :: OwlTree -> (Bool, Text)
- owlTree_maxId :: OwlTree -> REltId
- internal_owlTree_reorgKiddos :: OwlTree -> REltId -> OwlTree
- emptyOwlTree :: OwlTree
- owlTree_exists :: OwlTree -> REltId -> Bool
- owlTree_findSuperOwl :: OwlTree -> REltId -> Maybe SuperOwl
- owlTree_mustFindSuperOwl :: HasCallStack => OwlTree -> REltId -> SuperOwl
- owlTree_findKiddos :: OwlTree -> REltId -> Maybe (Seq REltId)
- owlTree_findSuperOwlAtOwlSpot :: OwlTree -> OwlSpot -> Maybe SuperOwl
- owlTree_goRightFromOwlSpot :: OwlTree -> OwlSpot -> Maybe OwlSpot
- owlTree_owlItemMeta_toOwlSpot :: OwlTree -> OwlItemMeta -> OwlSpot
- owlTree_rEltId_toOwlSpot :: HasCallStack => OwlTree -> REltId -> OwlSpot
- owlTree_rEltId_toFlattenedIndex_debug :: OwlTree -> REltId -> Int
- owlTree_makeAttachmentMap :: OwlTree -> AttachmentMap
- owlTree_hasDanglingAttachments :: OwlTree -> Bool
- owlTree_topSuperOwls :: OwlTree -> Seq SuperOwl
- owlTree_foldAt' :: (a -> SuperOwl -> a) -> a -> OwlTree -> SuperOwl -> a
- owlTree_foldAt :: (a -> SuperOwl -> a) -> a -> OwlTree -> REltId -> a
- owlTree_foldChildrenAt' :: (a -> SuperOwl -> a) -> a -> OwlTree -> SuperOwl -> a
- owlTree_foldChildrenAt :: (a -> SuperOwl -> a) -> a -> OwlTree -> REltId -> a
- owlTree_fold :: (a -> SuperOwl -> a) -> a -> OwlTree -> a
- owlTree_owlCount :: OwlTree -> Int
- owliterateat :: OwlTree -> REltId -> Seq SuperOwl
- owliteratechildrenat :: OwlTree -> REltId -> Seq SuperOwl
- owliterateall :: OwlTree -> Seq SuperOwl
- class HasOwlTree o where
- hasOwlTree_owlTree :: o -> OwlTree
- hasOwlTree_exists :: o -> REltId -> Bool
- hasOwlTree_findSuperOwl :: o -> REltId -> Maybe SuperOwl
- hasOwlTree_mustFindSuperOwl :: HasCallStack => o -> REltId -> SuperOwl
- hasOwlTree_test_findFirstSuperOwlByName :: o -> Text -> Maybe SuperOwl
- hasOwlTree_test_mustFindFirstSuperOwlByName :: o -> Text -> SuperOwl
- owlTree_toSuperOwlParliament :: OwlTree -> SuperOwlParliament
- owlTree_removeREltId :: REltId -> OwlTree -> OwlTree
- owlTree_removeSuperOwl :: SuperOwl -> OwlTree -> OwlTree
- owlTree_moveOwlParliament :: OwlParliament -> OwlSpot -> OwlTree -> (OwlTree, [SuperOwl])
- owlTree_addSEltTree :: OwlSpot -> SEltTree -> OwlTree -> (OwlTree, [SuperOwl])
- owlTree_reindex :: Int -> OwlTree -> OwlTree
- owlTree_addMiniOwlTree :: OwlSpot -> MiniOwlTree -> OwlTree -> (OwlTree, [SuperOwl])
- internal_owlTree_addOwlItem :: OwlSpot -> REltId -> OwlItem -> OwlTree -> (OwlTree, SuperOwl)
- owlTree_addOwlItem :: OwlSpot -> REltId -> OwlItem -> OwlTree -> (OwlTree, SuperOwl)
- owlTree_addOwlItemList :: [(REltId, OwlSpot, OwlItem)] -> OwlTree -> (OwlTree, [SuperOwl])
- owlTree_superOwl_comparePosition :: OwlTree -> SuperOwl -> SuperOwl -> Ordering
- internal_addUntilFolderEndRecursive :: REltIdMap SEltLabel -> Seq REltId -> Int -> REltId -> Int -> REltIdMap (OwlItemMeta, OwlItem) -> Seq REltId -> (Int, REltIdMap (OwlItemMeta, OwlItem), Seq REltId)
- owlTree_fromSEltTree :: SEltTree -> OwlTree
- owlTree_fromOldState :: REltIdMap SEltLabel -> Seq REltId -> OwlTree
- owlTree_toSEltTree :: OwlTree -> SEltTree
- superOwl_toSElt_hack :: SuperOwl -> SElt
- superOwl_toSEltLabel_hack :: SuperOwl -> SEltLabel
Documentation
type OwlMapping = REltIdMap (OwlItemMeta, OwlItem) Source #
owlItem_updateAttachments :: Bool -> REltIdMap REltId -> OwlItem -> OwlItem Source #
update attachments based on remap
type SiblingPosition = Int Source #
locateLeftSiblingIdFromSiblingPosition :: OwlMapping -> Seq REltId -> SiblingPosition -> Maybe REltId Source #
isDescendentOf :: HasCallStack => OwlMapping -> REltId -> REltId -> Bool Source #
data OwlItemMeta Source #
Instances
Instances
Generic OwlSpot Source # | |
Show OwlSpot Source # | |
NFData OwlSpot Source # | |
Defined in Potato.Flow.Owl | |
type Rep OwlSpot Source # | |
Defined in Potato.Flow.Owl type Rep OwlSpot = D1 ('MetaData "OwlSpot" "Potato.Flow.Owl" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "OwlSpot" 'PrefixI 'True) (S1 ('MetaSel ('Just "_owlSpot_parent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 REltId) :*: S1 ('MetaSel ('Just "_owlSpot_leftSibling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe REltId)))) |
Instances
attachmentMap_addSuperOwls' :: Foldable f => (Attachment -> Bool) -> f SuperOwl -> AttachmentMap -> AttachmentMap Source #
attachmentMap_addSuperOwls :: Foldable f => f SuperOwl -> AttachmentMap -> AttachmentMap Source #
updateAttachmentMapFromSuperOwlChanges :: SuperOwlChanges -> AttachmentMap -> AttachmentMap Source #
update AttachmentMap from SuperOwlChanges (call on SuperOwlChanges produced by updateOwlPFWorkspace)
getChangesFromAttachmentMap :: OwlTree -> AttachmentMap -> SuperOwlChanges -> SuperOwlChanges Source #
update SuperOwlChanges to include stuff attached to stuff that changed (call before rendering)
superOwl_isTopOwl :: SuperOwl -> Bool Source #
superOwl_isTopOwlSurely :: SuperOwl -> Bool Source #
same as superOwl_isTopOwl except checks all conditions, intended to be used in asserts
superOwl_parentId :: SuperOwl -> REltId Source #
superOwl_depth :: SuperOwl -> Int Source #
newtype OwlParliament Source #
Instances
Generic OwlParliament Source # | |
Defined in Potato.Flow.Owl type Rep OwlParliament :: Type -> Type # from :: OwlParliament -> Rep OwlParliament x # to :: Rep OwlParliament x -> OwlParliament # | |
Show OwlParliament Source # | |
Defined in Potato.Flow.Owl showsPrec :: Int -> OwlParliament -> ShowS # show :: OwlParliament -> String # showList :: [OwlParliament] -> ShowS # | |
NFData OwlParliament Source # | |
Defined in Potato.Flow.Owl rnf :: OwlParliament -> () # | |
IsParliament OwlParliament Source # | |
Defined in Potato.Flow.Owl | |
type Rep OwlParliament Source # | |
Defined in Potato.Flow.Owl type Rep OwlParliament = D1 ('MetaData "OwlParliament" "Potato.Flow.Owl" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'True) (C1 ('MetaCons "OwlParliament" 'PrefixI 'True) (S1 ('MetaSel ('Just "unOwlParliament") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq REltId)))) |
newtype SuperOwlParliament Source #
Instances
class IsParliament a where Source #
isParliament_disjointUnion :: a -> a -> a Source #
isParliament_null :: a -> Bool Source #
isParliament_empty :: a Source #
isParliament_length :: a -> Int Source #
Instances
disjointUnion :: Eq a => [a] -> [a] -> [a] Source #
partitionN :: (a -> Int) -> Seq a -> IntMap (Seq a) Source #
partition a list into groups based on int pairings
superOwlParliament_disjointUnionAndCorrect :: OwlTree -> SuperOwlParliament -> SuperOwlParliament -> SuperOwlParliament Source #
newtype CanvasSelection Source #
Instances
Show CanvasSelection Source # | |
Defined in Potato.Flow.Owl showsPrec :: Int -> CanvasSelection -> ShowS # show :: CanvasSelection -> String # showList :: [CanvasSelection] -> ShowS # | |
Eq CanvasSelection Source # | |
Defined in Potato.Flow.Owl (==) :: CanvasSelection -> CanvasSelection -> Bool # (/=) :: CanvasSelection -> CanvasSelection -> Bool # |
superOwlParliament_convertToCanvasSelection :: OwlTree -> (SuperOwl -> Bool) -> SuperOwlParliament -> CanvasSelection Source #
convert SuperOwlParliament to CanvasSelection (includes children and no folders) does not omits locked/hidden elts since Owl should not depend on Layers, you should do this using filterfn I guess??
superOwlParliament_convertToSeqWithChildren :: OwlTree -> SuperOwlParliament -> Seq SuperOwl Source #
owlParliament_convertToMiniOwltree :: OwlTree -> OwlParliament -> MiniOwlTree Source #
intended for use in OwlWorkspace to create PFCmd generate MiniOwlTree will be reindexed so as not to conflict with OwlTree relies on OwlParliament being correctly ordered
type OwlParliamentSet = IntSet Source #
owlParliamentSet_member :: REltId -> OwlParliamentSet -> Bool Source #
owlParliamentSet_descendent :: OwlTree -> REltId -> OwlParliamentSet -> Bool Source #
returns true if rid is a contained in the OwlParliamentSet or is a descendent of sset
Instances
type MiniOwlTree = OwlTree Source #
owlTree_equivalent :: OwlTree -> OwlTree -> Bool Source #
check if two OwlTree's are equivalent checks if structure is the same, REltIds can differ
owlTree_maxId :: OwlTree -> REltId Source #
owlTree_mustFindSuperOwl :: HasCallStack => OwlTree -> REltId -> SuperOwl Source #
owlTree_owlItemMeta_toOwlSpot :: OwlTree -> OwlItemMeta -> OwlSpot Source #
throws if OwlItemMeta is invalid in OwlTree TODO make naming consistent in this file...
owlTree_rEltId_toOwlSpot :: HasCallStack => OwlTree -> REltId -> OwlSpot Source #
throws if REltId is invalid in OwlTree
owlTree_rEltId_toFlattenedIndex_debug :: OwlTree -> REltId -> Int Source #
super inefficient implementation for testing only
owlTree_makeAttachmentMap :: OwlTree -> AttachmentMap Source #
NOTE this will return an AttachmentMap containing targets that have since been deleted
owlTree_hasDanglingAttachments :: OwlTree -> Bool Source #
return fales if any attachments are dangling (i.e. they are attached to a target that does not exist in the tree)
owlTree_foldAt :: (a -> SuperOwl -> a) -> a -> OwlTree -> REltId -> a Source #
fold over an element in the tree and all its children
owlTree_foldChildrenAt :: (a -> SuperOwl -> a) -> a -> OwlTree -> REltId -> a Source #
same as owlTree_foldAt but excludes parent
owlTree_fold :: (a -> SuperOwl -> a) -> a -> OwlTree -> a Source #
owlTree_owlCount :: OwlTree -> Int Source #
owliteratechildrenat :: OwlTree -> REltId -> Seq SuperOwl Source #
iterates an element's children (excluding self)
class HasOwlTree o where Source #
hasOwlTree_owlTree :: o -> OwlTree Source #
hasOwlTree_exists :: o -> REltId -> Bool Source #
hasOwlTree_findSuperOwl :: o -> REltId -> Maybe SuperOwl Source #
hasOwlTree_mustFindSuperOwl :: HasCallStack => o -> REltId -> SuperOwl Source #
hasOwlTree_test_findFirstSuperOwlByName :: o -> Text -> Maybe SuperOwl Source #
hasOwlTree_test_mustFindFirstSuperOwlByName :: o -> Text -> SuperOwl Source #
Instances
owlTree_toSuperOwlParliament :: OwlTree -> SuperOwlParliament Source #
select everything in the OwlTree
owlTree_moveOwlParliament :: OwlParliament -> OwlSpot -> OwlTree -> (OwlTree, [SuperOwl]) Source #
owlTree_addSEltTree :: OwlSpot -> SEltTree -> OwlTree -> (OwlTree, [SuperOwl]) Source #
assumes SEltTree REltIds do not collide with OwlTree
owlTree_reindex :: Int -> OwlTree -> OwlTree Source #
actually this might be OK... or at least we want to check against tree we are attaching to such that if we copy paste something that was attached it keeps those attachments (or maybe we don't!)
owlTree_addMiniOwlTree :: OwlSpot -> MiniOwlTree -> OwlTree -> (OwlTree, [SuperOwl]) Source #
internal_owlTree_addOwlItem :: OwlSpot -> REltId -> OwlItem -> OwlTree -> (OwlTree, SuperOwl) Source #
internal_addUntilFolderEndRecursive Source #
:: REltIdMap SEltLabel | |
-> Seq REltId | |
-> Int | current layer position we are adding |
-> REltId | parent |
-> Int | depth |
-> REltIdMap (OwlItemMeta, OwlItem) | accumulated directory |
-> Seq REltId | accumulated children at current level |
-> (Int, REltIdMap (OwlItemMeta, OwlItem), Seq REltId) | (next lp, accumulated directory, children of current level) |
use to convert old style layers to Owl
owlTree_toSEltTree :: OwlTree -> SEltTree Source #
superOwl_toSElt_hack :: SuperOwl -> SElt Source #