{-# LANGUAGE OverloadedStrings #-}

-- | Megaparsec-based parser for 'Value's in the textual value format.
-- The difference between this and the reader defined in
-- "Futhark.Data.Reader" is that we don't try to handle both the
-- textual and binary format - only the former.  On the other hand,
-- this parser has (much) better error messages and can be easily used
-- by other parsers (like the ones for FutharkScript or test blocks).
module Futhark.Data.Parser
  ( parsePrimType,
    parseType,
    parsePrimValue,
    parseValue,
  )
where

import Control.Monad (unless)
import Data.Char (digitToInt, isDigit, isHexDigit)
import Data.Functor
import qualified Data.Scientific as Sci
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Vector.Storable as SVec
import Data.Void
import Futhark.Data
import Text.Megaparsec
import Text.Megaparsec.Char (char)
import Text.Megaparsec.Char.Lexer (charLiteral, signed)
import Prelude hiding (exponent)

-- | Parse the name of a primitive type.  Does *not* consume any
-- trailing whitespace, nor does it permit any internal whitespace.
parsePrimType :: Parsec Void T.Text PrimType
parsePrimType :: Parsec Void Text PrimType
parsePrimType =
  forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
    [ ParsecT Void Text Identity Text
"i8" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
I8,
      ParsecT Void Text Identity Text
"i16" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
I16,
      ParsecT Void Text Identity Text
"i32" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
I32,
      ParsecT Void Text Identity Text
"i64" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
I64,
      ParsecT Void Text Identity Text
"u8" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
U8,
      ParsecT Void Text Identity Text
"u16" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
U16,
      ParsecT Void Text Identity Text
"u32" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
U32,
      ParsecT Void Text Identity Text
"u64" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
U64,
      ParsecT Void Text Identity Text
"f16" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
F16,
      ParsecT Void Text Identity Text
"f32" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
F32,
      ParsecT Void Text Identity Text
"f64" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
F64,
      ParsecT Void Text Identity Text
"bool" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PrimType
Bool
    ]

allowUnderscores :: String -> (Char -> Bool) -> Parsec Void T.Text T.Text
allowUnderscores :: String -> (Char -> Bool) -> ParsecT Void Text Identity Text
allowUnderscores String
desc Char -> Bool
p =
  (Char -> Bool) -> Text -> Text
T.filter (forall a. Eq a => a -> a -> Bool
/= Char
'_')
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ( forall a. Semigroup a => a -> a -> a
(<>)
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P (forall a. a -> Maybe a
Just String
desc) Char -> Bool
p
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP (forall a. a -> Maybe a
Just String
descOrUnderscore) Char -> Bool
pOrUnderscore
        )
  where
    descOrUnderscore :: String
descOrUnderscore = String
desc forall a. Semigroup a => a -> a -> a
<> String
" or underscore"
    pOrUnderscore :: Char -> Bool
pOrUnderscore Char
c = Char -> Bool
p Char
c Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'_'

-- Adapted from megaparsec.
decimal :: Num a => Parsec Void T.Text a
decimal :: forall a. Num a => Parsec Void Text a
decimal =
  Text -> a
mkNum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> (Char -> Bool) -> ParsecT Void Text Identity Text
allowUnderscores String
"digit" Char -> Bool
isDigit
  where
    mkNum :: Text -> a
mkNum = forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' forall {a}. Num a => a -> Char -> a
step a
0
    step :: a -> Char -> a
step a
a Char
c = a
a forall a. Num a => a -> a -> a
* a
10 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
digitToInt Char
c)

-- Adapted from megaparsec.
binary :: Num a => Parsec Void T.Text a
binary :: forall a. Num a => Parsec Void Text a
binary =
  Text -> a
mkNum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> (Char -> Bool) -> ParsecT Void Text Identity Text
allowUnderscores String
"binary digit" Char -> Bool
isBinDigit
  where
    mkNum :: Text -> a
mkNum = forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' forall {a}. Num a => a -> Char -> a
step a
0
    step :: a -> Char -> a
step a
a Char
c = a
a forall a. Num a => a -> a -> a
* a
2 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
digitToInt Char
c)
    isBinDigit :: Char -> Bool
isBinDigit Char
x = Char
x forall a. Eq a => a -> a -> Bool
== Char
'0' Bool -> Bool -> Bool
|| Char
x forall a. Eq a => a -> a -> Bool
== Char
'1'

-- Adapted from megaparsec.
hexadecimal :: Num a => Parsec Void T.Text a
hexadecimal :: forall a. Num a => Parsec Void Text a
hexadecimal =
  Text -> a
mkNum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> (Char -> Bool) -> ParsecT Void Text Identity Text
allowUnderscores String
"hexadecimal digit" Char -> Bool
isHexDigit
  where
    mkNum :: Text -> a
