1
- {-# LANGUAGE FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, RecordWildCards, TypeOperators, UndecidableInstances #-}
1
+ {-# LANGUAGE FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, RecordWildCards, TypeOperators, UndecidableInstances #-}
2
2
module Analysis.Concrete
3
3
( Concrete (.. )
4
4
, concrete
@@ -29,6 +29,7 @@ import Data.Loc
29
29
import qualified Data.Map as Map
30
30
import Data.Monoid (Alt (.. ))
31
31
import Data.Name
32
+ import Data.Text (Text , pack )
32
33
import Prelude hiding (fail )
33
34
34
35
type Precise = Int
@@ -41,7 +42,7 @@ data Concrete
41
42
= Closure Loc Name Core. Core Precise
42
43
| Unit
43
44
| Bool Bool
44
- | String String
45
+ | String Text
45
46
| Obj Frame
46
47
deriving (Eq , Ord , Show )
47
48
@@ -60,7 +61,7 @@ type Heap = IntMap.IntMap Concrete
60
61
61
62
-- | Concrete evaluation of a term to a value.
62
63
--
63
- -- >>> snd (concrete [File (Loc "bool" emptySpan) (Core.Bool True)])
64
+ -- >>> map fileBody ( snd (concrete [File (Loc "bool" emptySpan) (Core.Bool True)]) )
64
65
-- [Right (Bool True)]
65
66
concrete :: [File Core. Core ] -> (Heap , [File (Either (Loc , String ) Concrete )])
66
67
concrete
@@ -184,28 +185,32 @@ heapValueGraph h = heapGraph (const id) (const fromAddr) h
184
185
heapAddressGraph :: Heap -> G. Graph (EdgeType , Precise )
185
186
heapAddressGraph = heapGraph (\ addr v -> (Value v, addr)) (fmap G. vertex . (,) . either Edge Slot )
186
187
187
- addressStyle :: Heap -> G. Style (EdgeType , Precise ) String
188
+ addressStyle :: Heap -> G. Style (EdgeType , Precise ) Text
188
189
addressStyle heap = (G. defaultStyle vertex) { G. edgeAttributes }
189
- where vertex (_, addr) = maybe (show addr <> " = ? " ) ((( show addr <> " = " ) <> ) . fromConcrete) (IntMap. lookup addr heap)
190
+ where vertex (_, addr) = pack (show addr) <> " = " <> maybe " ? " fromConcrete (IntMap. lookup addr heap)
190
191
edgeAttributes _ (Slot name, _) = [" label" G. := fromName name]
191
192
edgeAttributes _ (Edge Core. Import , _) = [" color" G. := " blue" ]
192
193
edgeAttributes _ (Edge Core. Lexical , _) = [" color" G. := " green" ]
193
194
edgeAttributes _ _ = []
194
195
fromConcrete = \ case
195
196
Unit -> " ()"
196
- Bool b -> show b
197
- String s -> show s
197
+ Bool b -> pack $ show b
198
+ String s -> pack $ show s
198
199
Closure (Loc p (Span s e)) n _ _ -> " \\\\ " <> fromName n <> " [" <> p <> " :" <> showPos s <> " -" <> showPos e <> " ]"
199
200
Obj _ -> " {}"
200
- showPos (Pos l c) = show l <> " :" <> show c
201
+ showPos (Pos l c) = pack ( show l) <> " :" <> pack ( show c)
201
202
fromName (User s) = s
202
203
fromName (Gen sym) = fromGensym sym
203
- fromName (Path p) = show p
204
+ fromName (Path p) = pack $ show p
204
205
fromGensym (Root s) = s
205
- fromGensym (ss :/ (s, i)) = fromGensym ss <> " ." <> s <> show i
206
+ fromGensym (ss :/ (s, i)) = fromGensym ss <> " ." <> s <> pack ( show i)
206
207
207
208
data EdgeType
208
209
= Edge Core. Edge
209
210
| Slot Name
210
211
| Value Concrete
211
212
deriving (Eq , Ord , Show )
213
+
214
+
215
+ -- $setup
216
+ -- >>> :seti -XOverloadedStrings
0 commit comments