{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module PureNix.Identifiers
( Var (..),
mkVar,
numberedVars,
Key (..),
identKey,
stringKey,
moduleKey,
binderKey,
numberedKeys,
)
where
import Data.Maybe
import Data.Set (Set)
import qualified Data.Set as Set
import Data.String
import Data.Text (Text)
import qualified Data.Text as T
import qualified Language.PureScript as PS
import qualified Language.PureScript.PSString as PS
newtype Var = UnsafeVar {Var -> Text
unVar :: Text}
deriving newtype (String -> Var
forall a. (String -> a) -> IsString a
fromString :: String -> Var
$cfromString :: String -> Var
IsString, Var -> Var -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Var -> Var -> Bool
$c/= :: Var -> Var -> Bool
== :: Var -> Var -> Bool
$c== :: Var -> Var -> Bool
Eq, Int -> Var -> ShowS
[Var] -> ShowS
Var -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Var] -> ShowS
$cshowList :: [Var] -> ShowS
show :: Var -> String
$cshow :: Var -> String
showsPrec :: Int -> Var -> ShowS
$cshowsPrec :: Int -> Var -> ShowS
Show)
identToText :: PS.Ident -> Text
identToText :: Ident -> Text
identToText (PS.Ident Text
t) = Text
t
identToText (PS.GenIdent Maybe Text
mvar Integer
n) = forall a. a -> Maybe a -> a
fromMaybe Text
"__instance" Maybe Text
mvar forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (forall a. Show a => a -> String
show Integer
n)
identToText Ident
PS.UnusedIdent = Text
"_"
identToText (PS.InternalIdent InternalIdentData
_) = forall a. HasCallStack => String -> a
error String
"impossible"
mkVar :: PS.Ident -> Var
mkVar :: Ident -> Var
mkVar = Text -> Var
UnsafeVar forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
removeDollarSigns forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
tickKeywords forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ident -> Text
identToText
where
tickKeywords :: Text -> Text
tickKeywords Text
w
| forall a. Ord a => a -> Set a -> Bool
Set.member Text
w Set Text
keywords Bool -> Bool -> Bool
|| Text -> Text -> Bool
T.isPrefixOf Text
"__" Text
w = Text
w forall a. Semigroup a => a -> a -> a
<> Text
"-"
| Bool
otherwise = Text
w
removeDollarSigns :: Text -> Text
removeDollarSigns Text
w =
(Char -> Char) -> Text -> Text
T.map (\Char
c -> if Char
c forall a. Eq a => a -> a -> Bool
== Char
'$' then Char
'-' else Char
c) forall a b. (a -> b) -> a -> b
$
if Text -> Text -> Bool
T.isPrefixOf Text
"$" Text
w then Text -> Text
T.tail Text
w else Text
w
keywords :: Set Text
keywords :: Set Text
keywords = forall a. Ord a => [a] -> Set a
Set.fromList ([Text]
purenixIdents forall a. Semigroup a => a -> a -> a
<> [Text]
nixPrimops forall a. Semigroup a => a -> a -> a
<> [Text]
nixKeywords)
where
purenixIdents :: [Text]
purenixIdents = [Text
"module", Text
"foreign"]
nixPrimops :: [Text]
nixPrimops = [Text
"builtins", Text
"import", Text
"false", Text
"true"]
nixKeywords :: [Text]
nixKeywords :: [Text]
nixKeywords =
[Text
"if", Text
"then", Text
"else", Text
"assert", Text
"with", Text
"let", Text
"in", Text
"rec", Text
"inherit", Text
"or"]
newtype Key = UnsafeKey {Key -> Text
unKey :: Text}
deriving newtype (String -> Key
forall a. (String -> a) -> IsString a
fromString :: String -> Key
$cfromString :: String -> Key
IsString, Key -> Key -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq, Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Key] -> ShowS
$cshowList :: [Key] -> ShowS
show :: Key -> String
$cshow :: Key -> String
showsPrec :: Int -> Key -> ShowS
$cshowsPrec :: Int -> Key -> ShowS
Show)
moduleKey :: PS.ModuleName -> Key
moduleKey :: ModuleName -> Key
moduleKey (PS.ModuleName Text
mdl) = Text -> Key
UnsafeKey forall a b. (a -> b) -> a -> b
$ Text
"\"" forall a. Semigroup a => a -> a -> a
<> Text
mdl forall a. Semigroup a => a -> a -> a
<> Text
"\""
identKey :: PS.Ident -> Key
identKey :: Ident -> Key
identKey = Text -> Key
UnsafeKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. Var -> Text
unVar forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ident -> Var
mkVar
stringKey :: PS.PSString -> Key
stringKey :: PSString -> Key
stringKey = Text -> Key
UnsafeKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. PSString -> Text
PS.prettyPrintObjectKey
binderKey :: Var -> Key
binderKey :: Var -> Key
binderKey = Text -> Key
UnsafeKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. Var -> Text
unVar
numberedText :: Text -> [Text]
numberedText :: Text -> [Text]
numberedText Text
prefix = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
n -> Text
prefix forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (forall a. Show a => a -> String
show Int
n)) [Int
0 :: Int ..]
numberedVars :: Text -> [Var]
numberedVars :: Text -> [Var]
numberedVars = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Var
UnsafeVar forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
numberedText
numberedKeys :: Text -> [Key]
numberedKeys :: Text -> [Key]
numberedKeys = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Key
UnsafeKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
numberedText