gdritter repos virgil / master Language / Virgil.hs
master

Tree @master (Download .tar.gz)

Virgil.hs @masterraw · history · blame

module Language.Virgil
         ( -- * Virgil Parsers
           decode
         , eitherDecode
         , decodeStrict
         , eitherDecodeStrict
           -- * Re-Exported Aeson Types
           -- ** Core JSON Types
         , Aeson.Value(..)
         , Aeson.Array
         , Aeson.Object
           -- ** Type Conversion
         , Aeson.FromJSON(..)
         , Aeson.ToJSON(..)
         , Aeson.Result(..)
         , Aeson.fromJSON
           -- ** Inspecting Values
         , Aeson.withObject
         , Aeson.withText
         , Aeson.withArray
         , Aeson.withScientific
         , Aeson.withBool
           -- ** Accessors
         , (Aeson..:)
         , (Aeson..:?)
         , (Aeson..:!)
         , (Aeson..!=)
         ) where

import           Data.Aeson (FromJSON, Result(..), fromJSON)
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as BSE
import           Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy.Char8 as BS
import           Language.Virgil.AST (ChValue)
import           Language.Virgil.Eval
import           Language.Virgil.Lexer
import           Language.Virgil.Parser

parseVirgil :: ByteString -> Either String ChValue
parseVirgil = runAlex' parse "<input>" . BS.unpack

-- | Deserialize and execute a Virgil program. If parsing fails,
--   or if type-checking fails, or if the execution of the Virgil
--   program otherwise fails at runtime, then this function will
--   return 'Nothing'.
--
--   Note that Virgil rules out recursive programs, so executing a
--   Virgil program won't loop forever---but it may still take
--   a fair amount longer than parsing the equivalent JSON!
decode :: FromJSON a => ByteString -> Maybe a
decode bs = case eitherDecode bs of
  Error err   -> Nothing
  Success val -> pure val

-- | Deserialize and execute a Virgil program. If parsing fails,
--   or if type-checking fails, or if the execution of the Virgil
--   program otherwise fails at runtime, then this function will
--   return an approrpriately informative error message.
eitherDecode :: FromJSON a => ByteString -> Result a
eitherDecode bs = case parseVirgil bs of
  Left err -> Error err
  Right ch -> case evalCh ch of
    Left err -> Error err
    Right v -> fromJSON v

decodeStrict :: FromJSON a => BSE.ByteString -> Maybe a
decodeStrict = decode . BS.fromStrict

eitherDecodeStrict :: FromJSON a => BSE.ByteString -> Result a
eitherDecodeStrict = eitherDecode . BS.fromStrict