44{-# LANGUAGE ImpredicativeTypes #-}
55{-# LANGUAGE LambdaCase #-}
66{-# LANGUAGE LinearTypes #-}
7- {-# LANGUAGE MultiWayIf #-}
87{-# LANGUAGE TypeApplications #-}
98{-# LANGUAGE NoImplicitPrelude #-}
109
1110module Compact.SExpr where
1211
1312import Compact.Pure.Internal
1413import Control.DeepSeq (NFData )
15- import Control.Functor.Linear ((<$>) , (<&>) , (>>=) )
16- import Data.Bifunctor.Linear (Bifunctor (second ))
14+ import Control.Functor.Linear ((<&>) )
1715import Data.Char (isSpace )
18- import qualified Data.Functor.Linear as Data
1916import GHC.Generics (Generic )
2017import Prelude.Linear
2118import Text.Read (readMaybe )
22- import Unsafe.Linear (toLinear2 )
2319import qualified Prelude as NonLinear
2420
2521loadSampleData :: IO String
@@ -31,7 +27,7 @@ data SExpr
3127 | SInteger Int
3228 | SString String
3329 | SSymbol String
34- deriving (Eq , Generic , NFData )
30+ deriving (NonLinear. Eq , Generic , NFData )
3531
3632showSExpr :: Bool -> Int -> SExpr % 1 -> String
3733showSExpr cont indent = \ case
@@ -40,22 +36,22 @@ showSExpr cont indent = \case
4036 makeIndent cont indent
4137 ++ " ("
4238 ++ showSExpr True (indent + 1 ) x
43- ++ concatMap (\ x -> " \n " ++ showSExpr False (indent + 1 ) x) xs
39+ ++ concatMap (\ x' -> " \n " ++ showSExpr False (indent + 1 ) x' ) xs
4440 ++ " )"
4541 SFloat f -> makeIndent cont indent ++ show f
4642 SInteger i -> makeIndent cont indent ++ show i
4743 SString s -> makeIndent cont indent ++ show s
4844 SSymbol s -> makeIndent cont indent ++ s
4945 where
50- makeIndent cont indent = if cont then " " else replicate indent ' '
46+ makeIndent isCont n = if isCont then " " else replicate n ' '
5147
5248instance Show SExpr where
5349 show x = showSExpr False 0 x
5450
5551data SContext
5652 = NotInSList
5753 | InSList [SExpr ]
58- deriving (Eq , Generic , NFData )
54+ deriving (Generic , NFData )
5955
6056data DSContext r
6157 = DNotInSList (Dest SExpr r )
@@ -67,7 +63,7 @@ data SExprParseError
6763 | UnexpectedEOFSList (Maybe [SExpr ])
6864 | UnexpectedEOFSString Bool (Maybe String )
6965 | UnexpectedContentAfter SExpr (Maybe String )
70- deriving (Eq , Generic , NFData )
66+ deriving (Generic , NFData )
7167
7268instance Show SExprParseError where
7369 show = \ case
@@ -165,18 +161,18 @@ parseUsingDest' = \cases
165161 Nothing -> appendOrRet ctx (\ dExpr -> dExpr <| C @ " SSymbol" <|.. raw `lseq` Right ) remaining
166162 where
167163 appendOrRet :: DSContext r % 1 -> (Dest SExpr r % 1 -> String -> Either (Ur SExprParseError ) String ) % 1 -> String -> Either (Ur SExprParseError ) String
168- appendOrRet ctx f s = case ctx of
169- DNotInSList d -> f d s
164+ appendOrRet context f str = case context of
165+ DNotInSList d -> f d str
170166 DInSList d ->
171167 case d <| C @ " :" of
172- (dExpr, dRem) -> case f dExpr s of
173- Right s ' -> parseUsingDest' (DInSList dRem) s '
168+ (dExpr, dRem) -> case f dExpr str of
169+ Right str ' -> parseUsingDest' (DInSList dRem) str '
174170 Left err -> dRem <| C @ " []" `lseq` Left err
175171
176172parseUsingDest :: String -> Either SExprParseError SExpr
177- parseUsingDest s =
173+ parseUsingDest str =
178174 case withRegion $ \ r ->
179- case completeExtract $ alloc r <&> DNotInSList <&> flip parseUsingDest' s <&> finalizeResults of
175+ case completeExtract $ alloc r <&> DNotInSList <&> flip parseUsingDest' str <&> finalizeResults of
180176 Ur (expr, Right () ) -> Ur (Right expr)
181177 Ur (expr, Left errFn) -> Ur (Left $ errFn expr) of
182178 Ur res -> res
0 commit comments