mkNum = forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' forall {a}. Num a => a -> Char -> a
step a
0
    step :: a -> Char -> a
step a
a Char
c = a
a forall a. Num a => a -> a -> a
* a
16 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
digitToInt Char
c)

parseInteger :: Parsec Void T.Text Integer
parseInteger :: Parsec Void Text Integer
parseInteger =
  forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m () -> m a -> m a
signed (forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
      [ ParsecT Void Text Identity Text
"0b" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall a. Num a => Parsec Void Text a
binary,
        ParsecT Void Text Identity Text
"0x" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall a. Num a => Parsec Void Text a
hexadecimal,
        forall a. Num a => Parsec Void Text a
decimal
      ]

scalar :: SVec.Storable a => (Vector Int -> Vector a -> Value) -> a -> Value
scalar :: forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector a -> Value
f a
x = Vector Int -> Vector a -> Value
f forall a. Monoid a => a
mempty (forall a. Storable a => a -> Vector a
SVec.singleton a
x)

parseIntConst :: Parsec Void T.Text Value
parseIntConst :: Parsec Void Text Value
parseIntConst = do
  Integer
x <- Parsec Void Text Integer
parseInteger
  forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice [ParsecT Void Text Identity Text
"f16", ParsecT Void Text Identity Text
"f32", ParsecT Void Text Identity Text
"f64", ParsecT Void Text Identity Text
".", ParsecT Void Text Identity Text
"e"]
  forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
    [ forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Int8 -> Value
I8Value Integer
x ParsecT Void Text Identity Text
"i8",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Int16 -> Value
I16Value Integer
x ParsecT Void Text Identity Text
"i16",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Int32 -> Value
I32Value Integer
x ParsecT Void Text Identity Text
"i32",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Int64 -> Value
I64Value Integer
x ParsecT Void Text Identity Text
"i64",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Word8 -> Value
U8Value Integer
x ParsecT Void Text Identity Text
"u8",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Word16 -> Value
U16Value Integer
x ParsecT Void Text Identity Text
"u16",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Word32 -> Value
U32Value Integer
x ParsecT Void Text Identity Text
"u32",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Word64 -> Value
U64Value Integer
x ParsecT Void Text Identity Text
"u64",
      forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Num a) =>
(Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector Int32 -> Value
I32Value Integer
x ParsecT Void Text Identity Text
""
    ]
  where
    intV :: (Vector Int -> Vector a -> Value) -> Integer -> f a -> f Value
intV Vector Int -> Vector a -> Value
mk Integer
x f a
suffix =
      f a
suffix forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector a -> Value
mk (forall a. Num a => Integer -> a
fromInteger Integer
x)

-- Adapted from megaparsec.
float :: RealFloat a => Parsec Void T.Text a
float :: forall a. RealFloat a => Parsec Void Text a
float = do
  Integer
c' <- forall a. Num a => Parsec Void Text a
decimal
  forall a. RealFloat a => Scientific -> a
Sci.toRealFloat
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ( ( do
              (Integer
c, Int
e') <- forall {p} {b}.
(Num p, Num b) =>
p -> ParsecT Void Text Identity (p, b)
dotDecimal Integer
c'
              Int
e <- forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option Int
e' forall a b. (a -> b) -> a -> b
$ forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a b. (a -> b) -> a -> b
$ forall {b}. Num b => b -> ParsecT Void Text Identity b
exponent Int
e'
              forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Scientific
Sci.scientific Integer
c Int
e
          )
            forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Integer -> Int -> Scientific
Sci.scientific Integer
c' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {b}. Num b => b -> ParsecT Void Text Identity b
exponent Int
0)
        )
  where
    exponent :: b -> ParsecT Void Text Identity b
exponent b
e' = do
      forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice [ParsecT Void Text Identity Text
"e", ParsecT Void Text Identity Text
"E"]
      (forall a. Num a => a -> a -> a
+ b
e') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m () -> m a -> m a
signed (forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) forall a. Num a => Parsec Void Text a
decimal
    dotDecimal :: p -> ParsecT Void Text Identity (p, b)
dotDecimal p
c' = do
      forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Void Text Identity Text
"."
      Text -> (p, b)
mkNum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> (Char -> Bool) -> ParsecT Void Text Identity Text
allowUnderscores String
"digit" Char -> Bool
isDigit
      where
        mkNum :: Text -> (p, b)
mkNum = forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' forall {a} {b}. (Num a, Num b) => (a, b) -> Char -> (a, b)
step (p
c', b
0)
        step :: (a, b) -> Char -> (a, b)
step (a
a, b
e') Char
c =
          (a
a forall a. Num a => a -> a -> a
* a
10 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
digitToInt Char
c), b
e' forall a. Num a => a -> a -> a
- b
1)

parseFloatConst :: Parsec Void T.Text Value
parseFloatConst :: Parsec Void Text Value
parseFloatConst =
  forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
    [ ParsecT Void Text Identity Text
"f16.nan" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Half -> Value
F16Value (Half
0 forall a. Fractional a => a -> a -> a
/ Half
0),
      ParsecT Void Text Identity Text
"f32.nan" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Float -> Value
F32Value (Float
0 forall a. Fractional a => a -> a -> a
/ Float
0),
      ParsecT Void Text Identity Text
"f64.nan" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Double -> Value
F64Value (Double
0 forall a. Fractional a => a -> a -> a
/ Double
0),
      --
      ParsecT Void Text Identity Text
"f16.inf" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Half -> Value
F16Value (Half
1 forall a. Fractional a => a -> a -> a
/ Half
0),
      ParsecT Void Text Identity Text
"f32.inf" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Float -> Value
F32Value (Float
1 forall a. Fractional a => a -> a -> a
/ Float
0),
      ParsecT Void Text Identity Text
"f64.inf" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Double -> Value
F64Value (Double
1 forall a. Fractional a => a -> a -> a
/ Double
0),
      --
      ParsecT Void Text Identity Text
"-f16.inf" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Half -> Value
F16Value (-Half
1 forall a. Fractional a => a -> a -> a
/ Half
0),
      ParsecT Void Text Identity Text
"-f32.inf" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Float -> Value
F32Value (-Float
1 forall a. Fractional a => a -> a -> a
/ Float
0),
      ParsecT Void Text Identity Text
"-f64.inf" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector Double -> Value
F64Value (-Double
1 forall a. Fractional a => a -> a -> a
/ Double
0),
      Parsec Void Text Value
numeric
    ]
  where
    numeric :: Parsec Void Text Value
numeric = do
      Double
x <-
        forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m () -> m a -> m a
signed (forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice [forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try forall a. RealFloat a => Parsec Void Text a
float, forall a. Num a => Integer -> a
fromInteger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Num a => Parsec Void Text a
decimal]
      forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
        [ forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Fractional a) =>
(Vector Int -> Vector a -> Value) -> Double -> f a -> f Value
floatV Vector Int -> Vector Half -> Value
F16Value Double
x ParsecT Void Text Identity Text
"f16",
          forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Fractional a) =>
(Vector Int -> Vector a -> Value) -> Double -> f a -> f Value
floatV Vector Int -> Vector Float -> Value
F32Value Double
x ParsecT Void Text Identity Text
"f32",
          forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Fractional a) =>
(Vector Int -> Vector a -> Value) -> Double -> f a -> f Value
floatV Vector Int -> Vector Double -> Value
F64Value Double
x ParsecT Void Text Identity Text
"f64",
          forall {f :: * -> *} {a} {a}.
(Functor f, Storable a, Fractional a) =>
(Vector Int -> Vector a -> Value) -> Double -> f a -> f Value
floatV Vector Int -> Vector Double -> Value
F64Value Double
x ParsecT Void Text Identity Text
""
        ]

    floatV :: (Vector Int -> Vector a -> Value) -> Double -> f a -> f Value
