diff options
| author | Gregor Kleen <gkleen@yggdrasil.li> | 2019-05-30 12:18:08 +0200 |
|---|---|---|
| committer | Gregor Kleen <gkleen@yggdrasil.li> | 2019-05-30 12:18:08 +0200 |
| commit | f4c419b9ddec15bad267a4463f0720d6e28042d2 (patch) | |
| tree | 54a0259116476150247619c4410eae33f8669314 /interactive-edit-lens/src | |
| parent | 8afbe1f7df24034dd16fdf2e89b0665b2318ae2a (diff) | |
| download | incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar.gz incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar.bz2 incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar.xz incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.zip | |
Further work
Diffstat (limited to 'interactive-edit-lens/src')
| -rw-r--r-- | interactive-edit-lens/src/Interact.hs | 142 | ||||
| -rw-r--r-- | interactive-edit-lens/src/Interact/Types.hs | 26 | ||||
| -rw-r--r-- | interactive-edit-lens/src/Main.hs | 17 |
3 files changed, 131 insertions, 54 deletions
diff --git a/interactive-edit-lens/src/Interact.hs b/interactive-edit-lens/src/Interact.hs index 0074e86..662052b 100644 --- a/interactive-edit-lens/src/Interact.hs +++ b/interactive-edit-lens/src/Interact.hs | |||
| @@ -14,6 +14,7 @@ import Interact.Types | |||
| 14 | 14 | ||
| 15 | import Data.Text (Text) | 15 | import Data.Text (Text) |
| 16 | import qualified Data.Text as Text | 16 | import qualified Data.Text as Text |
| 17 | import qualified Data.Text.IO as Text | ||
| 17 | 18 | ||
| 18 | import Data.Text.Zipper | 19 | import Data.Text.Zipper |
| 19 | 20 | ||
| @@ -41,6 +42,7 @@ import Brick hiding (on) | |||
| 41 | import Brick.Focus | 42 | import Brick.Focus |
| 42 | import Brick.Widgets.Center | 43 | import Brick.Widgets.Center |
| 43 | import Brick.Widgets.Border | 44 | import Brick.Widgets.Border |
| 45 | import Brick.Widgets.FileBrowser | ||
| 44 | import Graphics.Vty hiding (showCursor) | 46 | import Graphics.Vty hiding (showCursor) |
| 45 | 47 | ||
| 46 | import Config.Dyre | 48 | import Config.Dyre |
| @@ -48,14 +50,20 @@ import Config.Dyre | |||
| 48 | import System.IO.Unsafe | 50 | import System.IO.Unsafe |
| 49 | import Debug.Trace | 51 | import Debug.Trace |
| 50 | 52 | ||
| 51 | interactiveEditLens :: (Params (InteractConfig c) -> Params (InteractConfig c)) -> InteractConfig c -> IO () | 53 | import System.CPUTime |
| 54 | import Text.Printf | ||
| 55 | |||
| 56 | import Control.Exception (evaluate) | ||
| 57 | import Control.DeepSeq | ||
| 58 | |||
| 59 | interactiveEditLens :: forall c. NFData c => (Params (InteractConfig c) -> Params (InteractConfig c)) -> InteractConfig c -> IO () | ||
| 52 | interactiveEditLens f = wrapMain . f $ defaultParams | 60 | interactiveEditLens f = wrapMain . f $ defaultParams |
| 53 | { projectName = "interact-edit-lens" | 61 | { projectName = "interact-edit-lens" |
| 54 | , showError = \s err -> s & compileError .~ Just err | 62 | , showError = \s err -> s & compileError .~ Just err |
| 55 | , realMain = interactiveEditLens' | 63 | , realMain = interactiveEditLens' |
| 56 | } | 64 | } |
| 57 | 65 | ||
| 58 | interactiveEditLens' :: forall c. InteractConfig c -> IO () | 66 | interactiveEditLens' :: forall c. NFData c => InteractConfig c -> IO () |
| 59 | interactiveEditLens' cfg@InteractConfig{..} | 67 | interactiveEditLens' cfg@InteractConfig{..} |
| 60 | | Just err <- icfgCompileError | 68 | | Just err <- icfgCompileError |
| 61 | = hPutStrLn stderr err | 69 | = hPutStrLn stderr err |
| @@ -89,9 +97,8 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
| 89 | where | 97 | where |
| 90 | infix 1 &?~ | 98 | infix 1 &?~ |
| 91 | 99 | ||
| 92 | (&?~) :: a -> RWS (InteractConfig c) () a b -> a | 100 | (&?~), actOn :: a -> RWS (InteractConfig c) () a b -> a |
| 93 | st &?~ act = (\(s, ()) -> s) $ execRWS act cfg st | 101 | st &?~ act = (\(s, ()) -> s) $ execRWS act cfg st |
| 94 | |||
| 95 | actOn = (&?~) | 102 | actOn = (&?~) |
| 96 | 103 | ||
| 97 | initialState :: InteractState c | 104 | initialState :: InteractState c |
| @@ -101,6 +108,8 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
| 101 | , istRight = (Last Valid, Last (init @(StringEdits Natural Char), 0), mempty) | 108 | , istRight = (Last Valid, Last (init @(StringEdits Natural Char), 0), mempty) |
| 102 | , istFocus = focusRing [LeftEditor, RightEditor] & | 109 | , istFocus = focusRing [LeftEditor, RightEditor] & |
| 103 | focusSetCurrent (case icfgInitial of InitialRight _ -> RightEditor; _other -> LeftEditor) | 110 | focusSetCurrent (case icfgInitial of InitialRight _ -> RightEditor; _other -> LeftEditor) |
| 111 | , istActive = True | ||
| 112 | , istLoadBrowser = Nothing | ||
| 104 | } | 113 | } |
| 105 | 114 | ||
| 106 | app :: InteractApp c | 115 | app :: InteractApp c |
| @@ -109,10 +118,15 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
| 109 | appDraw :: InteractState c -> [Widget InteractName] | 118 | appDraw :: InteractState c -> [Widget InteractName] |
| 110 | appDraw InteractState{..} = [ editors ] | 119 | appDraw InteractState{..} = [ editors ] |
| 111 | where | 120 | where |
| 112 | editors = hBox | 121 | editors = vBox |
| 113 | [ mbInvalid (withFocusRing istFocus renderEditor') (istLeft `WithName` LeftEditor) | 122 | [ case istLoadBrowser of |
| 114 | , vBorder | 123 | Nothing -> hBox |
| 115 | , mbInvalid (withFocusRing istFocus renderEditor') (istRight `WithName` RightEditor) | 124 | [ mbInvalid (withFocusRing istFocus renderEditor') (istLeft `WithName` LeftEditor) |
| 125 | , vBorder | ||
| 126 | , mbInvalid (withFocusRing istFocus renderEditor') (istRight `WithName` RightEditor) | ||
| 127 | ] | ||
| 128 | Just lBrowser -> renderFileBrowser True lBrowser | ||
| 129 | , hCenter . str $ bool "Inactive" "" istActive | ||
| 116 | ] | 130 | ] |
| 117 | renderEditor' :: Bool -> (Seq Char, Int) `WithName` InteractName -> Widget InteractName | 131 | renderEditor' :: Bool -> (Seq Char, Int) `WithName` InteractName -> Widget InteractName |
| 118 | renderEditor' foc ((content, cPos) `WithName` n) | 132 | renderEditor' foc ((content, cPos) `WithName` n) |
| @@ -133,42 +147,75 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
| 133 | mbInvalid f ((Last Valid , Last x, _) `WithName` n) = f $ x `WithName` n | 147 | mbInvalid f ((Last Valid , Last x, _) `WithName` n) = f $ x `WithName` n |
| 134 | 148 | ||
| 135 | appHandleEvent :: InteractState c -> BrickEvent InteractName InteractEvent -> EventM InteractName (Next (InteractState c)) | 149 | appHandleEvent :: InteractState c -> BrickEvent InteractName InteractEvent -> EventM InteractName (Next (InteractState c)) |
| 136 | appHandleEvent st@InteractState{..} (VtyEvent ev) = case ev of | 150 | appHandleEvent st@InteractState{..} (VtyEvent ev) |
| 137 | EvKey KEsc [] -> halt st | 151 | | Nothing <- istLoadBrowser = case ev of |
| 138 | EvKey (KChar 'c') [MCtrl] -> halt st | 152 | EvKey KEsc [] -> halt st |
| 139 | EvKey (KChar '\t') [] -> continue $ st & focus %~ focusNext | 153 | EvKey (KChar 'c') [MCtrl] -> halt st |
| 140 | EvKey KBackTab [] -> continue $ st & focus %~ focusPrev | 154 | EvKey (KChar '\t') [] -> continue . actOn st . runMaybeT $ do |
| 141 | EvKey (KChar 'a') [MCtrl] -> continue $ st &?~ doMove | 155 | guard =<< use active |
| 142 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, 0) else (l, 0)) | 156 | focus %= focusNext |
| 143 | EvKey (KChar 'e') [MCtrl] -> continue $ st &?~ doMove | 157 | EvKey KBackTab [] -> continue . actOn st . runMaybeT $ do |
| 144 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') $ c l then (pred l, Seq.length . c $ pred l) else (l, Seq.length $ c l)) | 158 | guard =<< use active |
| 145 | EvKey KLeft [MCtrl] -> continue $ st &?~ doMove | 159 | focus %= focusPrev |
| 146 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace (c l) || Seq.null (c l) then (pred l, 0) else (l - 2, 0)) | 160 | EvKey (KChar 'a') [MCtrl] -> continue $ st &?~ doMove |
| 147 | EvKey KRight [MCtrl] -> continue $ st &?~ doMove | 161 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, 0) else (l, 0)) |
| 148 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace $ c l then (succ l, 0) else (l + 2, 0)) | 162 | EvKey (KChar 'e') [MCtrl] -> continue $ st &?~ doMove |
| 149 | EvKey KUp [] -> continue $ st &?~ doMove | 163 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') $ c l then (pred l, Seq.length . c $ pred l) else (l, Seq.length $ c l)) |
| 150 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, p) else (l - 2, p)) | 164 | EvKey KLeft [MCtrl] -> continue $ st &?~ doMove |
| 151 | EvKey KDown [] -> continue $ st &?~ doMove | 165 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace (c l) || Seq.null (c l) then (pred l, 0) else (l - 2, 0)) |
| 152 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) then (succ l, p) else (l + 2, p)) | 166 | EvKey KRight [MCtrl] -> continue $ st &?~ doMove |
| 153 | EvKey KLeft [] -> continue $ st &?~ doMove moveLeft | 167 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace $ c l then (succ l, 0) else (l + 2, 0)) |
| 154 | EvKey KRight [] -> continue $ st &?~ doMove moveRight | 168 | EvKey KUp [] -> continue $ st &?~ doMove |
| 155 | EvKey KDel [] -> continue $ st &?~ doEdit (delete 0) | 169 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, p) else (l - 2, p)) |
| 156 | EvKey KBS [] -> continue . actOn st $ do | 170 | EvKey KDown [] -> continue $ st &?~ doMove |
| 157 | focused' <- preuse $ focused . _2 . _Wrapped | 171 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) then (succ l, p) else (l + 2, p)) |
| 158 | doEdit . delete $ -1 | 172 | EvKey KLeft [] -> continue $ st &?~ doMove moveLeft |
| 159 | unless (maybe False ((==) <$> view _2 <*> view (_1 . to Seq.length)) focused') $ | 173 | EvKey KRight [] -> continue $ st &?~ doMove moveRight |
| 160 | doMove moveLeft | 174 | EvKey KDel [] -> continue $ st &?~ doEdit (delete 0) |
| 161 | EvKey (KChar c) [] -> continue . actOn st $ do | 175 | EvKey KBS [] -> continue . actOn st $ do |
| 162 | doEdit $ insert 0 c | 176 | focused' <- preuse $ focused . _2 . _Wrapped |
| 163 | doMove moveRight | 177 | doEdit . delete $ -1 |
| 164 | EvKey KEnter [] -> continue . actOn st $ do | 178 | unless (maybe False ((==) <$> view _2 <*> view (_1 . to Seq.length)) focused') $ |
| 165 | doEdit $ insert 0 '\n' | 179 | doMove moveLeft |
| 166 | doMove moveRight | 180 | EvKey (KChar c) [] -> continue . actOn st $ do |
| 167 | other -> suspendAndResume $ do | 181 | doEdit $ insert 0 c |
| 168 | traceIO $ "Unhandled event:\n\t" ++ show other | 182 | doMove moveRight |
| 169 | return st | 183 | EvKey KEnter [] -> continue . actOn st $ do |
| 170 | -- where | 184 | doEdit $ insert 0 '\n' |
| 171 | -- editorMovement f = continue $ st & focused . _Just . editContentsL %~ f | 185 | doMove moveRight |
| 186 | EvKey (KChar 'p') [MCtrl] | ||
| 187 | | istActive -> do | ||
| 188 | void . liftIO . evaluate . force . ($ st) $ (,,) <$> view left <*> view right <*> view complement | ||
| 189 | continue $ st & active .~ False | ||
| 190 | | otherwise -> do | ||
| 191 | let st' = actOn st $ do | ||
| 192 | active .= True | ||
| 193 | doEdit mempty | ||
| 194 | before <- liftIO getCPUTime | ||
| 195 | void . liftIO . evaluate . force . ($ st') $ (,,) <$> view left <*> view right <*> view complement | ||
| 196 | after <- liftIO getCPUTime | ||
| 197 | suspendAndResume $ do | ||
| 198 | printf "Resume took %.12fs\n" (fromInteger (after - before) * 1e-12 :: Double) | ||
| 199 | return st' | ||
| 200 | EvKey (KChar 'o') [MCtrl] -> do | ||
| 201 | lBrowser <- liftIO $ newFileBrowser selectNonDirectories LoadBrowser Nothing | ||
| 202 | continue $ st & loadBrowser .~ Just lBrowser | ||
| 203 | other -> suspendAndResume $ do | ||
| 204 | traceIO $ "Unhandled event:\n\t" ++ show other | ||
| 205 | return st | ||
| 206 | -- where | ||
| 207 | -- editorMovement f = continue $ st & focused . _Just . editContentsL %~ f | ||
| 208 | | Just lBrowser <- istLoadBrowser = do | ||
| 209 | lBrowser' <- handleFileBrowserEvent ev lBrowser | ||
| 210 | case fileBrowserSelection lBrowser' of | ||
| 211 | [] -> continue $ st &?~ loadBrowser .= Just lBrowser' | ||
| 212 | (FileInfo{..} : _) -> do | ||
| 213 | insEdit <- divInit . view charseq <$> liftIO (Text.readFile fileInfoFilePath) | ||
| 214 | let st' = actOn st $ do | ||
| 215 | doEdit $ (insEdit :: StringEdits Natural Char) & stringEdits . sePos %~ fromIntegral | ||
| 216 | loadBrowser .= Nothing | ||
| 217 | continue st' | ||
| 218 | |||
| 172 | appHandleEvent st _ = continue st | 219 | appHandleEvent st _ = continue st |
| 173 | 220 | ||
| 174 | doMove = zoom $ focused . _2 . _Wrapped | 221 | doMove = zoom $ focused . _2 . _Wrapped |
| @@ -259,9 +306,10 @@ doEdit relativeEdit = void . runMaybeT $ do | |||
| 259 | | otherwise = currentPos | 306 | | otherwise = currentPos |
| 260 | aL . _2 %= (<> Last (newContent, currentPos')) | 307 | aL . _2 %= (<> Last (newContent, currentPos')) |
| 261 | absoluteEdit' <- uses (aL . _3) (absoluteEdit `mappend`) | 308 | absoluteEdit' <- uses (aL . _3) (absoluteEdit `mappend`) |
| 262 | bEdits <- prop direction absoluteEdit' | 309 | bRes <- runMaybeT $ do |
| 263 | bDom <- use $ bL . _2 . _Wrapped . _1 | 310 | guard =<< use active |
| 264 | case bDom `apply` bEdits of | 311 | (,) <$> use (bL . _2 . _Wrapped . _1) <*> prop direction absoluteEdit' |
| 312 | case uncurry apply =<< bRes of | ||
| 265 | Nothing -> do | 313 | Nothing -> do |
| 266 | bL . _1 %= (<> Last Invalid) | 314 | bL . _1 %= (<> Last Invalid) |
| 267 | aL . _3 .= absoluteEdit' | 315 | aL . _3 .= absoluteEdit' |
diff --git a/interactive-edit-lens/src/Interact/Types.hs b/interactive-edit-lens/src/Interact/Types.hs index a4d08ac..67f9ae3 100644 --- a/interactive-edit-lens/src/Interact/Types.hs +++ b/interactive-edit-lens/src/Interact/Types.hs | |||
| @@ -1,4 +1,4 @@ | |||
| 1 | {-# LANGUAGE TemplateHaskell #-} | 1 | {-# LANGUAGE TemplateHaskell, DeriveGeneric, StandaloneDeriving #-} |
| 2 | {-# OPTIONS_GHC -fno-warn-orphans #-} | 2 | {-# OPTIONS_GHC -fno-warn-orphans #-} |
| 3 | 3 | ||
| 4 | module Interact.Types | 4 | module Interact.Types |
| @@ -6,7 +6,7 @@ module Interact.Types | |||
| 6 | , _LeftEditor, _RightEditor, _PrimitiveName | 6 | , _LeftEditor, _RightEditor, _PrimitiveName |
| 7 | , Validity, pattern Valid, pattern Invalid | 7 | , Validity, pattern Valid, pattern Invalid |
| 8 | , InteractState(..) | 8 | , InteractState(..) |
| 9 | , HasLeft(..), HasRight(..), HasComplement(..), HasFocus(..), HasFocused(..) | 9 | , HasLeft(..), HasRight(..), HasComplement(..), HasFocus(..), HasFocused(..), HasActive(..), HasLoadBrowser(..) |
| 10 | , InteractInitial(..) | 10 | , InteractInitial(..) |
| 11 | , _InitialLeft, _InitialRight, _InitialEmpty | 11 | , _InitialLeft, _InitialRight, _InitialEmpty |
| 12 | , InteractConfig(..) | 12 | , InteractConfig(..) |
| @@ -38,6 +38,7 @@ import Numeric.Natural | |||
| 38 | import Brick | 38 | import Brick |
| 39 | import Brick.Focus | 39 | import Brick.Focus |
| 40 | import Brick.Widgets.Edit | 40 | import Brick.Widgets.Edit |
| 41 | import Brick.Widgets.FileBrowser | ||
| 41 | 42 | ||
| 42 | import Control.Lens | 43 | import Control.Lens |
| 43 | import Control.Lens.TH | 44 | import Control.Lens.TH |
| @@ -47,12 +48,29 @@ import Control.DFST.Lens | |||
| 47 | 48 | ||
| 48 | import Data.Text.Zipper.Generic | 49 | import Data.Text.Zipper.Generic |
| 49 | 50 | ||
| 51 | import Control.DeepSeq | ||
| 52 | import GHC.Generics (Generic) | ||
| 53 | |||
| 54 | |||
| 55 | deriving instance Generic (StringEdit n c) | ||
| 56 | instance (NFData n, NFData c) => NFData (StringEdit n c) | ||
| 57 | |||
| 58 | deriving instance Generic (StringEdits n c) | ||
| 59 | instance (NFData n, NFData c) => NFData (StringEdits n c) | ||
| 60 | |||
| 61 | deriving instance Generic (DFSTAction s c c') | ||
| 62 | instance (NFData s, NFData c, NFData c') => NFData (DFSTAction s c c') | ||
| 63 | |||
| 64 | instance (NFData s, NFData c, NFData c') => NFData (DFSTComplement s c c') where | ||
| 65 | rnf = foldr deepseq () | ||
| 66 | |||
| 50 | 67 | ||
| 51 | data InteractName | 68 | data InteractName |
| 52 | = LeftEditor | 69 | = LeftEditor |
| 53 | | RightEditor | 70 | | RightEditor |
| 71 | | LoadBrowser | ||
| 54 | | PrimitiveName !Text | 72 | | PrimitiveName !Text |
| 55 | deriving (Eq, Ord, Show, Read) | 73 | deriving (Eq, Ord, Show, Read, Generic) |
| 56 | 74 | ||
| 57 | makePrisms ''InteractName | 75 | makePrisms ''InteractName |
| 58 | 76 | ||
| @@ -64,6 +82,8 @@ data InteractState c = InteractState | |||
| 64 | { istLeft, istRight :: (Last Validity, Last (Seq Char, Int), StringEdits Natural Char) | 82 | { istLeft, istRight :: (Last Validity, Last (Seq Char, Int), StringEdits Natural Char) |
| 65 | , istComplement :: c | 83 | , istComplement :: c |
| 66 | , istFocus :: FocusRing InteractName | 84 | , istFocus :: FocusRing InteractName |
| 85 | , istActive :: Bool | ||
| 86 | , istLoadBrowser :: Maybe (FileBrowser InteractName) | ||
| 67 | } | 87 | } |
| 68 | 88 | ||
| 69 | makeLensesWith abbreviatedFields ''InteractState | 89 | makeLensesWith abbreviatedFields ''InteractState |
diff --git a/interactive-edit-lens/src/Main.hs b/interactive-edit-lens/src/Main.hs index 83c9725..c816515 100644 --- a/interactive-edit-lens/src/Main.hs +++ b/interactive-edit-lens/src/Main.hs | |||
| @@ -1,5 +1,6 @@ | |||
| 1 | {-# LANGUAGE OverloadedStrings | 1 | {-# LANGUAGE OverloadedStrings |
| 2 | , ExistentialQuantification | 2 | , ExistentialQuantification |
| 3 | , DeriveGeneric | ||
| 3 | #-} | 4 | #-} |
| 4 | 5 | ||
| 5 | module Main where | 6 | module Main where |
| @@ -30,18 +31,23 @@ import Debug.Trace | |||
| 30 | 31 | ||
| 31 | import Data.Universe | 32 | import Data.Universe |
| 32 | 33 | ||
| 33 | data SomeDFST = forall state. (Ord state, Show state, Finite state) => SomeDFST { someDFST :: DFST state Char Char } | 34 | import Control.DeepSeq |
| 35 | import GHC.Generics (Generic) | ||
| 36 | |||
| 37 | data SomeDFST = forall state. (Ord state, Show state, Finite state, NFData (DFSTComplement state Char Char)) => SomeDFST { someDFST :: DFST state Char Char } | ||
| 34 | 38 | ||
| 35 | data JsonContext = JCInDet | JCDict | JCDictKey | JCDictVal | JCArray | JCArrayVal | JCTop | 39 | data JsonContext = JCInDet | JCDict | JCDictKey | JCDictVal | JCArray | JCArrayVal | JCTop |
| 36 | deriving (Eq, Ord, Show, Read, Enum, Bounded) | 40 | deriving (Eq, Ord, Show, Read, Enum, Bounded, Generic) |
| 37 | instance Universe JsonContext | 41 | instance Universe JsonContext |
| 38 | instance Finite JsonContext | 42 | instance Finite JsonContext |
| 39 | 43 | ||
| 44 | instance NFData JsonContext | ||
| 45 | |||
| 40 | data JsonNewlState = JNElement JsonContext | 46 | data JsonNewlState = JNElement JsonContext |
| 41 | | JNTrue String JsonContext | JNFalse String JsonContext | JNNull String JsonContext | JNLitEnd JsonContext | 47 | | JNTrue String JsonContext | JNFalse String JsonContext | JNNull String JsonContext | JNLitEnd JsonContext |
| 42 | | JNString JsonContext | JNStringEsc Int JsonContext | JNStringEnd JsonContext | 48 | | JNString JsonContext | JNStringEsc Int JsonContext | JNStringEnd JsonContext |
| 43 | | JNNumberDigits Bool JsonContext | JNNumberDecimal JsonContext | JNNumberDecimalDigits Bool JsonContext | JNNumberExpSign JsonContext | JNNumberExpDigits Bool JsonContext | JNNumberEnd JsonContext | 49 | | JNNumberDigits Bool JsonContext | JNNumberDecimal JsonContext | JNNumberDecimalDigits Bool JsonContext | JNNumberExpSign JsonContext | JNNumberExpDigits Bool JsonContext | JNNumberEnd JsonContext |
| 44 | deriving (Eq, Ord, Show, Read) | 50 | deriving (Eq, Ord, Show, Read, Generic) |
| 45 | instance Universe JsonNewlState where | 51 | instance Universe JsonNewlState where |
| 46 | universe = concat | 52 | universe = concat |
| 47 | [ JNElement <$> universeF | 53 | [ JNElement <$> universeF |
| @@ -63,6 +69,8 @@ instance Universe JsonNewlState where | |||
| 63 | inits' xs = inits xs \\ [""] | 69 | inits' xs = inits xs \\ [""] |
| 64 | instance Finite JsonNewlState | 70 | instance Finite JsonNewlState |
| 65 | 71 | ||
| 72 | instance NFData JsonNewlState | ||
| 73 | |||
| 66 | jsonStrEscapes :: [(Char, Seq Char)] | 74 | jsonStrEscapes :: [(Char, Seq Char)] |
| 67 | jsonStrEscapes = [ ('"', "\\\"") | 75 | jsonStrEscapes = [ ('"', "\\\"") |
| 68 | , ('\\', "\\\\") | 76 | , ('\\', "\\\\") |
| @@ -78,10 +86,11 @@ hexDigits :: [Char] | |||
| 78 | hexDigits = ['0'..'9'] ++ ['a'..'f'] | 86 | hexDigits = ['0'..'9'] ++ ['a'..'f'] |
| 79 | 87 | ||
| 80 | data LineBreakState = LineBreak Int | 88 | data LineBreakState = LineBreak Int |
| 81 | deriving (Eq, Ord, Show, Read) | 89 | deriving (Eq, Ord, Show, Read, Generic) |
| 82 | instance Universe LineBreakState where | 90 | instance Universe LineBreakState where |
| 83 | universe = [ LineBreak n | n <- [0..80] ] | 91 | universe = [ LineBreak n | n <- [0..80] ] |
| 84 | instance Finite LineBreakState | 92 | instance Finite LineBreakState |
| 93 | instance NFData LineBreakState | ||
| 85 | 94 | ||
| 86 | dfstMap :: String -> Maybe SomeDFST | 95 | dfstMap :: String -> Maybe SomeDFST |
| 87 | dfstMap "double" = Just . SomeDFST $ DFST | 96 | dfstMap "double" = Just . SomeDFST $ DFST |
