{-# LANGUAGE RecordWildCards #-}
module Potato.Flow.Methods.Types where
import Relude
import Potato.Flow.Math
import Potato.Flow.Owl
import Potato.Flow.SElts
import qualified Data.Text as T
type SEltDrawerRenderFn = forall a. (HasOwlTree a) => a -> XY -> Maybe PChar
type SEltDrawerBoxFn = forall a. (HasOwlTree a) => a -> LBox
makePotatoRenderer :: LBox -> SEltDrawerRenderFn
makePotatoRenderer :: LBox -> SEltDrawerRenderFn
makePotatoRenderer LBox
lbox a
_ XY
pt = if LBox -> XY -> Bool
does_lBox_contains_XY LBox
lbox XY
pt
then forall a. a -> Maybe a
Just Char
'#'
else forall a. Maybe a
Nothing
data SEltDrawer = SEltDrawer {
SEltDrawer -> SEltDrawerBoxFn
_sEltDrawer_box :: SEltDrawerBoxFn
, SEltDrawer -> SEltDrawerRenderFn
_sEltDrawer_renderFn :: SEltDrawerRenderFn
, SEltDrawer -> Int
_sEltDrawer_maxCharWidth :: Int
}
nilDrawer :: SEltDrawer
nilDrawer :: SEltDrawer
nilDrawer = SEltDrawer {
_sEltDrawer_box :: SEltDrawerBoxFn
_sEltDrawer_box = forall a b. a -> b -> a
const LBox
nilLBox
, _sEltDrawer_renderFn :: SEltDrawerRenderFn
_sEltDrawer_renderFn = \a
_ XY
_ -> forall a. Maybe a
Nothing
, _sEltDrawer_maxCharWidth :: Int
_sEltDrawer_maxCharWidth = Int
1
}
sEltDrawer_renderToLines :: (HasOwlTree a) => SEltDrawer -> a -> [Text]
sEltDrawer_renderToLines :: forall a. HasOwlTree a => SEltDrawer -> a -> [Text]
sEltDrawer_renderToLines SEltDrawer {Int
SEltDrawerBoxFn
SEltDrawerRenderFn
_sEltDrawer_maxCharWidth :: Int
_sEltDrawer_renderFn :: SEltDrawerRenderFn
_sEltDrawer_box :: SEltDrawerBoxFn
_sEltDrawer_maxCharWidth :: SEltDrawer -> Int
_sEltDrawer_renderFn :: SEltDrawer -> SEltDrawerRenderFn
_sEltDrawer_box :: SEltDrawer -> SEltDrawerBoxFn
..} a
ot = [Text]
r where
LBox (V2 Int
sx Int
sy) (V2 Int
w Int
h) = SEltDrawerBoxFn
_sEltDrawer_box a
ot
pts :: [[(Int, Int)]]
pts = [[(Int
x,Int
y) | Int
x <- [Int
0..Int
wforall a. Num a => a -> a -> a
-Int
1]]| Int
y <- [Int
0..Int
hforall a. Num a => a -> a -> a
-Int
1]]
r' :: [[Char]]
r' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int
x,Int
y) -> forall a. a -> Maybe a -> a
fromMaybe Char
' ' (SEltDrawerRenderFn
_sEltDrawer_renderFn a
ot (forall a. a -> a -> V2 a
V2 (Int
sxforall a. Num a => a -> a -> a
+Int
x) (Int
syforall a. Num a => a -> a -> a
+Int
y))))) [[(Int, Int)]]
pts
r :: [Text]
r = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Text
T.pack [[Char]]
r'
getSEltBox_naive :: SElt -> Maybe LBox
getSEltBox_naive :: SElt -> Maybe LBox
getSEltBox_naive SElt
selt = case SElt
selt of
SElt
SEltNone -> forall a. Maybe a
Nothing
SElt
SEltFolderStart -> forall a. Maybe a
Nothing
SElt
SEltFolderEnd -> forall a. Maybe a
Nothing
SEltBox SBox
x -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ LBox -> LBox
canonicalLBox_from_lBox_ forall a b. (a -> b) -> a -> b
$ SBox -> LBox
_sBox_box SBox
x
SEltLine SAutoLine
x -> forall a. a -> Maybe a
Just LBox
r where
midpoints :: [XY]
midpoints = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(SAutoLineConstraintFixed XY
c) -> XY
c) (SAutoLine -> [SAutoLineConstraint]
_sAutoLine_midpoints SAutoLine
x)
r :: LBox
r = [XY] -> LBox
make_lBox_from_XYlist forall a b. (a -> b) -> a -> b
$ (SAutoLine -> XY
_sAutoLine_start SAutoLine
x) forall a. a -> [a] -> [a]
: (SAutoLine -> XY
_sAutoLine_end SAutoLine
x) forall a. a -> [a] -> [a]
: (SAutoLine -> XY
_sAutoLine_start SAutoLine
x forall a. Num a => a -> a -> a
+ XY
1) forall a. a -> [a] -> [a]
: (SAutoLine -> XY
_sAutoLine_end SAutoLine
x forall a. Num a => a -> a -> a
+ XY
1) forall a. a -> [a] -> [a]
: [XY]
midpoints
SEltTextArea STextArea
x -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ LBox -> LBox
canonicalLBox_from_lBox_ forall a b. (a -> b) -> a -> b
$ STextArea -> LBox
_sTextArea_box STextArea
x
getSEltLabelBox :: SEltLabel -> Maybe LBox
getSEltLabelBox :: SEltLabel -> Maybe LBox
getSEltLabelBox (SEltLabel Text
_ SElt
x) = SElt -> Maybe LBox
getSEltBox_naive SElt
x