floatV Vector Int -> Vector a -> Value
mk Double
x f a
suffix =
      f a
suffix forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> forall a.
Storable a =>
(Vector Int -> Vector a -> Value) -> a -> Value
scalar Vector Int -> Vector a -> Value
mk (forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double
x :: Double))

-- | Parse a primitive value.  Does *not* consume any trailing
-- whitespace, nor does it permit any internal whitespace.
parsePrimValue :: Parsec Void T.Text Value
parsePrimValue :: Parsec Void Text Value
parsePrimValue =
  forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
    [ forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parsec Void Text Value
parseIntConst,
      Parsec Void Text Value
parseFloatConst,
      ParsecT Void Text Identity Text
"true" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Vector Int -> Vector Bool -> Value
BoolValue forall a. Monoid a => a
mempty (forall a. Storable a => a -> Vector a
SVec.singleton Bool
True),
      ParsecT Void Text Identity Text
"false" forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Vector Int -> Vector Bool -> Value
BoolValue forall a. Monoid a => a
mempty (forall a. Storable a => a -> Vector a
SVec.singleton Bool
False)
    ]

parseStringConst :: Parsec Void T.Text Value
parseStringConst :: Parsec Void Text Value
parseStringConst =
  forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'"' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (forall t. PutValue1 t => t -> Value
putValue1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a end. MonadPlus m => m a -> m end -> m [a]
manyTill forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m Char
charLiteral (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'"'))

lexeme :: Parsec Void T.Text () -> Parsec Void T.Text a -> Parsec Void T.Text a
lexeme :: forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
lexeme ParsecT Void Text Identity ()
sep Parsec Void Text a
p = Parsec Void Text a
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity ()
sep

