module Michelson.Printer
( RenderDoc(..)
, printDoc
, printUntypedContract
, printTypedContractCode
, printTypedContract
, printSomeContract
, printTypedValue
, printUntypedValue
) where
import Data.Constraint (withDict)
import Data.Singletons (SingI)
import qualified Data.Text.Lazy as TL
import Michelson.Printer.Util (RenderDoc(..), doesntNeedParens, printDoc)
import Michelson.TypeCheck.Types (SomeContract(..))
import qualified Michelson.Typed as T
import qualified Michelson.Untyped as U
printUntypedContract :: (RenderDoc op) => Bool -> U.Contract' op -> TL.Text
printUntypedContract :: Bool -> Contract' op -> Text
printUntypedContract forceSingleLine :: Bool
forceSingleLine = Bool -> Doc -> Text
printDoc Bool
forceSingleLine (Doc -> Text) -> (Contract' op -> Doc) -> Contract' op -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderContext -> Contract' op -> Doc
forall a. RenderDoc a => RenderContext -> a -> Doc
renderDoc RenderContext
doesntNeedParens
printTypedContractCode :: (SingI p, SingI s) => Bool -> T.ContractCode p s -> TL.Text
printTypedContractCode :: Bool -> ContractCode p s -> Text
printTypedContractCode forceSingleLine :: Bool
forceSingleLine =
Bool -> Contract' ExpandedOp -> Text
forall op. RenderDoc op => Bool -> Contract' op -> Text
printUntypedContract Bool
forceSingleLine (Contract' ExpandedOp -> Text)
-> (ContractCode p s -> Contract' ExpandedOp)
-> ContractCode p s
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContractCode p s -> Contract' ExpandedOp
forall (param :: T) (store :: T).
(SingI param, SingI store) =>
ContractCode param store -> Contract' ExpandedOp
T.convertContractCode
printTypedContract :: Bool -> T.Contract p s -> TL.Text
printTypedContract :: Bool -> Contract p s -> Text
printTypedContract forceSingleLine :: Bool
forceSingleLine fc :: Contract p s
fc@T.Contract{} =
Bool -> Contract' ExpandedOp -> Text
forall op. RenderDoc op => Bool -> Contract' op -> Text
printUntypedContract Bool
forceSingleLine (Contract' ExpandedOp -> Text) -> Contract' ExpandedOp -> Text
forall a b. (a -> b) -> a -> b
$ Contract p s -> Contract' ExpandedOp
forall (param :: T) (store :: T).
(SingI param, SingI store) =>
Contract param store -> Contract' ExpandedOp
T.convertContract Contract p s
fc
printTypedValue
:: forall t.
(T.ProperPrintedValBetterErrors t)
=> Bool -> T.Value t -> TL.Text
printTypedValue :: Bool -> Value t -> Text
printTypedValue forceSingleLine :: Bool
forceSingleLine =
((SingI t, FailOnOperationFound (ContainsOp t))
:- PrintedValScope t)
-> (PrintedValScope t => Value t -> Text) -> Value t -> Text
forall (c :: Constraint) e r. HasDict c e => e -> (c => r) -> r
withDict ((SingI t, FailOnOperationFound (ContainsOp t)) :- PrintedValScope t
forall (t :: T).
ProperPrintedValBetterErrors t :- PrintedValScope t
T.properPrintedValEvi @t) ((PrintedValScope t => Value t -> Text) -> Value t -> Text)
-> (PrintedValScope t => Value t -> Text) -> Value t -> Text
forall a b. (a -> b) -> a -> b
$
Bool -> Value' ExpandedOp -> Text
forall op. RenderDoc op => Bool -> Value' op -> Text
printUntypedValue Bool
forceSingleLine (Value' ExpandedOp -> Text)
-> (Value t -> Value' ExpandedOp) -> Value t -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value t -> Value' ExpandedOp
forall (t :: T).
(SingI t, HasNoOp t) =>
Value' Instr t -> Value' ExpandedOp
T.untypeValue
printUntypedValue :: (RenderDoc op) => Bool -> U.Value' op -> TL.Text
printUntypedValue :: Bool -> Value' op -> Text
printUntypedValue forceSingleLine :: Bool
forceSingleLine =
Bool -> Doc -> Text
printDoc Bool
forceSingleLine (Doc -> Text) -> (Value' op -> Doc) -> Value' op -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderContext -> Value' op -> Doc
forall a. RenderDoc a => RenderContext -> a -> Doc
renderDoc RenderContext
doesntNeedParens
printSomeContract :: Bool -> SomeContract -> TL.Text
printSomeContract :: Bool -> SomeContract -> Text
printSomeContract forceSingleLine :: Bool
forceSingleLine (SomeContract fc :: Contract cp st
fc) =
Bool -> Contract cp st -> Text
forall (p :: T) (s :: T). Bool -> Contract p s -> Text
printTypedContract Bool
forceSingleLine Contract cp st
fc