summaryrefslogtreecommitdiff
path: root/interactive-edit-lens/src/Interact
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2018-12-18 13:51:16 +0100
committerGregor Kleen <gkleen@yggdrasil.li>2018-12-18 13:51:16 +0100
commit46ae60eaca841b554ba20c6a2b7a15b43c12b4df (patch)
tree0bb06127a0e08e75f8be755f5a5dfb1702b627b6 /interactive-edit-lens/src/Interact
parentb0b18979d5ccd109d5a56937396acdeb85c857aa (diff)
downloadincremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.gz
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.bz2
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.xz
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.zip
Much ado about nothing
Diffstat (limited to 'interactive-edit-lens/src/Interact')
-rw-r--r--interactive-edit-lens/src/Interact/Types.hs120
1 files changed, 120 insertions, 0 deletions
diff --git a/interactive-edit-lens/src/Interact/Types.hs b/interactive-edit-lens/src/Interact/Types.hs
new file mode 100644
index 0000000..a4d08ac
--- /dev/null
+++ b/interactive-edit-lens/src/Interact/Types.hs
@@ -0,0 +1,120 @@
1{-# LANGUAGE TemplateHaskell #-}
2{-# OPTIONS_GHC -fno-warn-orphans #-}
3
4module Interact.Types
5 ( InteractName(..)
6 , _LeftEditor, _RightEditor, _PrimitiveName
7 , Validity, pattern Valid, pattern Invalid
8 , InteractState(..)
9 , HasLeft(..), HasRight(..), HasComplement(..), HasFocus(..), HasFocused(..)
10 , InteractInitial(..)
11 , _InitialLeft, _InitialRight, _InitialEmpty
12 , InteractConfig(..)
13 , HasInitial(..), HasLens(..), HasCompileError(..)
14 , InteractEvent
15 , InteractApp
16 , InteractDirection(..)
17 , charseq
18 , WithName(..)
19 , module Control.Edit
20 , module Control.Lens.Edit
21 , module Control.DFST.Lens
22 , module Data.Semigroup
23 , module Numeric.Natural
24 ) where
25
26import Data.Text (Text)
27import qualified Data.Text as Text
28import Data.Text.Lens
29
30import Data.Sequence (Seq(..))
31import qualified Data.Sequence as Seq
32
33import qualified Data.Foldable as Foldable
34
35import Data.Semigroup (Semigroup(..), Last(..))
36import Numeric.Natural
37
38import Brick
39import Brick.Focus
40import Brick.Widgets.Edit
41
42import Control.Lens
43import Control.Lens.TH
44import Control.Edit
45import Control.Lens.Edit
46import Control.DFST.Lens
47
48import Data.Text.Zipper.Generic
49
50
51data InteractName
52 = LeftEditor
53 | RightEditor
54 | PrimitiveName !Text
55 deriving (Eq, Ord, Show, Read)
56
57makePrisms ''InteractName
58
59type Validity = Bool
60pattern Valid = True
61pattern Invalid = False
62
63data InteractState c = InteractState
64 { istLeft, istRight :: (Last Validity, Last (Seq Char, Int), StringEdits Natural Char)
65 , istComplement :: c
66 , istFocus :: FocusRing InteractName
67 }
68
69makeLensesWith abbreviatedFields ''InteractState
70
71class HasFocused s a | s -> a where
72 focused :: Traversal' s a
73
74instance HasFocused (InteractState c) (Last Validity, Last (Seq Char, Int), StringEdits Natural Char) where
75 focused f st@InteractState{..} = case focusGetCurrent istFocus of
76 Just LeftEditor -> left f st
77 Just RightEditor -> right f st
78 _other -> pure st
79
80data InteractInitial
81 = InitialLeft Text
82 | InitialRight Text
83 | InitialEmpty
84 deriving (Eq, Ord, Show, Read)
85
86makePrisms ''InteractInitial
87
88data InteractConfig c = InteractConfig
89 { icfgInitial :: InteractInitial
90 , icfgLens :: EditLens c (StringEdits Natural Char) (StringEdits Natural Char)
91 , icfgCompileError :: Maybe String
92 }
93
94instance HasEditLens (InteractConfig c) (StringEdits Natural Char) (StringEdits Natural Char) where
95 type Complement (InteractConfig c) = c
96 ground = ground . icfgLens
97 propR = propR . icfgLens
98 propL = propL . icfgLens
99
100makeLensesWith abbreviatedFields ''InteractConfig
101
102charseq :: Iso' Text (Seq Char)
103charseq = iso Text.unpack Text.pack . iso Seq.fromList Foldable.toList
104
105type InteractEvent = ()
106
107type InteractApp c = App (InteractState c) InteractEvent InteractName
108
109data InteractDirection = PropagateLeft | PropagateRight
110 deriving (Eq, Ord, Enum, Bounded, Show, Read)
111
112makePrisms ''InteractDirection
113
114
115infixr 1 `WithName`
116data WithName x n = WithName x n
117 deriving (Eq, Ord, Show, Read)
118
119instance Named (x `WithName` n) n where
120 getName (_ `WithName` n) = n