inBrackets :: Parsec Void T.Text () -> Parsec Void T.Text a -> Parsec Void T.Text a
inBrackets :: forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
inBrackets ParsecT Void Text Identity ()
sep = forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
lexeme ParsecT Void Text Identity ()
sep ParsecT Void Text Identity Text
"[") (forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
lexeme ParsecT Void Text Identity ()
sep ParsecT Void Text Identity Text
"]")

-- | Parse a type.  Does *not* consume any trailing whitespace, nor
-- does it permit any internal whitespace.
parseType :: Parsec Void T.Text ValueType
parseType :: Parsec Void Text ValueType
parseType = [Int] -> PrimType -> ValueType
ValueType forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ParsecT Void Text Identity Int
parseDim forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parsec Void Text PrimType
parsePrimType
  where
    parseDim :: ParsecT Void Text Identity Int
parseDim = forall a. Num a => Integer -> a
fromInteger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Void Text Identity Text
"[" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec Void Text Integer
parseInteger forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
"]")

parseEmpty :: Parsec Void T.Text Value
parseEmpty :: Parsec Void Text Value
parseEmpty = do
  ValueType [Int]
dims PrimType
t <- Parsec Void Text ValueType
parseType
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [Int]
dims forall a. Eq a => a -> a -> Bool
== Int
0) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected at least one empty dimension"
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case PrimType
t of
    PrimType
I8 -> Vector Int -> Vector Int8 -> Value
I8Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
I16 -> Vector Int -> Vector Int16 -> Value
I16Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
I32 -> Vector Int -> Vector Int32 -> Value
I32Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
I64 -> Vector Int -> Vector Int64 -> Value
I64Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
U8 -> Vector Int -> Vector Word8 -> Value
U8Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
U16 -> Vector Int -> Vector Word16 -> Value
U16Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
U32 -> Vector Int -> Vector Word32 -> Value
U32Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
U64 -> Vector Int -> Vector Word64 -> Value
U64Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
F16 -> Vector Int -> Vector Half -> Value
F16Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
F32 -> Vector Int -> Vector Float -> Value
F32Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
F64 -> Vector Int -> Vector Double -> Value
F64Value (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty
    PrimType
Bool -> Vector Int -> Vector Bool -> Value
BoolValue (forall a. Storable a => [a] -> Vector a
SVec.fromList [Int]
dims) forall a. Monoid a => a
mempty

-- | Parse a value, given a post-lexeme parser for whitespace.
parseValue :: Parsec Void T.Text () -> Parsec Void T.Text Value
parseValue :: ParsecT Void Text Identity () -> Parsec Void Text Value
parseValue ParsecT Void Text Identity ()
sep =
  forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
    [ forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
lexeme ParsecT Void Text Identity ()
sep Parsec Void Text Value
parsePrimValue,
      forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
lexeme ParsecT Void Text Identity ()
sep Parsec Void Text Value
parseStringConst,
      forall v.
PutValue v =>
Parsec Void Text v -> Parsec Void Text Value
putValue' forall a b. (a -> b) -> a -> b
$ forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
inBrackets ParsecT Void Text Identity ()
sep (ParsecT Void Text Identity () -> Parsec Void Text Value
parseValue ParsecT Void Text Identity ()
sep forall (m :: * -> *) a end. MonadPlus m => m a -> m end -> m [a]
`sepBy` forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
lexeme ParsecT Void Text Identity ()
sep ParsecT Void Text Identity Text
","),
      forall a.
ParsecT Void Text Identity ()
-> Parsec Void Text a -> Parsec Void Text a
lexeme ParsecT Void Text Identity ()
sep forall a b. (a -> b) -> a -> b
$ ParsecT Void Text Identity Text
"empty(" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec Void Text Value
parseEmpty forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
")"
    ]
  where
    putValue' :: PutValue v => Parsec Void T.Text v -> Parsec Void T.Text Value
    putValue' :: forall v.
PutValue v =>
Parsec Void Text v -> Parsec Void Text Value
putValue' Parsec Void Text v
p = do
      Int
o <- forall e s (m :: * -> *). MonadParsec e s m => m Int
getOffset
      v
x <- Parsec Void Text v
p
      case forall t. PutValue t => t -> Maybe Value
putValue v
x of
        Maybe Value
Nothing ->
          forall e s (m :: * -> *) a.
MonadParsec e s m =>
ParseError s e -> m a
parseError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s e. Int -> Set (ErrorFancy e) -> ParseError s e
FancyError Int
o forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Set a
S.singleton forall a b. (a -> b) -> a -> b
$
            forall e. String -> ErrorFancy e
ErrorFail String
"array is irregular or has elements of multiple types."
        Just Value
v ->
          forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
v