morley-0.3.0.1: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Text

Contents

Description

Strings compliant with Michelson constraints.

When writting a Michelson contract, you can only mention characters with codes from [32 .. 126] range in string literals. Same restriction applies to string literals passed to alphanet.sh.

However, Michelson allows some control sequences: "n". You have to write it exactly in this form, and internally it will be transformed to line feed character (this behaviour can be observed when looking at Packed data).

See tests for examples of good and bad strings.

Synopsis

Documentation

newtype MText Source #

Michelson string value.

This is basically a mere text with limits imposed by the language: http://tezos.gitlab.io/zeronet/whitedoc/michelson.html#constants Although, this document seems to be not fully correct, and thus we applied constraints deduced empirically.

You construct an item of this type using one of the following ways:

  • With QuasyQuotes when need to create a string literal.
>>> [mt|Some text|]
MTextUnsafe { unMText = "Some text" }
  • With mkMText when constructing from a runtime text value.
  • With mkMTextUnsafe or MTextUnsafe when absolutelly sure that given string does not violate invariants.
  • With mkMTextCut when not sure about text contents and want to make it compliant with Michelson constraints.

Constructors

MTextUnsafe 

Fields

Instances
Eq MText Source # 
Instance details

Defined in Michelson.Text

Methods

(==) :: MText -> MText -> Bool #

(/=) :: MText -> MText -> Bool #

Data MText Source # 
Instance details

Defined in Michelson.Text

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MText -> c MText #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MText #

toConstr :: MText -> Constr #

dataTypeOf :: MText -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MText) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MText) #

gmapT :: (forall b. Data b => b -> b) -> MText -> MText #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MText -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MText -> r #

gmapQ :: (forall d. Data d => d -> u) -> MText -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MText -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MText -> m MText #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MText -> m MText #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MText -> m MText #

Ord MText Source # 
Instance details

Defined in Michelson.Text

Methods

compare :: MText -> MText -> Ordering #

(<) :: MText -> MText -> Bool #

(<=) :: MText -> MText -> Bool #

(>) :: MText -> MText -> Bool #

(>=) :: MText -> MText -> Bool #

max :: MText -> MText -> MText #

min :: MText -> MText -> MText #

Show MText Source # 
Instance details

Defined in Michelson.Text

Methods

showsPrec :: Int -> MText -> ShowS #

show :: MText -> String #

showList :: [MText] -> ShowS #

(TypeError (Text "There is no instance defined for (IsString MText)" :$$: Text "Consider using QuasiQuotes: `[mt|some text...|]`") :: Constraint) => IsString MText Source # 
Instance details

Defined in Michelson.Text

Methods

fromString :: String -> MText #

Semigroup MText Source # 
Instance details

Defined in Michelson.Text

Methods

(<>) :: MText -> MText -> MText #

sconcat :: NonEmpty MText -> MText #

stimes :: Integral b => b -> MText -> MText #

Monoid MText Source # 
Instance details

Defined in Michelson.Text

Methods

mempty :: MText #

mappend :: MText -> MText -> MText #

mconcat :: [MText] -> MText #

Arbitrary MText Source # 
Instance details

Defined in Michelson.Text

Methods

arbitrary :: Gen MText #

shrink :: MText -> [MText] #

ToJSON MText Source # 
Instance details

Defined in Michelson.Text

FromJSON MText Source # 
Instance details

Defined in Michelson.Text

Buildable MText Source # 
Instance details

Defined in Michelson.Text

Methods

build :: MText -> Builder #

Container MText Source # 
Instance details

Defined in Michelson.Text

Associated Types

type Element MText :: Type #

Methods

toList :: MText -> [Element MText] #

null :: MText -> Bool #

foldr :: (Element MText -> b -> b) -> b -> MText -> b #

foldl :: (b -> Element MText -> b) -> b -> MText -> b #

foldl' :: (b -> Element MText -> b) -> b -> MText -> b #

length :: MText -> Int #

elem :: Element MText -> MText -> Bool #

maximum :: MText -> Element MText #

minimum :: MText -> Element MText #

foldMap :: Monoid m => (Element MText -> m) -> MText -> m #

fold :: MText -> Element MText #

foldr' :: (Element MText -> b -> b) -> b -> MText -> b #

foldr1 :: (Element MText -> Element MText -> Element MText) -> MText -> Element MText #

foldl1 :: (Element MText -> Element MText -> Element MText) -> MText -> Element MText #

notElem :: Element MText -> MText -> Bool #

all :: (Element MText -> Bool) -> MText -> Bool #

any :: (Element MText -> Bool) -> MText -> Bool #

and :: MText -> Bool #

or :: MText -> Bool #

find :: (Element MText -> Bool) -> MText -> Maybe (Element MText) #

safeHead :: MText -> Maybe (Element MText) #

ToText MText Source # 
Instance details

Defined in Michelson.Text

Methods

toText :: MText -> Text #

IsoValue MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T Source #

IsoCValue MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT MText :: CT Source #

SliceOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

ConcatOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

SizeOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

ArithOpHs Compare MText MText Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare MText MText :: Type Source #

type Element MText Source # 
Instance details

Defined in Michelson.Text

type ToT MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT MText = Tc (ToCT MText)
type ToCT MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ArithResHs Compare MText MText Source # 
Instance details

Defined in Lorentz.Arith

mkMText :: Text -> Either Text MText Source #

Wrap a Haskell text into MText, performing necessary checks.

You can use e.g. '\n' character directly in supplied argument, but attempt to use other bad characters like '\r' will cause failure.

mkMTextUnsafe :: HasCallStack => Text -> MText Source #

Contruct MText from a Haskell text, failing if provided Haskell text is invalid Michelson string.

mkMTextCut :: Text -> MText Source #

Construct MText from a Haskell text, eliminating all characters which should not appear in Michelson strings. Characters which can be displayed normally via escaping are preserved.

writeMText :: MText -> Text Source #

Print MText for Michelson code, with all unusual characters escaped.

isMChar :: Char -> Bool Source #

Constraint on literals appearing in Michelson contract code.

Misc

qqMText :: String -> Either Text String Source #

Parser used in mt quasi quoter.

mt :: QuasiQuoter Source #

QuasyQuoter for constructing Michelson strings.

Validity of result will be checked at compile time. Note:

  • slash must be escaped
  • newline character must appear as '\n'
  • use quotes as is
  • other special characters are not allowed.

type family DoNotUseTextError where ... Source #

A type error asking to use MText instead of ErrorMessage.

Equations

DoNotUseTextError = TypeError (Text "`Text` is not isomorphic to Michelson strings," :$$: Text "consider using `MText` type instead")