{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# HLINT ignore "Unused LANGUAGE pragma" #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
module Grisette.Internal.Core.Data.Symbol
( Identifier (..),
identifier,
withInfo,
withLoc,
uniqueIdentifier,
Symbol (..),
simple,
indexed,
)
where
import Control.DeepSeq (NFData (rnf))
import Data.Hashable (Hashable (hashWithSalt))
import Data.IORef (IORef, atomicModifyIORef', newIORef)
import Data.String (IsString (fromString))
import qualified Data.Text as T
import Data.Typeable (Proxy (Proxy), Typeable, eqT, typeRep, type (:~:) (Refl))
import Debug.Trace.LocationTH (__LOCATION__)
import GHC.Generics (Generic)
import GHC.IO (unsafePerformIO)
import Language.Haskell.TH.Syntax (Lift (liftTyped), unsafeTExpCoerce)
import Language.Haskell.TH.Syntax.Compat (SpliceQ, liftSplice)
data Identifier where
Identifier :: T.Text -> Identifier
IdentifierWithInfo ::
( Typeable a,
Ord a,
Lift a,
NFData a,
Show a,
Hashable a
) =>
Identifier ->
a ->
Identifier
instance Show Identifier where
show :: Identifier -> String
show (Identifier Text
i) = Text -> String
T.unpack Text
i
show (IdentifierWithInfo Identifier
s a
i) = Identifier -> String
forall a. Show a => a -> String
show Identifier
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
i
instance IsString Identifier where
fromString :: String -> Identifier
fromString = Text -> Identifier
Identifier (Text -> Identifier) -> (String -> Text) -> String -> Identifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
instance Eq Identifier where
Identifier Text
l == :: Identifier -> Identifier -> Bool
== Identifier Text
r = Text
l Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
r
IdentifierWithInfo Identifier
l (a
linfo :: linfo)
== IdentifierWithInfo Identifier
r (a
rinfo :: rinfo) = case forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
forall a b. (Typeable a, Typeable b) => Maybe (a :~: b)
eqT @linfo @rinfo of
Just a :~: a
Refl -> Identifier
l Identifier -> Identifier -> Bool
forall a. Eq a => a -> a -> Bool
== Identifier
r Bool -> Bool -> Bool
&& a
linfo a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a
rinfo
Maybe (a :~: a)
_ -> Bool
False
Identifier
_ == Identifier
_ = Bool
False
instance Ord Identifier where
Identifier Text
l <= :: Identifier -> Identifier -> Bool
<= Identifier Text
r = Text
l Text -> Text -> Bool
forall a. Ord a => a -> a -> Bool
<= Text
r
Identifier Text
_ <= Identifier
_ = Bool
True
Identifier
_ <= Identifier Text
_ = Bool
False
IdentifierWithInfo Identifier
l (a
linfo :: linfo)
<= IdentifierWithInfo Identifier
r (a
rinfo :: rinfo) =
Identifier
l Identifier -> Identifier -> Bool
forall a. Ord a => a -> a -> Bool
< Identifier
r
Bool -> Bool -> Bool
|| ( Identifier
l Identifier -> Identifier -> Bool
forall a. Eq a => a -> a -> Bool
== Identifier
r
Bool -> Bool -> Bool
&& ( case forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
forall a b. (Typeable a, Typeable b) => Maybe (a :~: b)
eqT @linfo @rinfo of
Just a :~: a
Refl -> a
linfo a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
a
rinfo
Maybe (a :~: a)
_ -> Proxy a -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @linfo) TypeRep -> TypeRep -> Bool
forall a. Ord a => a -> a -> Bool
<= Proxy a -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @rinfo)
)
)
instance Hashable Identifier where
hashWithSalt :: Int -> Identifier -> Int
hashWithSalt Int
s (Identifier Text
n) = Int
s Int -> Text -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Text
n
hashWithSalt Int
s (IdentifierWithInfo Identifier
n a
i) = Int
s Int -> Identifier -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Identifier
n Int -> a -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` a
i
instance Lift Identifier where
liftTyped :: forall (m :: * -> *). Quote m => Identifier -> Code m Identifier
liftTyped (Identifier Text
n) = [||Text -> Identifier
Identifier Text
n||]
liftTyped (IdentifierWithInfo Identifier
n a
i) = [||Identifier -> a -> Identifier
forall a.
(Typeable a, Ord a, Lift a, NFData a, Show a, Hashable a) =>
Identifier -> a -> Identifier
IdentifierWithInfo Identifier
n a
i||]
instance NFData Identifier where
rnf :: Identifier -> ()
rnf (Identifier Text
n) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
n
rnf (IdentifierWithInfo Identifier
n a
i) = Identifier -> ()
forall a. NFData a => a -> ()
rnf Identifier
n () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
forall a. NFData a => a -> ()
rnf a
i
identifier :: T.Text -> Identifier
identifier :: Text -> Identifier
identifier = Text -> Identifier
Identifier
withInfo ::
(Typeable a, Ord a, Lift a, NFData a, Show a, Hashable a) =>
Identifier ->
a ->
Identifier
withInfo :: forall a.
(Typeable a, Ord a, Lift a, NFData a, Show a, Hashable a) =>
Identifier -> a -> Identifier
withInfo = Identifier -> a -> Identifier
forall a.
(Typeable a, Ord a, Lift a, NFData a, Show a, Hashable a) =>
Identifier -> a -> Identifier
IdentifierWithInfo
data FileLocation = FileLocation
{ FileLocation -> String
locPath :: String,
FileLocation -> Int
locLineno :: Int,
FileLocation -> (Int, Int)
locSpan :: (Int, Int)
}
deriving (FileLocation -> FileLocation -> Bool
(FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool) -> Eq FileLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileLocation -> FileLocation -> Bool
== :: FileLocation -> FileLocation -> Bool
$c/= :: FileLocation -> FileLocation -> Bool
/= :: FileLocation -> FileLocation -> Bool
Eq, Eq FileLocation
Eq FileLocation =>
(FileLocation -> FileLocation -> Ordering)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> Bool)
-> (FileLocation -> FileLocation -> FileLocation)
-> (FileLocation -> FileLocation -> FileLocation)
-> Ord FileLocation
FileLocation -> FileLocation -> Bool
FileLocation -> FileLocation -> Ordering
FileLocation -> FileLocation -> FileLocation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FileLocation -> FileLocation -> Ordering
compare :: FileLocation -> FileLocation -> Ordering
$c< :: FileLocation -> FileLocation -> Bool
< :: FileLocation -> FileLocation -> Bool
$c<= :: FileLocation -> FileLocation -> Bool
<= :: FileLocation -> FileLocation -> Bool
$c> :: FileLocation -> FileLocation -> Bool
> :: FileLocation -> FileLocation -> Bool
$c>= :: FileLocation -> FileLocation -> Bool
>= :: FileLocation -> FileLocation -> Bool
$cmax :: FileLocation -> FileLocation -> FileLocation
max :: FileLocation -> FileLocation -> FileLocation
$cmin :: FileLocation -> FileLocation -> FileLocation
min :: FileLocation -> FileLocation -> FileLocation
Ord, (forall x. FileLocation -> Rep FileLocation x)
-> (forall x. Rep FileLocation x -> FileLocation)
-> Generic FileLocation
forall x. Rep FileLocation x -> FileLocation
forall x. FileLocation -> Rep FileLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FileLocation -> Rep FileLocation x
from :: forall x. FileLocation -> Rep FileLocation x
$cto :: forall x. Rep FileLocation x -> FileLocation
to :: forall x. Rep FileLocation x -> FileLocation
Generic, (forall (m :: * -> *). Quote m => FileLocation -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation)
-> Lift FileLocation
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FileLocation -> m Exp
forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation
$clift :: forall (m :: * -> *). Quote m => FileLocation -> m Exp
lift :: forall (m :: * -> *). Quote m => FileLocation -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation
liftTyped :: forall (m :: * -> *).
Quote m =>
FileLocation -> Code m FileLocation
Lift, FileLocation -> ()
(FileLocation -> ()) -> NFData FileLocation
forall a. (a -> ()) -> NFData a
$crnf :: FileLocation -> ()
rnf :: FileLocation -> ()
NFData, Eq FileLocation
Eq FileLocation =>
(Int -> FileLocation -> Int)
-> (FileLocation -> Int) -> Hashable FileLocation
Int -> FileLocation -> Int
FileLocation -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> FileLocation -> Int
hashWithSalt :: Int -> FileLocation -> Int
$chash :: FileLocation -> Int
hash :: FileLocation -> Int
Hashable)
instance Show FileLocation where
show :: FileLocation -> String
show (FileLocation String
p Int
l (Int
s1, Int
s2)) =
String
p String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
l String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
s1 String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
s2
parseFileLocation :: String -> FileLocation
parseFileLocation :: String -> FileLocation
parseFileLocation String
str =
let r :: String
r = ShowS
forall a. [a] -> [a]
reverse String
str
(String
s2, String
r1) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-') String
r
(String
s1, String
r2) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. HasCallStack => [a] -> [a]
tail String
r1
(String
l, String
p) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. HasCallStack => [a] -> [a]
tail String
r2
in String -> Int -> (Int, Int) -> FileLocation
FileLocation
(ShowS
forall a. [a] -> [a]
reverse ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. HasCallStack => [a] -> [a]
tail String
p)
(String -> Int
forall a. Read a => String -> a
read (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
reverse String
l)
(String -> Int
forall a. Read a => String -> a
read (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
reverse String
s1, String -> Int
forall a. Read a => String -> a
read (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
reverse String
s2)
withLoc :: Identifier -> SpliceQ Identifier
withLoc :: Identifier -> SpliceQ Identifier
withLoc Identifier
s =
[||
Identifier -> a -> Identifier
forall a.
(Typeable a, Ord a, Lift a, NFData a, Show a, Hashable a) =>
Identifier -> a -> Identifier
withInfo
Identifier
s
(String -> FileLocation
parseFileLocation $$(Q (TExp String) -> Splice Q String
forall a (m :: * -> *). m (TExp a) -> Splice m a
liftSplice (Q (TExp String) -> Splice Q String)
-> Q (TExp String) -> Splice Q String
forall a b. (a -> b) -> a -> b
$ Q Exp -> Q (TExp String)
forall a (m :: * -> *). Quote m => m Exp -> m (TExp a)
unsafeTExpCoerce Q Exp
__LOCATION__))
||]
identifierCount :: IORef Int
identifierCount :: IORef Int
identifierCount = IO (IORef Int) -> IORef Int
forall a. IO a -> a
unsafePerformIO (IO (IORef Int) -> IORef Int) -> IO (IORef Int) -> IORef Int
forall a b. (a -> b) -> a -> b
$ Int -> IO (IORef Int)
forall a. a -> IO (IORef a)
newIORef Int
0
{-# NOINLINE identifierCount #-}
newtype UniqueCount = UniqueCount Int
deriving newtype (UniqueCount -> UniqueCount -> Bool
(UniqueCount -> UniqueCount -> Bool)
-> (UniqueCount -> UniqueCount -> Bool) -> Eq UniqueCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UniqueCount -> UniqueCount -> Bool
== :: UniqueCount -> UniqueCount -> Bool
$c/= :: UniqueCount -> UniqueCount -> Bool
/= :: UniqueCount -> UniqueCount -> Bool
Eq, Eq UniqueCount
Eq UniqueCount =>
(UniqueCount -> UniqueCount -> Ordering)
-> (UniqueCount -> UniqueCount -> Bool)
-> (UniqueCount -> UniqueCount -> Bool)
-> (UniqueCount -> UniqueCount -> Bool)
-> (UniqueCount -> UniqueCount -> Bool)
-> (UniqueCount -> UniqueCount -> UniqueCount)
-> (UniqueCount -> UniqueCount -> UniqueCount)
-> Ord UniqueCount
UniqueCount -> UniqueCount -> Bool
UniqueCount -> UniqueCount -> Ordering
UniqueCount -> UniqueCount -> UniqueCount
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UniqueCount -> UniqueCount -> Ordering
compare :: UniqueCount -> UniqueCount -> Ordering
$c< :: UniqueCount -> UniqueCount -> Bool
< :: UniqueCount -> UniqueCount -> Bool
$c<= :: UniqueCount -> UniqueCount -> Bool
<= :: UniqueCount -> UniqueCount -> Bool
$c> :: UniqueCount -> UniqueCount -> Bool
> :: UniqueCount -> UniqueCount -> Bool
$c>= :: UniqueCount -> UniqueCount -> Bool
>= :: UniqueCount -> UniqueCount -> Bool
$cmax :: UniqueCount -> UniqueCount -> UniqueCount
max :: UniqueCount -> UniqueCount -> UniqueCount
$cmin :: UniqueCount -> UniqueCount -> UniqueCount
min :: UniqueCount -> UniqueCount -> UniqueCount
Ord, UniqueCount -> ()
(UniqueCount -> ()) -> NFData UniqueCount
forall a. (a -> ()) -> NFData a
$crnf :: UniqueCount -> ()
rnf :: UniqueCount -> ()
NFData, Eq UniqueCount
Eq UniqueCount =>
(Int -> UniqueCount -> Int)
-> (UniqueCount -> Int) -> Hashable UniqueCount
Int -> UniqueCount -> Int
UniqueCount -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> UniqueCount -> Int
hashWithSalt :: Int -> UniqueCount -> Int
$chash :: UniqueCount -> Int
hash :: UniqueCount -> Int
Hashable)
deriving ((forall (m :: * -> *). Quote m => UniqueCount -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
UniqueCount -> Code m UniqueCount)
-> Lift UniqueCount
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => UniqueCount -> m Exp
forall (m :: * -> *). Quote m => UniqueCount -> Code m UniqueCount
$clift :: forall (m :: * -> *). Quote m => UniqueCount -> m Exp
lift :: forall (m :: * -> *). Quote m => UniqueCount -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => UniqueCount -> Code m UniqueCount
liftTyped :: forall (m :: * -> *). Quote m => UniqueCount -> Code m UniqueCount
Lift)
instance Show UniqueCount where
show :: UniqueCount -> String
show (UniqueCount Int
i) = String
"unique<" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
i String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
">"
uniqueIdentifier :: T.Text -> IO Identifier
uniqueIdentifier :: Text -> IO Identifier
uniqueIdentifier Text
ident = do
Int
i <- IORef Int -> (Int -> (Int, Int)) -> IO Int
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef Int
identifierCount (\Int
x -> (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, Int
x))
Identifier -> IO Identifier
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Identifier -> IO Identifier) -> Identifier -> IO Identifier
forall a b. (a -> b) -> a -> b
$ Identifier -> UniqueCount -> Identifier
forall a.
(Typeable a, Ord a, Lift a, NFData a, Show a, Hashable a) =>
Identifier -> a -> Identifier
withInfo (Text -> Identifier
identifier Text
ident) (Int -> UniqueCount
UniqueCount Int
i)
data Symbol where
SimpleSymbol :: Identifier -> Symbol
IndexedSymbol :: Identifier -> Int -> Symbol
deriving (Symbol -> Symbol -> Bool
(Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool) -> Eq Symbol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Symbol -> Symbol -> Bool
== :: Symbol -> Symbol -> Bool
$c/= :: Symbol -> Symbol -> Bool
/= :: Symbol -> Symbol -> Bool
Eq, Eq Symbol
Eq Symbol =>
(Symbol -> Symbol -> Ordering)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> Ord Symbol
Symbol -> Symbol -> Bool
Symbol -> Symbol -> Ordering
Symbol -> Symbol -> Symbol
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Symbol -> Symbol -> Ordering
compare :: Symbol -> Symbol -> Ordering
$c< :: Symbol -> Symbol -> Bool
< :: Symbol -> Symbol -> Bool
$c<= :: Symbol -> Symbol -> Bool
<= :: Symbol -> Symbol -> Bool
$c> :: Symbol -> Symbol -> Bool
> :: Symbol -> Symbol -> Bool
$c>= :: Symbol -> Symbol -> Bool
>= :: Symbol -> Symbol -> Bool
$cmax :: Symbol -> Symbol -> Symbol
max :: Symbol -> Symbol -> Symbol
$cmin :: Symbol -> Symbol -> Symbol
min :: Symbol -> Symbol -> Symbol
Ord, (forall x. Symbol -> Rep Symbol x)
-> (forall x. Rep Symbol x -> Symbol) -> Generic Symbol
forall x. Rep Symbol x -> Symbol
forall x. Symbol -> Rep Symbol x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Symbol -> Rep Symbol x
from :: forall x. Symbol -> Rep Symbol x
$cto :: forall x. Rep Symbol x -> Symbol
to :: forall x. Rep Symbol x -> Symbol
Generic, (forall (m :: * -> *). Quote m => Symbol -> m Exp)
-> (forall (m :: * -> *). Quote m => Symbol -> Code m Symbol)
-> Lift Symbol
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Symbol -> m Exp
forall (m :: * -> *). Quote m => Symbol -> Code m Symbol
$clift :: forall (m :: * -> *). Quote m => Symbol -> m Exp
lift :: forall (m :: * -> *). Quote m => Symbol -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Symbol -> Code m Symbol
liftTyped :: forall (m :: * -> *). Quote m => Symbol -> Code m Symbol
Lift, Symbol -> ()
(Symbol -> ()) -> NFData Symbol
forall a. (a -> ()) -> NFData a
$crnf :: Symbol -> ()
rnf :: Symbol -> ()
NFData, Eq Symbol
Eq Symbol =>
(Int -> Symbol -> Int) -> (Symbol -> Int) -> Hashable Symbol
Int -> Symbol -> Int
Symbol -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Symbol -> Int
hashWithSalt :: Int -> Symbol -> Int
$chash :: Symbol -> Int
hash :: Symbol -> Int
Hashable)
instance Show Symbol where
show :: Symbol -> String
show (SimpleSymbol Identifier
i) = Identifier -> String
forall a. Show a => a -> String
show Identifier
i
show (IndexedSymbol Identifier
i Int
idx) = Identifier -> String
forall a. Show a => a -> String
show Identifier
i String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"@" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
idx
instance IsString Symbol where
fromString :: String -> Symbol
fromString = Identifier -> Symbol
SimpleSymbol (Identifier -> Symbol)
-> (String -> Identifier) -> String -> Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Identifier
forall a. IsString a => String -> a
fromString
simple :: Identifier -> Symbol
simple :: Identifier -> Symbol
simple = Identifier -> Symbol
SimpleSymbol
indexed :: Identifier -> Int -> Symbol
indexed :: Identifier -> Int -> Symbol
indexed = Identifier -> Int -> Symbol
IndexedSymbol