-- SPDX-FileCopyrightText: 2021 Oxhead Alpha
-- SPDX-License-Identifier: LicenseRef-MIT-OA


-- | Core parser types

module Morley.Michelson.Parser.Types
  ( Parser
  , MichelsonSource (.., MSStdin, MSCli)
  , codeSrc
  ) where

import Fmt (Buildable(..))
import GHC.Stack (SrcLoc(..))
import Text.Megaparsec (Parsec)

import Morley.Michelson.Parser.Error

type Parser = Parsec CustomParserException Text

data ParserOptions = ParserOptions
  { ParserOptions -> Bool
poMorleyExts :: Bool
  } deriving stock (Int -> ParserOptions -> ShowS
[ParserOptions] -> ShowS
ParserOptions -> String
(Int -> ParserOptions -> ShowS)
-> (ParserOptions -> String)
-> ([ParserOptions] -> ShowS)
-> Show ParserOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParserOptions] -> ShowS
$cshowList :: [ParserOptions] -> ShowS
show :: ParserOptions -> String
$cshow :: ParserOptions -> String
showsPrec :: Int -> ParserOptions -> ShowS
$cshowsPrec :: Int -> ParserOptions -> ShowS
Show, ParserOptions -> ParserOptions -> Bool
(ParserOptions -> ParserOptions -> Bool)
-> (ParserOptions -> ParserOptions -> Bool) -> Eq ParserOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParserOptions -> ParserOptions -> Bool
$c/= :: ParserOptions -> ParserOptions -> Bool
== :: ParserOptions -> ParserOptions -> Bool
$c== :: ParserOptions -> ParserOptions -> Bool
Eq)

-- | Where a contract or value in Michelson comes from.
data MichelsonSource
  -- | From given file.
  = MSFile FilePath
  -- | Only source name is known.
  | MSName Text
  -- | Defined in Haskell code.
  | MSCode SrcLoc
  -- | Some unknown source.
  | MSUnspecified
  deriving stock (Int -> MichelsonSource -> ShowS
[MichelsonSource] -> ShowS
MichelsonSource -> String
(Int -> MichelsonSource -> ShowS)
-> (MichelsonSource -> String)
-> ([MichelsonSource] -> ShowS)
-> Show MichelsonSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MichelsonSource] -> ShowS
$cshowList :: [MichelsonSource] -> ShowS
show :: MichelsonSource -> String
$cshow :: MichelsonSource -> String
showsPrec :: Int -> MichelsonSource -> ShowS
$cshowsPrec :: Int -> MichelsonSource -> ShowS
Show, MichelsonSource -> MichelsonSource -> Bool
(MichelsonSource -> MichelsonSource -> Bool)
-> (MichelsonSource -> MichelsonSource -> Bool)
-> Eq MichelsonSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MichelsonSource -> MichelsonSource -> Bool
$c/= :: MichelsonSource -> MichelsonSource -> Bool
== :: MichelsonSource -> MichelsonSource -> Bool
$c== :: MichelsonSource -> MichelsonSource -> Bool
Eq)

-- | Designates @stdin@ source.
pattern MSStdin :: MichelsonSource
pattern $bMSStdin :: MichelsonSource
$mMSStdin :: forall {r}. MichelsonSource -> (Void# -> r) -> (Void# -> r) -> r
MSStdin = MSName "<stdin>"

-- | Designates command line input source.
pattern MSCli :: MichelsonSource
pattern $bMSCli :: MichelsonSource
$mMSCli :: forall {r}. MichelsonSource -> (Void# -> r) -> (Void# -> r) -> r
MSCli = MSName "<cli>"

instance IsString MichelsonSource where
  fromString :: String -> MichelsonSource
fromString = Text -> MichelsonSource
MSName (Text -> MichelsonSource)
-> (String -> Text) -> String -> MichelsonSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString

-- Dunno why these are necessary, hlint behaves weirdly
{-# ANN module ("HLint: ignore Use 'callStack' from Universum" :: Text) #-}
{-# ANN module ("HLint: ignore Use 'getCallStack' from Universum" :: Text) #-}

-- | 'MichelsonSource' that points to the current position.
codeSrc :: HasCallStack => MichelsonSource
codeSrc :: HasCallStack => MichelsonSource
codeSrc = SrcLoc -> MichelsonSource
MSCode (SrcLoc -> MichelsonSource) -> SrcLoc -> MichelsonSource
forall a b. (a -> b) -> a -> b
$
  case [(String, SrcLoc)] -> [(String, SrcLoc)]
forall a. [a] -> [a]
reverse (CallStack -> [(String, SrcLoc)]
getCallStack CallStack
HasCallStack => CallStack
callStack) of
    [] -> Text -> SrcLoc
forall a. HasCallStack => Text -> a
error Text
"Unexpectedly empty callstack"
    (String
_funName, SrcLoc
srcLoc) : [(String, SrcLoc)]
_ -> SrcLoc
srcLoc

instance Buildable MichelsonSource where
  build :: MichelsonSource -> Builder
build = \case
    MSFile String
file -> String -> Builder
forall p. Buildable p => p -> Builder
build String
file
    MichelsonSource
MSStdin -> Builder
"<user input>"
    MichelsonSource
MSCli -> Builder
"<user input via CLI>"
    MSName Text
name -> Text -> Builder
forall p. Buildable p => p -> Builder
build Text
name
    MSCode SrcLoc{Int
String
srcLocEndCol :: SrcLoc -> Int
srcLocEndLine :: SrcLoc -> Int
srcLocFile :: SrcLoc -> String
srcLocModule :: SrcLoc -> String
srcLocPackage :: SrcLoc -> String
srcLocStartCol :: SrcLoc -> Int
srcLocStartLine :: SrcLoc -> Int
srcLocEndCol :: Int
srcLocEndLine :: Int
srcLocStartCol :: Int
srcLocStartLine :: Int
srcLocFile :: String
srcLocModule :: String
srcLocPackage :: String
..} ->
      String -> Builder
forall p. Buildable p => p -> Builder
build String
srcLocFile Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
":" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall p. Buildable p => p -> Builder
build Int
srcLocStartLine Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
":" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall p. Buildable p => p -> Builder
build Int
srcLocStartCol
    MichelsonSource
MSUnspecified -> Builder
""