{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Futhark.CLI.Literate (main) where
import qualified Codec.BMP as BMP
import Control.Monad.Except
import Control.Monad.State hiding (State)
import Data.Bifunctor (first, second)
import Data.Bits
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import Data.Char
import Data.Functor
import Data.Hashable (hash)
import Data.Int (Int64)
import Data.List (foldl', transpose)
import qualified Data.Map as M
import Data.Maybe
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import qualified Data.Vector.Storable as SVec
import qualified Data.Vector.Storable.ByteString as SVec
import Data.Void
import Data.Word (Word32, Word8)
import Futhark.Script
import Futhark.Server
import Futhark.Test
import Futhark.Test.Values
import Futhark.Util
( directoryContents,
hashIntText,
nubOrd,
runProgramWithExitCode,
)
import Futhark.Util.Options
import Futhark.Util.Pretty (prettyText, prettyTextOneLine)
import qualified Futhark.Util.Pretty as PP
import System.Directory
( copyFile,
createDirectoryIfMissing,
doesFileExist,
removePathForcibly,
)
import System.Environment (getExecutablePath)
import System.Exit
import System.FilePath
import System.IO
import System.IO.Error (isDoesNotExistError)
import System.IO.Temp (withSystemTempDirectory, withSystemTempFile)
import Text.Megaparsec hiding (State, failure, token)
import Text.Megaparsec.Char
import Text.Printf
data VideoParams = VideoParams
{ VideoParams -> Maybe Int
videoFPS :: Maybe Int,
VideoParams -> Maybe Bool
videoLoop :: Maybe Bool,
VideoParams -> Maybe Bool
videoAutoplay :: Maybe Bool,
VideoParams -> Maybe Text
videoFormat :: Maybe T.Text
}
deriving (Int -> VideoParams -> ShowS
[VideoParams] -> ShowS
VideoParams -> String
(Int -> VideoParams -> ShowS)
-> (VideoParams -> String)
-> ([VideoParams] -> ShowS)
-> Show VideoParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoParams] -> ShowS
$cshowList :: [VideoParams] -> ShowS
show :: VideoParams -> String
$cshow :: VideoParams -> String
showsPrec :: Int -> VideoParams -> ShowS
$cshowsPrec :: Int -> VideoParams -> ShowS
Show)
defaultVideoParams :: VideoParams
defaultVideoParams :: VideoParams
defaultVideoParams =
VideoParams :: Maybe Int -> Maybe Bool -> Maybe Bool -> Maybe Text -> VideoParams
VideoParams
{ videoFPS :: Maybe Int
videoFPS = Maybe Int
forall a. Maybe a
Nothing,
videoLoop :: Maybe Bool
videoLoop = Maybe Bool
forall a. Maybe a
Nothing,
videoAutoplay :: Maybe Bool
videoAutoplay = Maybe Bool
forall a. Maybe a
Nothing,
videoFormat :: Maybe Text
videoFormat = Maybe Text
forall a. Maybe a
Nothing
}
data Directive
= DirectiveRes Exp
| DirectiveBrief Directive
| DirectiveCovert Directive
| DirectiveImg Exp
| DirectivePlot Exp (Maybe (Int, Int))
| DirectiveGnuplot Exp T.Text
| DirectiveVideo Exp VideoParams
deriving (Int -> Directive -> ShowS
[Directive] -> ShowS
Directive -> String
(Int -> Directive -> ShowS)
-> (Directive -> String)
-> ([Directive] -> ShowS)
-> Show Directive
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Directive] -> ShowS
$cshowList :: [Directive] -> ShowS
show :: Directive -> String
$cshow :: Directive -> String
showsPrec :: Int -> Directive -> ShowS
$cshowsPrec :: Int -> Directive -> ShowS
Show)
varsInDirective :: Directive -> S.Set EntryName
varsInDirective :: Directive -> Set Text
varsInDirective (DirectiveRes Exp
e) = Exp -> Set Text
varsInExp Exp
e
varsInDirective (DirectiveBrief Directive
d) = Directive -> Set Text
varsInDirective Directive
d
varsInDirective (DirectiveCovert Directive
d) = Directive -> Set Text
varsInDirective Directive
d
varsInDirective (DirectiveImg Exp
e) = Exp -> Set Text
varsInExp Exp
e
varsInDirective (DirectivePlot Exp
e Maybe (Int, Int)
_) = Exp -> Set Text
varsInExp Exp
e
varsInDirective (DirectiveGnuplot Exp
e Text
_) = Exp -> Set Text
varsInExp Exp
e
varsInDirective (DirectiveVideo Exp
e VideoParams
_) = Exp -> Set Text
varsInExp Exp
e
pprDirective :: Bool -> Directive -> PP.Doc
pprDirective :: Bool -> Directive -> Doc
pprDirective Bool
_ (DirectiveRes Exp
e) =
Doc
"> " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
PP.align (Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e)
pprDirective Bool
_ (DirectiveBrief Directive
f) =
Bool -> Directive -> Doc
pprDirective Bool
False Directive
f
pprDirective Bool
_ (DirectiveCovert Directive
f) =
Bool -> Directive -> Doc
pprDirective Bool
False Directive
f
pprDirective Bool
_ (DirectiveImg Exp
e) =
Doc
"> :img " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
PP.align (Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e)
pprDirective Bool
True (DirectivePlot Exp
e (Just (Int
h, Int
w))) =
[Doc] -> Doc
PP.stack
[ Doc
"> :plot2d " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
";",
Doc
"size: (" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Int
w Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"," Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Int -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Int
h Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
")"
]
pprDirective Bool
_ (DirectivePlot Exp
e Maybe (Int, Int)
_) =
Doc
"> :plot2d " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
PP.align (Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e)
pprDirective Bool
True (DirectiveGnuplot Exp
e Text
script) =
[Doc] -> Doc
PP.stack ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
Doc
"> :gnuplot " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
PP.align (Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
";" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
:
(Text -> Doc) -> [Text] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Doc
PP.strictText (Text -> [Text]
T.lines Text
script)
pprDirective Bool
False (DirectiveGnuplot Exp
e Text
_) =
Doc
"> :gnuplot " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
PP.align (Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e)
pprDirective Bool
False (DirectiveVideo Exp
e VideoParams
_) =
Doc
"> :video " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
PP.align (Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e)
pprDirective Bool
True (DirectiveVideo Exp
e VideoParams
params) =
Doc
"> :video " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Exp -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Exp
e
Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> if [Doc] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Doc]
params' then Doc
forall a. Monoid a => a
mempty else [Doc] -> Doc
PP.stack ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
";" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [Doc]
params'
where
params' :: [Doc]
params' =
[Maybe Doc] -> [Doc]
forall a. [Maybe a] -> [a]
catMaybes
[ Doc -> (VideoParams -> Maybe Int) -> (Int -> Doc) -> Maybe Doc
forall b t.
(Semigroup b, IsString b) =>
b -> (VideoParams -> Maybe t) -> (t -> b) -> Maybe b
p Doc
"fps" VideoParams -> Maybe Int
videoFPS Int -> Doc
forall a. Pretty a => a -> Doc
PP.ppr,
Doc -> (VideoParams -> Maybe Bool) -> (Bool -> Doc) -> Maybe Doc
forall b t.
(Semigroup b, IsString b) =>
b -> (VideoParams -> Maybe t) -> (t -> b) -> Maybe b
p Doc
"loop" VideoParams -> Maybe Bool
videoLoop Bool -> Doc
forall p. IsString p => Bool -> p
ppBool,
Doc -> (VideoParams -> Maybe Bool) -> (Bool -> Doc) -> Maybe Doc
forall b t.
(Semigroup b, IsString b) =>
b -> (VideoParams -> Maybe t) -> (t -> b) -> Maybe b
p Doc
"autoplay" VideoParams -> Maybe Bool
videoAutoplay Bool -> Doc
forall p. IsString p => Bool -> p
ppBool,
Doc -> (VideoParams -> Maybe Text) -> (Text -> Doc) -> Maybe Doc
forall b t.
(Semigroup b, IsString b) =>
b -> (VideoParams -> Maybe t) -> (t -> b) -> Maybe b
p Doc
"format" VideoParams -> Maybe Text
videoFormat Text -> Doc
PP.strictText
]
ppBool :: Bool -> p
ppBool Bool
b = if Bool
b then p
"true" else p
"false"
p :: b -> (VideoParams -> Maybe t) -> (t -> b) -> Maybe b
p b
s VideoParams -> Maybe t
f t -> b
ppr = do
t
x <- VideoParams -> Maybe t
f VideoParams
params
b -> Maybe b
forall a. a -> Maybe a
Just (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ b
s b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
": " b -> b -> b
forall a. Semigroup a => a -> a -> a
<> t -> b
ppr t
x
instance PP.Pretty Directive where
ppr :: Directive -> Doc
ppr = Bool -> Directive -> Doc
pprDirective Bool
True
data Block
= BlockCode T.Text
| T.Text
| BlockDirective Directive
deriving (Int -> Block -> ShowS
[Block] -> ShowS
Block -> String
(Int -> Block -> ShowS)
-> (Block -> String) -> ([Block] -> ShowS) -> Show Block
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Block] -> ShowS
$cshowList :: [Block] -> ShowS
show :: Block -> String
$cshow :: Block -> String
showsPrec :: Int -> Block -> ShowS
$cshowsPrec :: Int -> Block -> ShowS
Show)
varsInScripts :: [Block] -> S.Set EntryName
varsInScripts :: [Block] -> Set Text
varsInScripts = (Block -> Set Text) -> [Block] -> Set Text
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Block -> Set Text
varsInBlock
where
varsInBlock :: Block -> Set Text
varsInBlock (BlockDirective Directive
d) = Directive -> Set Text
varsInDirective Directive
d
varsInBlock BlockCode {} = Set Text
forall a. Monoid a => a
mempty
varsInBlock BlockComment {} = Set Text
forall a. Monoid a => a
mempty
type Parser = Parsec Void T.Text
postlexeme :: Parser ()
postlexeme :: Parser ()
postlexeme = ParsecT Void Text Identity (Maybe ()) -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text Identity (Maybe ()) -> Parser ())
-> ParsecT Void Text Identity (Maybe ()) -> Parser ()
forall a b. (a -> b) -> a -> b
$ Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
hspace Parser ()
-> ParsecT Void Text Identity (Maybe ())
-> ParsecT Void Text Identity (Maybe ())
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser () -> ParsecT Void Text Identity (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
"-- " ParsecT Void Text Identity Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser ()
postlexeme)
lexeme :: Parser a -> Parser a
lexeme :: Parser a -> Parser a
lexeme Parser a
p = Parser a
p Parser a -> Parser () -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
postlexeme
token :: T.Text -> Parser ()
token :: Text -> Parser ()
token = ParsecT Void Text Identity Text -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text Identity Text -> Parser ())
-> (Text -> ParsecT Void Text Identity Text) -> Text -> Parser ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Void Text Identity Text -> ParsecT Void Text Identity Text
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text)
-> (Text -> ParsecT Void Text Identity Text)
-> Text
-> ParsecT Void Text Identity Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Void Text Identity Text -> ParsecT Void Text Identity Text
forall a. Parser a -> Parser a
lexeme (ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text)
-> (Text -> ParsecT Void Text Identity Text)
-> Text
-> ParsecT Void Text Identity Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ParsecT Void Text Identity Text
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string
parseInt :: Parser Int
parseInt :: Parser Int
parseInt = Parser Int -> Parser Int
forall a. Parser a -> Parser a
lexeme (Parser Int -> Parser Int) -> Parser Int -> Parser Int
forall a b. (a -> b) -> a -> b
$ String -> Int
forall a. Read a => String -> a
read (String -> Int) -> ParsecT Void Text Identity String -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ((Token Text -> Bool) -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy Char -> Bool
Token Text -> Bool
isDigit)
restOfLine :: Parser T.Text
restOfLine :: ParsecT Void Text Identity Text
restOfLine = Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP Maybe String
forall a. Maybe a
Nothing (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n') ParsecT Void Text Identity Text
-> Parser () -> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (ParsecT Void Text Identity Text -> Parser ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol Parser () -> Parser () -> Parser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof)
parseBlockComment :: Parser T.Text
= [Text] -> Text
T.unlines ([Text] -> Text)
-> ParsecT Void Text Identity [Text]
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity [Text]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ParsecT Void Text Identity Text
line
where
line :: ParsecT Void Text Identity Text
line = ParsecT Void Text Identity Text
"--" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (Maybe Text)
-> ParsecT Void Text Identity (Maybe Text)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT Void Text Identity Text
" " ParsecT Void Text Identity (Maybe Text)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
restOfLine
parseTestBlock :: Parser T.Text
parseTestBlock :: ParsecT Void Text Identity Text
parseTestBlock =
[Text] -> Text
T.unlines ([Text] -> Text)
-> ParsecT Void Text Identity [Text]
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((:) (Text -> [Text] -> [Text])
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity ([Text] -> [Text])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
header ParsecT Void Text Identity ([Text] -> [Text])
-> ParsecT Void Text Identity [Text]
-> ParsecT Void Text Identity [Text]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Void Text Identity [Text]
remainder)
where
header :: ParsecT Void Text Identity Text
header = ParsecT Void Text Identity Text
"-- ==" ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (Tokens Text)
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol
remainder :: ParsecT Void Text Identity [Text]
remainder = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text
"-- " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines (Text -> [Text])
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
parseBlockComment
parseBlockCode :: Parser T.Text
parseBlockCode :: ParsecT Void Text Identity Text
parseBlockCode = [Text] -> Text
T.unlines ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
noblanks ([Text] -> Text)
-> ParsecT Void Text Identity [Text]
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity [Text]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ParsecT Void Text Identity Text
line
where
noblanks :: [Text] -> [Text]
noblanks = [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> ([Text] -> [Text]) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Text -> Bool
T.null ([Text] -> [Text]) -> ([Text] -> [Text]) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> ([Text] -> [Text]) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Text -> Bool
T.null
line :: ParsecT Void Text Identity Text
line = Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT Void Text Identity Text -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy ParsecT Void Text Identity Text
"--") Parser () -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof Parser ()
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
restOfLine
parsePlotParams :: Parser (Maybe (Int, Int))
parsePlotParams :: Parser (Maybe (Int, Int))
parsePlotParams =
ParsecT Void Text Identity (Int, Int) -> Parser (Maybe (Int, Int))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT Void Text Identity (Int, Int)
-> Parser (Maybe (Int, Int)))
-> ParsecT Void Text Identity (Int, Int)
-> Parser (Maybe (Int, Int))
forall a b. (a -> b) -> a -> b
$
ParsecT Void Text Identity Text
";" ParsecT Void Text Identity Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
hspace Parser ()
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol ParsecT Void Text Identity Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> Parser ()
token Text
"-- size:"
Parser () -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> Parser ()
token Text
"("
Parser ()
-> ParsecT Void Text Identity (Int, Int)
-> ParsecT Void Text Identity (Int, Int)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ((,) (Int -> Int -> (Int, Int))
-> Parser Int -> ParsecT Void Text Identity (Int -> (Int, Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Int
parseInt ParsecT Void Text Identity (Int -> (Int, Int))
-> Parser () -> ParsecT Void Text Identity (Int -> (Int, Int))
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> Parser ()
token Text
"," ParsecT Void Text Identity (Int -> (Int, Int))
-> Parser Int -> ParsecT Void Text Identity (Int, Int)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int
parseInt) ParsecT Void Text Identity (Int, Int)
-> Parser () -> ParsecT Void Text Identity (Int, Int)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> Parser ()
token Text
")"
parseVideoParams :: Parser VideoParams
parseVideoParams :: Parser VideoParams
parseVideoParams =
(Maybe VideoParams -> VideoParams)
-> ParsecT Void Text Identity (Maybe VideoParams)
-> Parser VideoParams
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (VideoParams -> Maybe VideoParams -> VideoParams
forall a. a -> Maybe a -> a
fromMaybe VideoParams
defaultVideoParams) (ParsecT Void Text Identity (Maybe VideoParams)
-> Parser VideoParams)
-> ParsecT Void Text Identity (Maybe VideoParams)
-> Parser VideoParams
forall a b. (a -> b) -> a -> b
$
Parser VideoParams
-> ParsecT Void Text Identity (Maybe VideoParams)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser VideoParams
-> ParsecT Void Text Identity (Maybe VideoParams))
-> Parser VideoParams
-> ParsecT Void Text Identity (Maybe VideoParams)
forall a b. (a -> b) -> a -> b
$ ParsecT Void Text Identity Text
";" ParsecT Void Text Identity Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
hspace Parser ()
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
"-- " ParsecT Void Text Identity Text
-> Parser VideoParams -> Parser VideoParams
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> VideoParams -> Parser VideoParams
parseParams VideoParams
defaultVideoParams
where
parseParams :: VideoParams -> Parser VideoParams
parseParams VideoParams
params =
[Parser VideoParams] -> Parser VideoParams
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ [Parser VideoParams] -> Parser VideoParams
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[VideoParams -> Parser VideoParams
pLoop VideoParams
params, VideoParams -> Parser VideoParams
pFPS VideoParams
params, VideoParams -> Parser VideoParams
pAutoplay VideoParams
params, VideoParams -> Parser VideoParams
pFormat VideoParams
params]
Parser VideoParams
-> (VideoParams -> Parser VideoParams) -> Parser VideoParams
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= VideoParams -> Parser VideoParams
parseParams,
VideoParams -> Parser VideoParams
forall (f :: * -> *) a. Applicative f => a -> f a
pure VideoParams
params
]
parseBool :: ParsecT Void Text Identity Bool
parseBool = Text -> Parser ()
token Text
"true" Parser () -> Bool -> ParsecT Void Text Identity Bool
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
True ParsecT Void Text Identity Bool
-> ParsecT Void Text Identity Bool
-> ParsecT Void Text Identity Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser ()
token Text
"false" Parser () -> Bool -> ParsecT Void Text Identity Bool
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
False
pLoop :: VideoParams -> Parser VideoParams
pLoop VideoParams
params = do
Text -> Parser ()
token Text
"loop:"
Bool
b <- ParsecT Void Text Identity Bool
parseBool
VideoParams -> Parser VideoParams
forall (f :: * -> *) a. Applicative f => a -> f a
pure VideoParams
params {videoLoop :: Maybe Bool
videoLoop = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
b}
pFPS :: VideoParams -> Parser VideoParams
pFPS VideoParams
params = do
Text -> Parser ()
token Text
"fps:"
Int
fps <- Parser Int
parseInt
VideoParams -> Parser VideoParams
forall (f :: * -> *) a. Applicative f => a -> f a
pure VideoParams
params {videoFPS :: Maybe Int
videoFPS = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
fps}
pAutoplay :: VideoParams -> Parser VideoParams
pAutoplay VideoParams
params = do
Text -> Parser ()
token Text
"autoplay:"
Bool
b <- ParsecT Void Text Identity Bool
parseBool
VideoParams -> Parser VideoParams
forall (f :: * -> *) a. Applicative f => a -> f a
pure VideoParams
params {videoAutoplay :: Maybe Bool
videoAutoplay = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
b}
pFormat :: VideoParams -> Parser VideoParams
pFormat VideoParams
params = do
Text -> Parser ()
token Text
"format:"
Text
s <- ParsecT Void Text Identity Text -> ParsecT Void Text Identity Text
forall a. Parser a -> Parser a
lexeme (ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall a b. (a -> b) -> a -> b
$ Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhileP Maybe String
forall a. Maybe a
Nothing (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace)
VideoParams -> Parser VideoParams
forall (f :: * -> *) a. Applicative f => a -> f a
pure VideoParams
params {videoFormat :: Maybe Text
videoFormat = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s}
parseBlock :: Parser Block
parseBlock :: Parser Block
parseBlock =
[Parser Block] -> Parser Block
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Text -> Parser ()
token Text
"-- >" Parser ()
-> (Directive -> Block)
-> ParsecT Void Text Identity (Directive -> Block)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Directive -> Block
BlockDirective ParsecT Void Text Identity (Directive -> Block)
-> ParsecT Void Text Identity Directive -> Parser Block
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Void Text Identity Directive
parseDirective,
Text -> Block
BlockCode (Text -> Block) -> ParsecT Void Text Identity Text -> Parser Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
parseTestBlock,
Text -> Block
BlockCode (Text -> Block) -> ParsecT Void Text Identity Text -> Parser Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
parseBlockCode,
Text -> Block
BlockComment (Text -> Block) -> ParsecT Void Text Identity Text -> Parser Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
parseBlockComment
]
where
parseDirective :: ParsecT Void Text Identity Directive
parseDirective =
[ParsecT Void Text Identity Directive]
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ Exp -> Directive
DirectiveRes (Exp -> Directive)
-> ParsecT Void Text Identity Exp
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser () -> ParsecT Void Text Identity Exp
parseExp Parser ()
postlexeme,
Text -> Parser ()
directiveName Text
"covert" Parser ()
-> (Directive -> Directive)
-> ParsecT Void Text Identity (Directive -> Directive)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Directive -> Directive
DirectiveCovert
ParsecT Void Text Identity (Directive -> Directive)
-> ParsecT Void Text Identity Directive
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Void Text Identity Directive
parseDirective,
Text -> Parser ()
directiveName Text
"brief" Parser ()
-> (Directive -> Directive)
-> ParsecT Void Text Identity (Directive -> Directive)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Directive -> Directive
DirectiveBrief
ParsecT Void Text Identity (Directive -> Directive)
-> ParsecT Void Text Identity Directive
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Void Text Identity Directive
parseDirective,
Text -> Parser ()
directiveName Text
"img" Parser ()
-> (Exp -> Directive)
-> ParsecT Void Text Identity (Exp -> Directive)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Exp -> Directive
DirectiveImg
ParsecT Void Text Identity (Exp -> Directive)
-> ParsecT Void Text Identity Exp
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser () -> ParsecT Void Text Identity Exp
parseExp Parser ()
postlexeme ParsecT Void Text Identity Directive
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol,
Text -> Parser ()
directiveName Text
"plot2d" Parser ()
-> (Exp -> Maybe (Int, Int) -> Directive)
-> ParsecT
Void Text Identity (Exp -> Maybe (Int, Int) -> Directive)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Exp -> Maybe (Int, Int) -> Directive
DirectivePlot
ParsecT Void Text Identity (Exp -> Maybe (Int, Int) -> Directive)
-> ParsecT Void Text Identity Exp
-> ParsecT Void Text Identity (Maybe (Int, Int) -> Directive)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser () -> ParsecT Void Text Identity Exp
parseExp Parser ()
postlexeme
ParsecT Void Text Identity (Maybe (Int, Int) -> Directive)
-> Parser (Maybe (Int, Int))
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe (Int, Int))
parsePlotParams ParsecT Void Text Identity Directive
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol,
Text -> Parser ()
directiveName Text
"gnuplot" Parser ()
-> (Exp -> Text -> Directive)
-> ParsecT Void Text Identity (Exp -> Text -> Directive)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Exp -> Text -> Directive
DirectiveGnuplot
ParsecT Void Text Identity (Exp -> Text -> Directive)
-> ParsecT Void Text Identity Exp
-> ParsecT Void Text Identity (Text -> Directive)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser () -> ParsecT Void Text Identity Exp
parseExp Parser ()
postlexeme
ParsecT Void Text Identity (Text -> Directive)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParsecT Void Text Identity Text
";" ParsecT Void Text Identity Text -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser ()
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m ()
hspace Parser ()
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity Text
parseBlockComment),
(Text -> Parser ()
directiveName Text
"video" Parser () -> Parser () -> Parser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser ()
directiveName Text
"video") Parser ()
-> (Exp -> VideoParams -> Directive)
-> ParsecT Void Text Identity (Exp -> VideoParams -> Directive)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Exp -> VideoParams -> Directive
DirectiveVideo
ParsecT Void Text Identity (Exp -> VideoParams -> Directive)
-> ParsecT Void Text Identity Exp
-> ParsecT Void Text Identity (VideoParams -> Directive)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser () -> ParsecT Void Text Identity Exp
parseExp Parser ()
postlexeme
ParsecT Void Text Identity (VideoParams -> Directive)
-> Parser VideoParams -> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser VideoParams
parseVideoParams ParsecT Void Text Identity Directive
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity Directive
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity Text
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Tokens s)
eol
]
directiveName :: Text -> Parser ()
directiveName Text
s = Parser () -> Parser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ Text -> Parser ()
token (Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s)
parseProg :: FilePath -> T.Text -> Either T.Text [Block]
parseProg :: String -> Text -> Either Text [Block]
parseProg String
fname Text
s =
(ParseErrorBundle Text Void -> Either Text [Block])
-> ([Block] -> Either Text [Block])
-> Either (ParseErrorBundle Text Void) [Block]
-> Either Text [Block]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Either Text [Block]
forall a b. a -> Either a b
Left (Text -> Either Text [Block])
-> (ParseErrorBundle Text Void -> Text)
-> ParseErrorBundle Text Void
-> Either Text [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text)
-> (ParseErrorBundle Text Void -> String)
-> ParseErrorBundle Text Void
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty) [Block] -> Either Text [Block]
forall a b. b -> Either a b
Right (Either (ParseErrorBundle Text Void) [Block]
-> Either Text [Block])
-> Either (ParseErrorBundle Text Void) [Block]
-> Either Text [Block]
forall a b. (a -> b) -> a -> b
$
Parsec Void Text [Block]
-> String -> Text -> Either (ParseErrorBundle Text Void) [Block]
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
parse (Parser Block -> Parsec Void Text [Block]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many Parser Block
parseBlock Parsec Void Text [Block] -> Parser () -> Parsec Void Text [Block]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof) String
fname Text
s
parseProgFile :: FilePath -> IO [Block]
parseProgFile :: String -> IO [Block]
parseProgFile String
prog = do
Either Text [Block]
pres <- String -> Text -> Either Text [Block]
parseProg String
prog (Text -> Either Text [Block])
-> IO Text -> IO (Either Text [Block])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Text
T.readFile String
prog
case Either Text [Block]
pres of
Left Text
err -> do
Handle -> Text -> IO ()
T.hPutStr Handle
stderr Text
err
IO [Block]
forall a. IO a
exitFailure
Right [Block]
script ->
[Block] -> IO [Block]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Block]
script
type Files = S.Set FilePath
newtype State = State {State -> Files
stateFiles :: Files}
newtype ScriptM a = ScriptM (ExceptT T.Text (StateT State IO) a)
deriving
( a -> ScriptM b -> ScriptM a
(a -> b) -> ScriptM a -> ScriptM b
(forall a b. (a -> b) -> ScriptM a -> ScriptM b)
-> (forall a b. a -> ScriptM b -> ScriptM a) -> Functor ScriptM
forall a b. a -> ScriptM b -> ScriptM a
forall a b. (a -> b) -> ScriptM a -> ScriptM b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ScriptM b -> ScriptM a
$c<$ :: forall a b. a -> ScriptM b -> ScriptM a
fmap :: (a -> b) -> ScriptM a -> ScriptM b
$cfmap :: forall a b. (a -> b) -> ScriptM a -> ScriptM b
Functor,
Functor ScriptM
a -> ScriptM a
Functor ScriptM
-> (forall a. a -> ScriptM a)
-> (forall a b. ScriptM (a -> b) -> ScriptM a -> ScriptM b)
-> (forall a b c.
(a -> b -> c) -> ScriptM a -> ScriptM b -> ScriptM c)
-> (forall a b. ScriptM a -> ScriptM b -> ScriptM b)
-> (forall a b. ScriptM a -> ScriptM b -> ScriptM a)
-> Applicative ScriptM
ScriptM a -> ScriptM b -> ScriptM b
ScriptM a -> ScriptM b -> ScriptM a
ScriptM (a -> b) -> ScriptM a -> ScriptM b
(a -> b -> c) -> ScriptM a -> ScriptM b -> ScriptM c
forall a. a -> ScriptM a
forall a b. ScriptM a -> ScriptM b -> ScriptM a
forall a b. ScriptM a -> ScriptM b -> ScriptM b
forall a b. ScriptM (a -> b) -> ScriptM a -> ScriptM b
forall a b c. (a -> b -> c) -> ScriptM a -> ScriptM b -> ScriptM c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: ScriptM a -> ScriptM b -> ScriptM a
$c<* :: forall a b. ScriptM a -> ScriptM b -> ScriptM a
*> :: ScriptM a -> ScriptM b -> ScriptM b
$c*> :: forall a b. ScriptM a -> ScriptM b -> ScriptM b
liftA2 :: (a -> b -> c) -> ScriptM a -> ScriptM b -> ScriptM c
$cliftA2 :: forall a b c. (a -> b -> c) -> ScriptM a -> ScriptM b -> ScriptM c
<*> :: ScriptM (a -> b) -> ScriptM a -> ScriptM b
$c<*> :: forall a b. ScriptM (a -> b) -> ScriptM a -> ScriptM b
pure :: a -> ScriptM a
$cpure :: forall a. a -> ScriptM a
$cp1Applicative :: Functor ScriptM
Applicative,
Applicative ScriptM
a -> ScriptM a
Applicative ScriptM
-> (forall a b. ScriptM a -> (a -> ScriptM b) -> ScriptM b)
-> (forall a b. ScriptM a -> ScriptM b -> ScriptM b)
-> (forall a. a -> ScriptM a)
-> Monad ScriptM
ScriptM a -> (a -> ScriptM b) -> ScriptM b
ScriptM a -> ScriptM b -> ScriptM b
forall a. a -> ScriptM a
forall a b. ScriptM a -> ScriptM b -> ScriptM b
forall a b. ScriptM a -> (a -> ScriptM b) -> ScriptM b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> ScriptM a
$creturn :: forall a. a -> ScriptM a
>> :: ScriptM a -> ScriptM b -> ScriptM b
$c>> :: forall a b. ScriptM a -> ScriptM b -> ScriptM b
>>= :: ScriptM a -> (a -> ScriptM b) -> ScriptM b
$c>>= :: forall a b. ScriptM a -> (a -> ScriptM b) -> ScriptM b
$cp1Monad :: Applicative ScriptM
Monad,
MonadError T.Text,
Monad ScriptM
Monad ScriptM
-> (forall a. String -> ScriptM a) -> MonadFail ScriptM
String -> ScriptM a
forall a. String -> ScriptM a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> ScriptM a
$cfail :: forall a. String -> ScriptM a
$cp1MonadFail :: Monad ScriptM
MonadFail,
Monad ScriptM
Monad ScriptM -> (forall a. IO a -> ScriptM a) -> MonadIO ScriptM
IO a -> ScriptM a
forall a. IO a -> ScriptM a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> ScriptM a
$cliftIO :: forall a. IO a -> ScriptM a
$cp1MonadIO :: Monad ScriptM
MonadIO,
MonadState State
)
runScriptM :: ScriptM a -> IO (Either T.Text a, Files)
runScriptM :: ScriptM a -> IO (Either Text a, Files)
runScriptM (ScriptM ExceptT Text (StateT State IO) a
m) = (State -> Files)
-> (Either Text a, State) -> (Either Text a, Files)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second State -> Files
stateFiles ((Either Text a, State) -> (Either Text a, Files))
-> IO (Either Text a, State) -> IO (Either Text a, Files)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT State IO (Either Text a)
-> State -> IO (Either Text a, State)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (ExceptT Text (StateT State IO) a -> StateT State IO (Either Text a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT Text (StateT State IO) a
m) State
s
where
s :: State
s = Files -> State
State Files
forall a. Monoid a => a
mempty
withTempFile :: (FilePath -> ScriptM a) -> ScriptM a
withTempFile :: (String -> ScriptM a) -> ScriptM a
withTempFile String -> ScriptM a
f =
ScriptM (ScriptM a) -> ScriptM a
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (ScriptM (ScriptM a) -> ScriptM a)
-> ((String -> Handle -> IO (ScriptM a)) -> ScriptM (ScriptM a))
-> (String -> Handle -> IO (ScriptM a))
-> ScriptM a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (ScriptM a) -> ScriptM (ScriptM a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ScriptM a) -> ScriptM (ScriptM a))
-> ((String -> Handle -> IO (ScriptM a)) -> IO (ScriptM a))
-> (String -> Handle -> IO (ScriptM a))
-> ScriptM (ScriptM a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> (String -> Handle -> IO (ScriptM a)) -> IO (ScriptM a)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"futhark-literate" ((String -> Handle -> IO (ScriptM a)) -> ScriptM a)
-> (String -> Handle -> IO (ScriptM a)) -> ScriptM a
forall a b. (a -> b) -> a -> b
$ \String
tmpf Handle
tmpf_h -> do
Handle -> IO ()
hClose Handle
tmpf_h
(Either Text a
res, Files
files) <- ScriptM a -> IO (Either Text a, Files)
forall a. ScriptM a -> IO (Either Text a, Files)
runScriptM (String -> ScriptM a
f String
tmpf)
ScriptM a -> IO (ScriptM a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ScriptM a -> IO (ScriptM a)) -> ScriptM a -> IO (ScriptM a)
forall a b. (a -> b) -> a -> b
$ do
(State -> State) -> ScriptM ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((State -> State) -> ScriptM ()) -> (State -> State) -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ \State
s -> State
s {stateFiles :: Files
stateFiles = Files
files Files -> Files -> Files
forall a. Semigroup a => a -> a -> a
<> State -> Files
stateFiles State
s}
(Text -> ScriptM a)
-> (a -> ScriptM a) -> Either Text a -> ScriptM a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Text -> ScriptM a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError a -> ScriptM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either Text a
res
withTempDir :: (FilePath -> ScriptM a) -> ScriptM a
withTempDir :: (String -> ScriptM a) -> ScriptM a
withTempDir String -> ScriptM a
f =
ScriptM (ScriptM a) -> ScriptM a
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (ScriptM (ScriptM a) -> ScriptM a)
-> ((String -> IO (ScriptM a)) -> ScriptM (ScriptM a))
-> (String -> IO (ScriptM a))
-> ScriptM a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (ScriptM a) -> ScriptM (ScriptM a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ScriptM a) -> ScriptM (ScriptM a))
-> ((String -> IO (ScriptM a)) -> IO (ScriptM a))
-> (String -> IO (ScriptM a))
-> ScriptM (ScriptM a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> (String -> IO (ScriptM a)) -> IO (ScriptM a)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> m a) -> m a
withSystemTempDirectory String
"futhark-literate" ((String -> IO (ScriptM a)) -> ScriptM a)
-> (String -> IO (ScriptM a)) -> ScriptM a
forall a b. (a -> b) -> a -> b
$ \String
dir -> do
(Either Text a
res, Files
files) <- ScriptM a -> IO (Either Text a, Files)
forall a. ScriptM a -> IO (Either Text a, Files)
runScriptM (String -> ScriptM a
f String
dir)
ScriptM a -> IO (ScriptM a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ScriptM a -> IO (ScriptM a)) -> ScriptM a -> IO (ScriptM a)
forall a b. (a -> b) -> a -> b
$ do
(State -> State) -> ScriptM ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((State -> State) -> ScriptM ()) -> (State -> State) -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ \State
s -> State
s {stateFiles :: Files
stateFiles = Files
files Files -> Files -> Files
forall a. Semigroup a => a -> a -> a
<> State -> Files
stateFiles State
s}
(Text -> ScriptM a)
-> (a -> ScriptM a) -> Either Text a -> ScriptM a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Text -> ScriptM a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError a -> ScriptM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either Text a
res
greyFloatToImg ::
(RealFrac a, SVec.Storable a) =>
SVec.Vector a ->
SVec.Vector Word32
greyFloatToImg :: Vector a -> Vector Word32
greyFloatToImg = (a -> Word32) -> Vector a -> Vector Word32
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
SVec.map a -> Word32
forall a a. (Bits a, RealFrac a, Integral a) => a -> a
grey
where
grey :: a -> a
grey a
i =
let i' :: a
i' = a -> a
forall a b. (RealFrac a, Integral b) => a -> b
round (a
i a -> a -> a
forall a. Num a => a -> a -> a
* a
255) a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
0xFF
in (a
i' a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
16) a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
i' a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
8) a -> a -> a
forall a. Bits a => a -> a -> a
.|. a
i'
greyByteToImg ::
(Integral a, SVec.Storable a) =>
SVec.Vector a ->
SVec.Vector Word32
greyByteToImg :: Vector a -> Vector Word32
greyByteToImg = (a -> Word32) -> Vector a -> Vector Word32
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
SVec.map a -> Word32
forall a a. (Bits a, Integral a, Num a) => a -> a
grey
where
grey :: a -> a
grey a
i =
(a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
16) a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
8) a -> a -> a
forall a. Bits a => a -> a -> a
.|. a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i
vecToBMP :: Int -> Int -> SVec.Vector Word32 -> LBS.ByteString
vecToBMP :: Int -> Int -> Vector Word32 -> ByteString
vecToBMP Int
h Int
w = BMP -> ByteString
BMP.renderBMP (BMP -> ByteString)
-> (Vector Word32 -> BMP) -> Vector Word32 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> ByteString -> BMP
BMP.packRGBA32ToBMP24 Int
w Int
h (ByteString -> BMP)
-> (Vector Word32 -> ByteString) -> Vector Word32 -> BMP
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Word8 -> ByteString
forall a. Storable a => Vector a -> ByteString
SVec.vectorToByteString (Vector Word8 -> ByteString)
-> (Vector Word32 -> Vector Word8) -> Vector Word32 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Word32 -> Vector Word8
forall a.
(Integral a, Storable a, Bits a) =>
Vector a -> Vector Word8
frobVec
where
frobVec :: Vector a -> Vector Word8
frobVec Vector a
vec = Int -> (Int -> Word8) -> Vector Word8
forall a. Storable a => Int -> (Int -> a) -> Vector a
SVec.generate (Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4) (Vector a -> Int -> Word8
forall a.
(Integral a, Storable a, Bits a) =>
Vector a -> Int -> Word8
pix Vector a
vec)
pix :: Vector a -> Int -> Word8
pix Vector a
vec Int
l =
let (Int
i, Int
j) = (Int
l Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
4) Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
w
argb :: a
argb = Vector a
vec Vector a -> Int -> a
forall a. Storable a => Vector a -> Int -> a
SVec.! ((Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
j)
c :: a
c = (a
argb a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` (Int
24 Int -> Int -> Int
forall a. Num a => a -> a -> a
- ((Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
4) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)) a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
0xFF
in a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
c :: Word8
valueToBMP :: Value -> Maybe LBS.ByteString
valueToBMP :: Value -> Maybe ByteString
valueToBMP v :: Value
v@(Word32Value Vector Int
_ Vector Word32
bytes)
| [Int
h, Int
w] <- Value -> [Int]
valueShape Value
v =
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Word32 -> ByteString
vecToBMP Int
h Int
w Vector Word32
bytes
valueToBMP v :: Value
v@(Int32Value Vector Int
_ Vector Int32
bytes)
| [Int
h, Int
w] <- Value -> [Int]
valueShape Value
v =
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Word32 -> ByteString
vecToBMP Int
h Int
w (Vector Word32 -> ByteString) -> Vector Word32 -> ByteString
forall a b. (a -> b) -> a -> b
$ (Int32 -> Word32) -> Vector Int32 -> Vector Word32
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
SVec.map Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Vector Int32
bytes
valueToBMP v :: Value
v@(Float32Value Vector Int
_ Vector Float
bytes)
| [Int
h, Int
w] <- Value -> [Int]
valueShape Value
v =
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Word32 -> ByteString
vecToBMP Int
h Int
w (Vector Word32 -> ByteString) -> Vector Word32 -> ByteString
forall a b. (a -> b) -> a -> b
$ Vector Float -> Vector Word32
forall a. (RealFrac a, Storable a) => Vector a -> Vector Word32
greyFloatToImg Vector Float
bytes
valueToBMP v :: Value
v@(Word8Value Vector Int
_ Vector Word8
bytes)
| [Int
h, Int
w] <- Value -> [Int]
valueShape Value
v =
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Word32 -> ByteString
vecToBMP Int
h Int
w (Vector Word32 -> ByteString) -> Vector Word32 -> ByteString
forall a b. (a -> b) -> a -> b
$ Vector Word8 -> Vector Word32
forall a. (Integral a, Storable a) => Vector a -> Vector Word32
greyByteToImg Vector Word8
bytes
valueToBMP v :: Value
v@(Float64Value Vector Int
_ Vector Double
bytes)
| [Int
h, Int
w] <- Value -> [Int]
valueShape Value
v =
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Word32 -> ByteString
vecToBMP Int
h Int
w (Vector Word32 -> ByteString) -> Vector Word32 -> ByteString
forall a b. (a -> b) -> a -> b
$ Vector Double -> Vector Word32
forall a. (RealFrac a, Storable a) => Vector a -> Vector Word32
greyFloatToImg Vector Double
bytes
valueToBMP v :: Value
v@(BoolValue Vector Int
_ Vector Bool
bytes)
| [Int
h, Int
w] <- Value -> [Int]
valueShape Value
v =
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Word32 -> ByteString
vecToBMP Int
h Int
w (Vector Word32 -> ByteString) -> Vector Word32 -> ByteString
forall a b. (a -> b) -> a -> b
$ Vector Int -> Vector Word32
forall a. (Integral a, Storable a) => Vector a -> Vector Word32
greyByteToImg (Vector Int -> Vector Word32) -> Vector Int -> Vector Word32
forall a b. (a -> b) -> a -> b
$ (Bool -> Int) -> Vector Bool -> Vector Int
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
SVec.map (Int -> Int -> Int
forall a. Num a => a -> a -> a
(*) Int
255 (Int -> Int) -> (Bool -> Int) -> Bool -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Vector Bool
bytes
valueToBMP Value
_ = Maybe ByteString
forall a. Maybe a
Nothing
valueToBMPs :: Value -> Maybe [LBS.ByteString]
valueToBMPs :: Value -> Maybe [ByteString]
valueToBMPs = (Value -> Maybe ByteString) -> [Value] -> Maybe [ByteString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Value -> Maybe ByteString
valueToBMP ([Value] -> Maybe [ByteString])
-> (Value -> [Value]) -> Value -> Maybe [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> [Value]
valueElems
system ::
(MonadIO m, MonadError T.Text m) =>
FilePath ->
[String] ->
T.Text ->
m T.Text
system :: String -> [String] -> Text -> m Text
system String
prog [String]
options Text
input = do
Either IOException (ExitCode, String, String)
res <- IO (Either IOException (ExitCode, String, String))
-> m (Either IOException (ExitCode, String, String))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either IOException (ExitCode, String, String))
-> m (Either IOException (ExitCode, String, String)))
-> IO (Either IOException (ExitCode, String, String))
-> m (Either IOException (ExitCode, String, String))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ByteString
-> IO (Either IOException (ExitCode, String, String))
runProgramWithExitCode String
prog [String]
options (ByteString -> IO (Either IOException (ExitCode, String, String)))
-> ByteString -> IO (Either IOException (ExitCode, String, String))
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 Text
input
case Either IOException (ExitCode, String, String)
res of
Left IOException
err ->
Text -> m Text
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m Text) -> Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text
prog' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" failed: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (IOException -> String
forall a. Show a => a -> String
show IOException
err)
Right (ExitCode
ExitSuccess, String
stdout_t, String
_) ->
Text -> m Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> m Text) -> Text -> m Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
stdout_t
Right (ExitFailure Int
code', String
_, String
stderr_t) ->
Text -> m Text
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m Text) -> Text -> m Text
forall a b. (a -> b) -> a -> b
$
Text
prog' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" failed with exit code "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
code')
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" and stderr:\n"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
stderr_t
where
prog' :: Text
prog' = Text
"'" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
prog Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'"
formatDataForGnuplot :: [Value] -> T.Text
formatDataForGnuplot :: [Value] -> Text
formatDataForGnuplot = [Text] -> Text
T.unlines ([Text] -> Text) -> ([Value] -> [Text]) -> [Value] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Value] -> Text) -> [[Value]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map [Value] -> Text
line ([[Value]] -> [Text])
-> ([Value] -> [[Value]]) -> [Value] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Value]] -> [[Value]]
forall a. [[a]] -> [[a]]
transpose ([[Value]] -> [[Value]])
-> ([Value] -> [[Value]]) -> [Value] -> [[Value]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> [Value]) -> [Value] -> [[Value]]
forall a b. (a -> b) -> [a] -> [b]
map Value -> [Value]
valueElems
where
line :: [Value] -> Text
line = [Text] -> Text
T.unwords ([Text] -> Text) -> ([Value] -> [Text]) -> [Value] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Text) -> [Value] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Value -> Text
forall a. Pretty a => a -> Text
prettyText
imgBlock :: FilePath -> T.Text
imgBlock :: String -> Text
imgBlock String
f = Text
"\n\n![](" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
f Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")\n\n"
videoBlock :: VideoParams -> FilePath -> T.Text
videoBlock :: VideoParams -> String -> Text
videoBlock VideoParams
opts String
f = Text
"\n\n![](" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
f Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
opts' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n\n"
where
opts' :: Text
opts'
| (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
T.null [Text
loop, Text
autoplay] =
Text
forall a. Monoid a => a
mempty
| Bool
otherwise =
Text
"{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.unwords [Text
loop, Text
autoplay] Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
boolOpt :: a -> (VideoParams -> Maybe Bool) -> a
boolOpt a
s VideoParams -> Maybe Bool
prop
| Just Bool
b <- VideoParams -> Maybe Bool
prop VideoParams
opts =
if Bool
b then a
s a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"=\"true\"" else a
s a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"=\"false\""
| Bool
otherwise =
a
forall a. Monoid a => a
mempty
loop :: Text
loop = Text -> (VideoParams -> Maybe Bool) -> Text
forall a.
(IsString a, Monoid a) =>
a -> (VideoParams -> Maybe Bool) -> a
boolOpt Text
"loop" VideoParams -> Maybe Bool
videoLoop
autoplay :: Text
autoplay = Text -> (VideoParams -> Maybe Bool) -> Text
forall a.
(IsString a, Monoid a) =>
a -> (VideoParams -> Maybe Bool) -> a
boolOpt Text
"autoplay" VideoParams -> Maybe Bool
videoAutoplay
plottable :: CompoundValue -> Maybe [Value]
plottable :: CompoundValue -> Maybe [Value]
plottable (ValueTuple [CompoundValue]
vs) = do
([Value]
vs', [Int]
ns') <- [(Value, Int)] -> ([Value], [Int])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Value, Int)] -> ([Value], [Int]))
-> Maybe [(Value, Int)] -> Maybe ([Value], [Int])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CompoundValue -> Maybe (Value, Int))
-> [CompoundValue] -> Maybe [(Value, Int)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM CompoundValue -> Maybe (Value, Int)
inspect [CompoundValue]
vs
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Int] -> [Int]
forall a. Ord a => [a] -> [a]
nubOrd [Int]
ns') Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
[Value] -> Maybe [Value]
forall a. a -> Maybe a
Just [Value]
vs'
where
inspect :: CompoundValue -> Maybe (Value, Int)
inspect (ValueAtom Value
v)
| [Int
n] <- Value -> [Int]
valueShape Value
v = (Value, Int) -> Maybe (Value, Int)
forall a. a -> Maybe a
Just (Value
v, Int
n)
inspect CompoundValue
_ = Maybe (Value, Int)
forall a. Maybe a
Nothing
plottable CompoundValue
_ = Maybe [Value]
forall a. Maybe a
Nothing
withGnuplotData ::
[(T.Text, T.Text)] ->
[(T.Text, [Value])] ->
([T.Text] -> [T.Text] -> ScriptM a) ->
ScriptM a
withGnuplotData :: [(Text, Text)]
-> [(Text, [Value])]
-> ([Text] -> [Text] -> ScriptM a)
-> ScriptM a
withGnuplotData [(Text, Text)]
sets [] [Text] -> [Text] -> ScriptM a
cont = ([Text] -> [Text] -> ScriptM a) -> ([Text], [Text]) -> ScriptM a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Text] -> [Text] -> ScriptM a
cont (([Text], [Text]) -> ScriptM a) -> ([Text], [Text]) -> ScriptM a
forall a b. (a -> b) -> a -> b
$ [(Text, Text)] -> ([Text], [Text])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Text, Text)] -> ([Text], [Text]))
-> [(Text, Text)] -> ([Text], [Text])
forall a b. (a -> b) -> a -> b
$ [(Text, Text)] -> [(Text, Text)]
forall a. [a] -> [a]
reverse [(Text, Text)]
sets
withGnuplotData [(Text, Text)]
sets ((Text
f, [Value]
vs) : [(Text, [Value])]
xys) [Text] -> [Text] -> ScriptM a
cont =
(String -> ScriptM a) -> ScriptM a
forall a. (String -> ScriptM a) -> ScriptM a
withTempFile ((String -> ScriptM a) -> ScriptM a)
-> (String -> ScriptM a) -> ScriptM a
forall a b. (a -> b) -> a -> b
$ \String
fname -> do
IO () -> ScriptM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ScriptM ()) -> IO () -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ String -> Text -> IO ()
T.writeFile String
fname (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ [Value] -> Text
formatDataForGnuplot [Value]
vs
[(Text, Text)]
-> [(Text, [Value])]
-> ([Text] -> [Text] -> ScriptM a)
-> ScriptM a
forall a.
[(Text, Text)]
-> [(Text, [Value])]
-> ([Text] -> [Text] -> ScriptM a)
-> ScriptM a
withGnuplotData ((Text
f, Text
f Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"='" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
fname Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'") (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
sets) [(Text, [Value])]
xys [Text] -> [Text] -> ScriptM a
cont
loadBMP :: FilePath -> ScriptM (Compound Value)
loadBMP :: String -> ScriptM CompoundValue
loadBMP String
bmpfile = do
Either Error BMP
res <- IO (Either Error BMP) -> ScriptM (Either Error BMP)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either Error BMP) -> ScriptM (Either Error BMP))
-> IO (Either Error BMP) -> ScriptM (Either Error BMP)
forall a b. (a -> b) -> a -> b
$ String -> IO (Either Error BMP)
BMP.readBMP String
bmpfile
case Either Error BMP
res of
Left Error
err ->
Text -> ScriptM CompoundValue
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM CompoundValue) -> Text -> ScriptM CompoundValue
forall a b. (a -> b) -> a -> b
$ Text
"Failed to read BMP:\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Error -> String
forall a. Show a => a -> String
show Error
err)
Right BMP
bmp -> do
let bmp_bs :: ByteString
bmp_bs = BMP -> ByteString
BMP.unpackBMPToRGBA32 BMP
bmp
(Int
w, Int
h) = BMP -> (Int, Int)
BMP.bmpDimensions BMP
bmp
shape :: Vector Int
shape = [Int] -> Vector Int
forall a. Storable a => [a] -> Vector a
SVec.fromList [Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
h, Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w]
pix :: Int -> a
pix Int
l =
let (Int
i, Int
j) = Int
l Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
w
l' :: Int
l' = (Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
j
r :: a
r = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> a) -> Word8 -> a
forall a b. (a -> b) -> a -> b
$ ByteString
bmp_bs ByteString -> Int -> Word8
`BS.index` (Int
l' Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4)
g :: a
g = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> a) -> Word8 -> a
forall a b. (a -> b) -> a -> b
$ ByteString
bmp_bs ByteString -> Int -> Word8
`BS.index` (Int
l' Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
b :: a
b = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> a) -> Word8 -> a
forall a b. (a -> b) -> a -> b
$ ByteString
bmp_bs ByteString -> Int -> Word8
`BS.index` (Int
l' Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
a :: a
a = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> a) -> Word8 -> a
forall a b. (a -> b) -> a -> b
$ ByteString
bmp_bs ByteString -> Int -> Word8
`BS.index` (Int
l' Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
in (a
a a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
24) a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
r a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
16) a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
g a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
8) a -> a -> a
forall a. Bits a => a -> a -> a
.|. a
b
CompoundValue -> ScriptM CompoundValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CompoundValue -> ScriptM CompoundValue)
-> CompoundValue -> ScriptM CompoundValue
forall a b. (a -> b) -> a -> b
$ Value -> CompoundValue
forall v. v -> Compound v
ValueAtom (Value -> CompoundValue) -> Value -> CompoundValue
forall a b. (a -> b) -> a -> b
$ Vector Int -> Vector Word32 -> Value
Word32Value Vector Int
shape (Vector Word32 -> Value) -> Vector Word32 -> Value
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Word32) -> Vector Word32
forall a. Storable a => Int -> (Int -> a) -> Vector a
SVec.generate (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
h) Int -> Word32
forall a. (Bits a, Num a) => Int -> a
pix
loadImage :: FilePath -> ScriptM (Compound Value)
loadImage :: String -> ScriptM CompoundValue
loadImage String
imgfile =
(String -> ScriptM CompoundValue) -> ScriptM CompoundValue
forall a. (String -> ScriptM a) -> ScriptM a
withTempDir ((String -> ScriptM CompoundValue) -> ScriptM CompoundValue)
-> (String -> ScriptM CompoundValue) -> ScriptM CompoundValue
forall a b. (a -> b) -> a -> b
$ \String
dir -> do
let bmpfile :: String
bmpfile = String
dir String -> ShowS
</> ShowS
takeBaseName String
imgfile String -> ShowS
`replaceExtension` String
"bmp"
ScriptM Text -> ScriptM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ScriptM Text -> ScriptM ()) -> ScriptM Text -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> Text -> ScriptM Text
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> [String] -> Text -> m Text
system String
"convert" [String
imgfile, String
"-type", String
"TrueColorAlpha", String
bmpfile] Text
forall a. Monoid a => a
mempty
String -> ScriptM CompoundValue
loadBMP String
bmpfile
literateBuiltin :: EvalBuiltin ScriptM
literateBuiltin :: EvalBuiltin ScriptM
literateBuiltin Text
"loadimg" [CompoundValue]
vs =
case [CompoundValue]
vs of
[ValueAtom Value
v]
| Just [Word8]
path <- Value -> Maybe [Word8]
forall t. GetValue t => Value -> Maybe t
getValue Value
v -> do
let path' :: String
path' = (Word8 -> Char) -> [Word8] -> String
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char
chr (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ([Word8]
path :: [Word8])
String -> ScriptM CompoundValue
loadImage String
path'
[CompoundValue]
_ ->
Text -> ScriptM CompoundValue
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM CompoundValue) -> Text -> ScriptM CompoundValue
forall a b. (a -> b) -> a -> b
$
Text
"$imgfile does not accept arguments of types: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
", " ((CompoundValue -> Text) -> [CompoundValue] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Compound ValueType -> Text
forall a. Pretty a => a -> Text
prettyText (Compound ValueType -> Text)
-> (CompoundValue -> Compound ValueType) -> CompoundValue -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> ValueType) -> CompoundValue -> Compound ValueType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ValueType
valueType) [CompoundValue]
vs)
literateBuiltin Text
f [CompoundValue]
_ =
Text -> ScriptM CompoundValue
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM CompoundValue) -> Text -> ScriptM CompoundValue
forall a b. (a -> b) -> a -> b
$ Text
"Unknown builtin function $" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
forall a. Pretty a => a -> Text
prettyText Text
f
data Options = Options
{ Options -> String
scriptBackend :: String,
Options -> Maybe String
scriptFuthark :: Maybe FilePath,
:: [String],
Options -> [String]
scriptCompilerOptions :: [String],
Options -> Bool
scriptSkipCompilation :: Bool,
Options -> Maybe String
scriptOutput :: Maybe FilePath,
Options -> Int
scriptVerbose :: Int,
Options -> Bool
scriptStopOnError :: Bool
}
initialOptions :: Options
initialOptions :: Options
initialOptions =
Options :: String
-> Maybe String
-> [String]
-> [String]
-> Bool
-> Maybe String
-> Int
-> Bool
-> Options
Options
{ scriptBackend :: String
scriptBackend = String
"c",
scriptFuthark :: Maybe String
scriptFuthark = Maybe String
forall a. Maybe a
Nothing,
scriptExtraOptions :: [String]
scriptExtraOptions = [],
scriptCompilerOptions :: [String]
scriptCompilerOptions = [],
scriptSkipCompilation :: Bool
scriptSkipCompilation = Bool
False,
scriptOutput :: Maybe String
scriptOutput = Maybe String
forall a. Maybe a
Nothing,
scriptVerbose :: Int
scriptVerbose = Int
0,
scriptStopOnError :: Bool
scriptStopOnError = Bool
False
}
data Env = Env
{ Env -> String
envImgDir :: FilePath,
Env -> Options
envOpts :: Options,
Env -> ScriptServer
envServer :: ScriptServer,
Env -> Int
envHash :: Int
}
newFile :: Env -> FilePath -> (FilePath -> ScriptM ()) -> ScriptM FilePath
newFile :: Env -> String -> (String -> ScriptM ()) -> ScriptM String
newFile Env
env String
template String -> ScriptM ()
m = do
let fname :: String
fname =
Env -> String
envImgDir Env
env
String -> ShowS
</> Text -> String
T.unpack (Int -> Text
hashIntText (Env -> Int
envHash Env
env)) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"-" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
template
Bool
exists <- IO Bool -> ScriptM Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> ScriptM Bool) -> IO Bool -> ScriptM Bool
forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesFileExist String
fname
IO () -> ScriptM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ScriptM ()) -> IO () -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Env -> String
envImgDir Env
env
Bool -> ScriptM () -> ScriptM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
exists Bool -> Bool -> Bool
&& Options -> Int
scriptVerbose (Env -> Options
envOpts Env
env) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (ScriptM () -> ScriptM ()) -> ScriptM () -> ScriptM ()
forall a b. (a -> b) -> a -> b
$
IO () -> ScriptM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ScriptM ()) -> IO () -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"Using existing file: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
fname
Bool -> ScriptM () -> ScriptM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
exists (ScriptM () -> ScriptM ()) -> ScriptM () -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ String -> ScriptM ()
m String
fname
(State -> State) -> ScriptM ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((State -> State) -> ScriptM ()) -> (State -> State) -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ \State
s -> State
s {stateFiles :: Files
stateFiles = String -> Files -> Files
forall a. Ord a => a -> Set a -> Set a
S.insert String
fname (Files -> Files) -> Files -> Files
forall a b. (a -> b) -> a -> b
$ State -> Files
stateFiles State
s}
String -> ScriptM String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
fname
processDirective :: Env -> Directive -> ScriptM T.Text
processDirective :: Env -> Directive -> ScriptM Text
processDirective Env
env (DirectiveBrief Directive
d) =
Env -> Directive -> ScriptM Text
processDirective Env
env Directive
d
processDirective Env
env (DirectiveCovert Directive
d) =
Env -> Directive -> ScriptM Text
processDirective Env
env Directive
d
processDirective Env
env (DirectiveRes Exp
e) = do
CompoundValue
v <- (Compound ScriptValueType -> ScriptM CompoundValue)
-> (CompoundValue -> ScriptM CompoundValue)
-> Either (Compound ScriptValueType) CompoundValue
-> ScriptM CompoundValue
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Compound ScriptValueType -> ScriptM CompoundValue
forall (m :: * -> *) a a. (MonadError Text m, Pretty a) => a -> m a
nope CompoundValue -> ScriptM CompoundValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Compound ScriptValueType) CompoundValue
-> ScriptM CompoundValue)
-> ScriptM (Either (Compound ScriptValueType) CompoundValue)
-> ScriptM CompoundValue
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EvalBuiltin ScriptM
-> ScriptServer
-> Exp
-> ScriptM (Either (Compound ScriptValueType) CompoundValue)
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
EvalBuiltin m
-> ScriptServer
-> Exp
-> m (Either (Compound ScriptValueType) CompoundValue)
evalExpToGround EvalBuiltin ScriptM
literateBuiltin (Env -> ScriptServer
envServer Env
env) Exp
e
Text -> ScriptM Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$
[Text] -> Text
T.unlines
[ Text
"",
Text
"```",
CompoundValue -> Text
forall a. Pretty a => a -> Text
prettyText CompoundValue
v,
Text
"```",
Text
""
]
where
nope :: a -> m a
nope a
t =
Text -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m a) -> Text -> m a
forall a b. (a -> b) -> a -> b
$ Text
"Cannot show value of type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. Pretty a => a -> Text
prettyText a
t
processDirective Env
env (DirectiveImg Exp
e) = do
Either (Compound ScriptValueType) CompoundValue
maybe_v <- EvalBuiltin ScriptM
-> ScriptServer
-> Exp
-> ScriptM (Either (Compound ScriptValueType) CompoundValue)
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
EvalBuiltin m
-> ScriptServer
-> Exp
-> m (Either (Compound ScriptValueType) CompoundValue)
evalExpToGround EvalBuiltin ScriptM
literateBuiltin (Env -> ScriptServer
envServer Env
env) Exp
e
case Either (Compound ScriptValueType) CompoundValue
maybe_v of
Right (ValueAtom Value
v)
| Just ByteString
bmp <- Value -> Maybe ByteString
valueToBMP Value
v -> do
String
pngfile <- (String -> ScriptM String) -> ScriptM String
forall a. (String -> ScriptM a) -> ScriptM a
withTempDir ((String -> ScriptM String) -> ScriptM String)
-> (String -> ScriptM String) -> ScriptM String
forall a b. (a -> b) -> a -> b
$ \String
dir -> do
let bmpfile :: String
bmpfile = String
dir String -> ShowS
</> String
"img.bmp"
IO () -> ScriptM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ScriptM ()) -> IO () -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
LBS.writeFile String
bmpfile ByteString
bmp
Env -> String -> (String -> ScriptM ()) -> ScriptM String
newFile Env
env String
"img.png" ((String -> ScriptM ()) -> ScriptM String)
-> (String -> ScriptM ()) -> ScriptM String
forall a b. (a -> b) -> a -> b
$ \String
pngfile ->
ScriptM Text -> ScriptM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ScriptM Text -> ScriptM ()) -> ScriptM Text -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> Text -> ScriptM Text
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> [String] -> Text -> m Text
system String
"convert" [String
bmpfile, String
pngfile] Text
forall a. Monoid a => a
mempty
Text -> ScriptM Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ String -> Text
imgBlock String
pngfile
Right CompoundValue
v ->
Compound ValueType -> ScriptM Text
forall (m :: * -> *) a a. (MonadError Text m, Pretty a) => a -> m a
nope (Compound ValueType -> ScriptM Text)
-> Compound ValueType -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ (Value -> ValueType) -> CompoundValue -> Compound ValueType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ValueType
valueType CompoundValue
v
Left Compound ScriptValueType
t ->
Compound ScriptValueType -> ScriptM Text
forall (m :: * -> *) a a. (MonadError Text m, Pretty a) => a -> m a
nope Compound ScriptValueType
t
where
nope :: a -> m a
nope a
t =
Text -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> m a) -> Text -> m a
forall a b. (a -> b) -> a -> b
$
Text
"Cannot create image from value of type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. Pretty a => a -> Text
prettyText a
t
processDirective Env
env (DirectivePlot Exp
e Maybe (Int, Int)
size) = do
Either (Compound ScriptValueType) CompoundValue
maybe_v <- EvalBuiltin ScriptM
-> ScriptServer
-> Exp
-> ScriptM (Either (Compound ScriptValueType) CompoundValue)
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
EvalBuiltin m
-> ScriptServer
-> Exp
-> m (Either (Compound ScriptValueType) CompoundValue)
evalExpToGround EvalBuiltin ScriptM
literateBuiltin (Env -> ScriptServer
envServer Env
env) Exp
e
case Either (Compound ScriptValueType) CompoundValue
maybe_v of
Right CompoundValue
v
| Just [Value]
vs <- CompoundValue -> Maybe [Value]
plottable2d CompoundValue
v -> do
String
pngfile <- Env -> String -> (String -> ScriptM ()) -> ScriptM String
newFile Env
env String
"plot.png" ((String -> ScriptM ()) -> ScriptM String)
-> (String -> ScriptM ()) -> ScriptM String
forall a b. (a -> b) -> a -> b
$ [(Maybe Text, [Value])] -> String -> ScriptM ()
plotWith [(Maybe Text
forall a. Maybe a
Nothing, [Value]
vs)]
Text -> ScriptM Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ String -> Text
imgBlock String
pngfile
Right (ValueRecord Map Text CompoundValue
m)
| Just Map Text [Value]
m' <- (CompoundValue -> Maybe [Value])
-> Map Text CompoundValue -> Maybe (Map Text [Value])
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse CompoundValue -> Maybe [Value]
plottable2d Map Text CompoundValue
m -> do
String
pngfile <- Env -> String -> (String -> ScriptM ()) -> ScriptM String
newFile Env
env String
"plot.png" ((String -> ScriptM ()) -> ScriptM String)
-> (String -> ScriptM ()) -> ScriptM String
forall a b. (a -> b) -> a -> b
$ [(Maybe Text, [Value])] -> String -> ScriptM ()
plotWith ([(Maybe Text, [Value])] -> String -> ScriptM ())
-> [(Maybe Text, [Value])] -> String -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ ((Text, [Value]) -> (Maybe Text, [Value]))
-> [(Text, [Value])] -> [(Maybe Text, [Value])]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> Maybe Text) -> (Text, [Value]) -> (Maybe Text, [Value])
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Text -> Maybe Text
forall a. a -> Maybe a
Just) ([(Text, [Value])] -> [(Maybe Text, [Value])])
-> [(Text, [Value])] -> [(Maybe Text, [Value])]
forall a b. (a -> b) -> a -> b
$ Map Text [Value] -> [(Text, [Value])]
forall k a. Map k a -> [(k, a)]
M.toList Map Text [Value]
m'
Text -> ScriptM Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ String -> Text
imgBlock String
pngfile
Right CompoundValue
v ->
Text -> ScriptM Text
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ Text
"Cannot plot value of type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound ValueType -> Text
forall a. Pretty a => a -> Text
prettyText ((Value -> ValueType) -> CompoundValue -> Compound ValueType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ValueType
valueType CompoundValue
v)
Left Compound ScriptValueType
t ->
Text -> ScriptM Text
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ Text
"Cannot plot opaque value of type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound ScriptValueType -> Text
forall a. Pretty a => a -> Text
prettyText Compound ScriptValueType
t
where
plottable2d :: CompoundValue -> Maybe [Value]
plottable2d CompoundValue
v = do
[Value
x, Value
y] <- CompoundValue -> Maybe [Value]
plottable CompoundValue
v
[Value] -> Maybe [Value]
forall a. a -> Maybe a
Just [Value
x, Value
y]
tag :: (Maybe Text, b) -> Int -> (Text, b)
tag (Maybe Text
Nothing, b
xys) Int
j = (Text
"data" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (Int
j :: Int)), b
xys)
tag (Just Text
f, b
xys) Int
_ = (Text
f, b
xys)
plotWith :: [(Maybe Text, [Value])] -> String -> ScriptM ()
plotWith [(Maybe Text, [Value])]
xys String
pngfile =
[(Text, Text)]
-> [(Text, [Value])]
-> ([Text] -> [Text] -> ScriptM ())
-> ScriptM ()
forall a.
[(Text, Text)]
-> [(Text, [Value])]
-> ([Text] -> [Text] -> ScriptM a)
-> ScriptM a
withGnuplotData [] (((Maybe Text, [Value]) -> Int -> (Text, [Value]))
-> [(Maybe Text, [Value])] -> [Int] -> [(Text, [Value])]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Maybe Text, [Value]) -> Int -> (Text, [Value])
forall b. (Maybe Text, b) -> Int -> (Text, b)
tag [(Maybe Text, [Value])]
xys [Int
0 ..]) (([Text] -> [Text] -> ScriptM ()) -> ScriptM ())
-> ([Text] -> [Text] -> ScriptM ()) -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ \[Text]
fs [Text]
sets -> do
let size' :: Text
size' = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
case Maybe (Int, Int)
size of
Maybe (Int, Int)
Nothing -> String
"500,500"
Just (Int
w, Int
h) -> Int -> String
forall a. Show a => a -> String
show Int
w String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"," String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
h
plotCmd :: a -> Maybe a -> a
plotCmd a
f Maybe a
title =
let title' :: a
title' = case Maybe a
title of
Maybe a
Nothing -> a
"notitle"
Just x -> a
"title '" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
x a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"'"
in a
f a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
" " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
title' a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
" with lines"
cmds :: Text
cmds = Text -> [Text] -> Text
T.intercalate Text
", " ((Text -> Maybe Text -> Text) -> [Text] -> [Maybe Text] -> [Text]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Text -> Maybe Text -> Text
forall a. (IsString a, Semigroup a) => a -> Maybe a -> a
plotCmd [Text]
fs (((Maybe Text, [Value]) -> Maybe Text)
-> [(Maybe Text, [Value])] -> [Maybe Text]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Text, [Value]) -> Maybe Text
forall a b. (a, b) -> a
fst [(Maybe Text, [Value])]
xys))
script :: Text
script =
[Text] -> Text
T.unlines
[ Text
"set terminal png size " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
size' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" enhanced",
Text
"set output '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
pngfile Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'",
Text
"set key outside",
[Text] -> Text
T.unlines [Text]
sets,
Text
"plot " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cmds
]
ScriptM Text -> ScriptM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ScriptM Text -> ScriptM ()) -> ScriptM Text -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> Text -> ScriptM Text
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> [String] -> Text -> m Text
system String
"gnuplot" [] Text
script
processDirective Env
env (DirectiveGnuplot Exp
e Text
script) = do
Either (Compound ScriptValueType) CompoundValue
maybe_v <- EvalBuiltin ScriptM
-> ScriptServer
-> Exp
-> ScriptM (Either (Compound ScriptValueType) CompoundValue)
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
EvalBuiltin m
-> ScriptServer
-> Exp
-> m (Either (Compound ScriptValueType) CompoundValue)
evalExpToGround EvalBuiltin ScriptM
literateBuiltin (Env -> ScriptServer
envServer Env
env) Exp
e
case Either (Compound ScriptValueType) CompoundValue
maybe_v of
Right (ValueRecord Map Text CompoundValue
m)
| Just Map Text [Value]
m' <- (CompoundValue -> Maybe [Value])
-> Map Text CompoundValue -> Maybe (Map Text [Value])
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse CompoundValue -> Maybe [Value]
plottable Map Text CompoundValue
m -> do
String
pngfile <- Env -> String -> (String -> ScriptM ()) -> ScriptM String
newFile Env
env String
"plot.png" ((String -> ScriptM ()) -> ScriptM String)
-> (String -> ScriptM ()) -> ScriptM String
forall a b. (a -> b) -> a -> b
$ [(Text, [Value])] -> String -> ScriptM ()
plotWith ([(Text, [Value])] -> String -> ScriptM ())
-> [(Text, [Value])] -> String -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ Map Text [Value] -> [(Text, [Value])]
forall k a. Map k a -> [(k, a)]
M.toList Map Text [Value]
m'
Text -> ScriptM Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ String -> Text
imgBlock String
pngfile
Right CompoundValue
v ->
Text -> ScriptM Text
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ Text
"Cannot plot value of type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound ValueType -> Text
forall a. Pretty a => a -> Text
prettyText ((Value -> ValueType) -> CompoundValue -> Compound ValueType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ValueType
valueType CompoundValue
v)
Left Compound ScriptValueType
t ->
Text -> ScriptM Text
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ Text
"Cannot plot opaque value of type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound ScriptValueType -> Text
forall a. Pretty a => a -> Text
prettyText Compound ScriptValueType
t
where
plotWith :: [(Text, [Value])] -> String -> ScriptM ()
plotWith [(Text, [Value])]
xys String
pngfile = [(Text, Text)]
-> [(Text, [Value])]
-> ([Text] -> [Text] -> ScriptM ())
-> ScriptM ()
forall a.
[(Text, Text)]
-> [(Text, [Value])]
-> ([Text] -> [Text] -> ScriptM a)
-> ScriptM a
withGnuplotData [] [(Text, [Value])]
xys (([Text] -> [Text] -> ScriptM ()) -> ScriptM ())
-> ([Text] -> [Text] -> ScriptM ()) -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ \[Text]
_ [Text]
sets -> do
let script' :: Text
script' =
[Text] -> Text
T.unlines
[ Text
"set terminal png enhanced",
Text
"set output '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
pngfile Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'",
[Text] -> Text
T.unlines [Text]
sets,
Text
script
]
ScriptM Text -> ScriptM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ScriptM Text -> ScriptM ()) -> ScriptM Text -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> Text -> ScriptM Text
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> [String] -> Text -> m Text
system String
"gnuplot" [] Text
script'
processDirective Env
env (DirectiveVideo Exp
e VideoParams
params) = do
Bool -> ScriptM () -> ScriptM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
format Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text
"webm", Text
"gif"]) (ScriptM () -> ScriptM ()) -> ScriptM () -> ScriptM ()
forall a b. (a -> b) -> a -> b
$
Text -> ScriptM ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM ()) -> Text -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ Text
"Unknown video format: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
format
ExpValue
v <- EvalBuiltin ScriptM -> ScriptServer -> Exp -> ScriptM ExpValue
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
EvalBuiltin m -> ScriptServer -> Exp -> m ExpValue
evalExp EvalBuiltin ScriptM
literateBuiltin (Env -> ScriptServer
envServer Env
env) Exp
e
let nope :: ScriptM a
nope =
Text -> ScriptM a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM a) -> Text -> ScriptM a
forall a b. (a -> b) -> a -> b
$
Text
"Cannot produce video from value of type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound ScriptValueType -> Text
forall a. Pretty a => a -> Text
prettyText ((ScriptValue ValOrVar -> ScriptValueType)
-> ExpValue -> Compound ScriptValueType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ScriptValue ValOrVar -> ScriptValueType
forall v. ScriptValue v -> ScriptValueType
scriptValueType ExpValue
v)
String
videofile <- Env -> String -> (String -> ScriptM ()) -> ScriptM String
newFile Env
env (String
"video" String -> ShowS
<.> Text -> String
T.unpack Text
format) ((String -> ScriptM ()) -> ScriptM String)
-> (String -> ScriptM ()) -> ScriptM String
forall a b. (a -> b) -> a -> b
$ \String
videofile ->
case ExpValue
v of
ValueAtom SValue {} -> do
ValueAtom Value
arr <- ScriptServer -> ExpValue -> ScriptM CompoundValue
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
ScriptServer -> ExpValue -> m CompoundValue
getExpValue (Env -> ScriptServer
envServer Env
env) ExpValue
v
case Value -> Maybe [ByteString]
valueToBMPs Value
arr of
Maybe [ByteString]
Nothing -> ScriptM ()
forall a. ScriptM a
nope
Just [ByteString]
bmps ->
(String -> ScriptM ()) -> ScriptM ()
forall a. (String -> ScriptM a) -> ScriptM a
withTempDir ((String -> ScriptM ()) -> ScriptM ())
-> (String -> ScriptM ()) -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ \String
dir -> do
(Int -> ByteString -> ScriptM ())
-> [Int] -> [ByteString] -> ScriptM ()
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m ()
zipWithM_ (String -> Int -> ByteString -> ScriptM ()
forall (m :: * -> *).
MonadIO m =>
String -> Int -> ByteString -> m ()
writeBMPFile String
dir) [Int
0 ..] [ByteString]
bmps
String -> String -> ScriptM ()
forall (f :: * -> *).
(MonadIO f, MonadError Text f) =>
String -> String -> f ()
onWebM String
videofile (String -> ScriptM ()) -> ScriptM String -> ScriptM ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> ScriptM String
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> m String
bmpsToVideo String
dir
ValueTuple [ExpValue
stepfun, ExpValue
initial, ExpValue
num_frames]
| ValueAtom (SFun Text
stepfun' [Text]
_ [Text
_, Text
_] [ScriptValue ValOrVar]
closure) <- ExpValue
stepfun,
ValueAtom (SValue Text
_ ValOrVar
_) <- ExpValue
initial,
ValueAtom (SValue Text
"i64" ValOrVar
_) <- ExpValue
num_frames -> do
Just (ValueAtom Int64
num_frames') <-
(Value -> Maybe Int64) -> CompoundValue -> Maybe (Compound Int64)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Value -> Maybe Int64
forall t. GetValue t => Value -> Maybe t
getValue (CompoundValue -> Maybe (Compound Int64))
-> ScriptM CompoundValue -> ScriptM (Maybe (Compound Int64))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScriptServer -> ExpValue -> ScriptM CompoundValue
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
ScriptServer -> ExpValue -> m CompoundValue
getExpValue (Env -> ScriptServer
envServer Env
env) ExpValue
num_frames
(String -> ScriptM ()) -> ScriptM ()
forall a. (String -> ScriptM a) -> ScriptM a
withTempDir ((String -> ScriptM ()) -> ScriptM ())
-> (String -> ScriptM ()) -> ScriptM ()
forall a b. (a -> b) -> a -> b
$ \String
dir -> do
let num_frames_int :: Int
num_frames_int = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64
num_frames' :: Int64)
String -> (Text, [ExpValue]) -> ExpValue -> Int -> ScriptM ()
renderFrames String
dir (Text
stepfun', (ScriptValue ValOrVar -> ExpValue)
-> [ScriptValue ValOrVar] -> [ExpValue]
forall a b. (a -> b) -> [a] -> [b]
map ScriptValue ValOrVar -> ExpValue
forall v. v -> Compound v
ValueAtom [ScriptValue ValOrVar]
closure) ExpValue
initial Int
num_frames_int
String -> String -> ScriptM ()
forall (f :: * -> *).
(MonadIO f, MonadError Text f) =>
String -> String -> f ()
onWebM String
videofile (String -> ScriptM ()) -> ScriptM String -> ScriptM ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> ScriptM String
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> m String
bmpsToVideo String
dir
ExpValue
_ ->
ScriptM ()
forall a. ScriptM a
nope
Text -> ScriptM Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> ScriptM Text) -> Text -> ScriptM Text
forall a b. (a -> b) -> a -> b
$ VideoParams -> String -> Text
videoBlock VideoParams
params String
videofile
where
framerate :: Int
framerate = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
30 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ VideoParams -> Maybe Int
videoFPS VideoParams
params
format :: Text
format = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"webm" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ VideoParams -> Maybe Text
videoFormat VideoParams
params
bmpfile :: String -> Int -> String
bmpfile String
dir Int
j = String
dir String -> ShowS
</> String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"frame%010d.bmp" (Int
j :: Int)
renderFrames :: String -> (Text, [ExpValue]) -> ExpValue -> Int -> ScriptM ()
renderFrames String
dir (Text
stepfun, [ExpValue]
closure) ExpValue
initial Int
num_frames =
(ExpValue -> Int -> ScriptM ExpValue)
-> ExpValue -> [Int] -> ScriptM ()
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m ()
foldM_ ExpValue -> Int -> ScriptM ExpValue
frame ExpValue
initial [Int
0 .. Int
num_frames Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1]
where
frame :: ExpValue -> Int -> ScriptM ExpValue
frame ExpValue
old_state Int
j = do
ExpValue
v <-
EvalBuiltin ScriptM -> ScriptServer -> Exp -> ScriptM ExpValue
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
EvalBuiltin m -> ScriptServer -> Exp -> m ExpValue
evalExp EvalBuiltin ScriptM
literateBuiltin (Env -> ScriptServer
envServer Env
env)
(Exp -> ScriptM ExpValue)
-> ([ExpValue] -> Exp) -> [ExpValue] -> ScriptM ExpValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Func -> [Exp] -> Exp
Call (Text -> Func
FuncFut Text
stepfun)
([Exp] -> Exp) -> ([ExpValue] -> [Exp]) -> [ExpValue] -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExpValue -> Exp) -> [ExpValue] -> [Exp]
forall a b. (a -> b) -> [a] -> [b]
map ExpValue -> Exp
valueToExp
([ExpValue] -> ScriptM ExpValue) -> [ExpValue] -> ScriptM ExpValue
forall a b. (a -> b) -> a -> b
$ [ExpValue]
closure [ExpValue] -> [ExpValue] -> [ExpValue]
forall a. [a] -> [a] -> [a]
++ [ExpValue
old_state]
ScriptServer -> ExpValue -> ScriptM ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
ScriptServer -> ExpValue -> m ()
freeValue (Env -> ScriptServer
envServer Env
env) ExpValue
old_state
let nope :: ScriptM a
nope =
Text -> ScriptM a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ScriptM a) -> Text -> ScriptM a
forall a b. (a -> b) -> a -> b
$
Text
"Cannot handle step function return type: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Compound ScriptValueType -> Text
forall a. Pretty a => a -> Text
prettyText ((ScriptValue ValOrVar -> ScriptValueType)
-> ExpValue -> Compound ScriptValueType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ScriptValue ValOrVar -> ScriptValueType
forall v. ScriptValue v -> ScriptValueType
scriptValueType ExpValue
v)
case ExpValue
v of
ValueTuple [arr_v :: ExpValue
arr_v@(ValueAtom SValue {}), ExpValue
new_state] -> do
ValueAtom Value
arr <- ScriptServer -> ExpValue -> ScriptM CompoundValue
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
ScriptServer -> ExpValue -> m CompoundValue
getExpValue (Env -> ScriptServer
envServer Env
env) ExpValue
arr_v
ScriptServer -> ExpValue -> ScriptM ()
forall (m :: * -> *).
(MonadError Text m, MonadIO m) =>
ScriptServer -> ExpValue -> m ()
freeValue (Env -> ScriptServer
envServer Env
env) ExpValue
arr_v
case Value -> Maybe ByteString
valueToBMP Value
arr of
Maybe ByteString
Nothing -> ScriptM ExpValue
forall a. ScriptM a
nope
Just ByteString
bmp -> do
String -> Int -> ByteString -> ScriptM ()
forall (m :: * -> *).
MonadIO m =>
String -> Int -> ByteString -> m ()
writeBMPFile String
dir Int
j ByteString
bmp
ExpValue -> ScriptM ExpValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExpValue
new_state
ExpValue
_ -> ScriptM ExpValue
forall a. ScriptM a
nope
writeBMPFile :: String -> Int -> ByteString -> m ()
writeBMPFile String
dir Int
j ByteString
bmp =
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
LBS.writeFile (String -> Int -> String
bmpfile String
dir Int
j) ByteString
bmp
bmpsToVideo :: String -> m String
bmpsToVideo String
dir = do
m Text -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m Text -> m ()) -> m Text -> m ()
forall a b. (a -> b) -> a -> b
$
String -> [String] -> Text -> m Text
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> [String] -> Text -> m Text
system
String
"ffmpeg"
[ String
"-y",
String
"-r",
Int -> String
forall a. Show a => a -> String
show Int
framerate,
String
"-i",
String
dir String -> ShowS
</> String
"frame%010d.bmp",
String
"-c:v",
String
"libvpx-vp9",
String
"-pix_fmt",
String
"yuv420p",
String
"-b:v",
String
"2M",
String
dir String -> ShowS
</> String
"video.webm"
]
Text
forall a. Monoid a => a
mempty
String -> m String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> m String) -> String -> m String
forall a b. (a -> b) -> a -> b
$ String
dir String -> ShowS
</> String
"video.webm"
onWebM :: String -> String -> f ()
onWebM String
videofile String
webmfile
| Text
format Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"gif" =
f Text -> f ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (f Text -> f ()) -> f Text -> f ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> Text -> f Text
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> [String] -> Text -> m Text
system String
"ffmpeg" [String
"-i", String
webmfile, String
videofile] Text
forall a. Monoid a => a
mempty
| Bool
otherwise =
IO () -> f ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> f ()) -> IO () -> f ()
forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
copyFile String
webmfile String
videofile
data Failure = Failure | Success
deriving (Failure -> Failure -> Bool
(Failure -> Failure -> Bool)
-> (Failure -> Failure -> Bool) -> Eq Failure
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Failure -> Failure -> Bool
$c/= :: Failure -> Failure -> Bool
== :: Failure -> Failure -> Bool
$c== :: Failure -> Failure -> Bool
Eq, Eq Failure
Eq Failure
-> (Failure -> Failure -> Ordering)
-> (Failure -> Failure -> Bool)
-> (Failure -> Failure -> Bool)
-> (Failure -> Failure -> Bool)
-> (Failure -> Failure -> Bool)
-> (Failure -> Failure -> Failure)
-> (Failure -> Failure -> Failure)
-> Ord Failure
Failure -> Failure -> Bool
Failure -> Failure -> Ordering
Failure -> Failure -> Failure
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Failure -> Failure -> Failure
$cmin :: Failure -> Failure -> Failure
max :: Failure -> Failure -> Failure
$cmax :: Failure -> Failure -> Failure
>= :: Failure -> Failure -> Bool
$c>= :: Failure -> Failure -> Bool
> :: Failure -> Failure -> Bool
$c> :: Failure -> Failure -> Bool
<= :: Failure -> Failure -> Bool
$c<= :: Failure -> Failure -> Bool
< :: Failure -> Failure -> Bool
$c< :: Failure -> Failure -> Bool
compare :: Failure -> Failure -> Ordering
$ccompare :: Failure -> Failure -> Ordering
$cp1Ord :: Eq Failure
Ord, Int -> Failure -> ShowS
[Failure] -> ShowS
Failure -> String
(Int -> Failure -> ShowS)
-> (Failure -> String) -> ([Failure] -> ShowS) -> Show Failure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Failure] -> ShowS
$cshowList :: [Failure] -> ShowS
show :: Failure -> String
$cshow :: Failure -> String
showsPrec :: Int -> Failure -> ShowS
$cshowsPrec :: Int -> Failure -> ShowS
Show)
processBlock :: Env -> Block -> IO (Failure, T.Text, Files)
processBlock :: Env -> Block -> IO (Failure, Text, Files)
processBlock Env
_ (BlockCode Text
code)
| Text -> Bool
T.null Text
code = (Failure, Text, Files) -> IO (Failure, Text, Files)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure
Success, Text
"\n", Files
forall a. Monoid a => a
mempty)
| Bool
otherwise = (Failure, Text, Files) -> IO (Failure, Text, Files)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure
Success, Text
"\n```futhark\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
code Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"```\n\n", Files
forall a. Monoid a => a
mempty)
processBlock Env
_ (BlockComment Text
text) =
(Failure, Text, Files) -> IO (Failure, Text, Files)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure
Success, Text
text, Files
forall a. Monoid a => a
mempty)
processBlock Env
env (BlockDirective Directive
directive) = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Options -> Int
scriptVerbose (Env -> Options
envOpts Env
env) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr (Text -> IO ()) -> (Doc -> Text) -> Doc -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> Text
forall a. Pretty a => a -> Text
prettyText (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$
Doc
"Processing " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc -> Doc
PP.align (Directive -> Doc
forall a. Pretty a => a -> Doc
PP.ppr Directive
directive) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"..."
let prompt :: Text
prompt = case Directive
directive of
DirectiveCovert Directive
_ -> Text
forall a. Monoid a => a
mempty
DirectiveBrief Directive
_ ->
Text
"```\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Doc -> Text
forall a. Pretty a => a -> Text
prettyText (Bool -> Directive -> Doc
pprDirective Bool
False Directive
directive) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n```\n"
Directive
_ ->
Text
"```\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Doc -> Text
forall a. Pretty a => a -> Text
prettyText (Bool -> Directive -> Doc
pprDirective Bool
True Directive
directive) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n```\n"
env' :: Env
env' = Env
env {envHash :: Int
envHash = (Int, Text) -> Int
forall a. Hashable a => a -> Int
hash (Env -> Int
envHash Env
env, Directive -> Text
forall a. Pretty a => a -> Text
prettyText Directive
directive)}
(Either Text Text
r, Files
files) <- ScriptM Text -> IO (Either Text Text, Files)
forall a. ScriptM a -> IO (Either Text a, Files)
runScriptM (ScriptM Text -> IO (Either Text Text, Files))
-> ScriptM Text -> IO (Either Text Text, Files)
forall a b. (a -> b) -> a -> b
$ Env -> Directive -> ScriptM Text
processDirective Env
env' Directive
directive
case Either Text Text
r of
Left Text
err -> Text -> Text -> Files -> IO (Failure, Text, Files)
forall c. Text -> Text -> c -> IO (Failure, Text, c)
failed Text
prompt Text
err Files
files
Right Text
t -> (Failure, Text, Files) -> IO (Failure, Text, Files)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure
Success, Text
prompt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t, Files
files)
where
failed :: Text -> Text -> c -> IO (Failure, Text, c)
failed Text
prompt Text
err c
files = do
let message :: Text
message = Directive -> Text
forall a. Pretty a => a -> Text
prettyTextOneLine Directive
directive Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" failed:\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
err Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
IO () -> IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Handle -> Text -> IO ()
T.hPutStr Handle
stderr Text
message
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Options -> Bool
scriptStopOnError (Env -> Options
envOpts Env
env)) IO ()
forall a. IO a
exitFailure
(Failure, Text, c) -> IO (Failure, Text, c)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( Failure
Failure,
[Text] -> Text
T.unlines [Text
prompt, Text
"**FAILED**", Text
"```", Text
err, Text
"```"],
c
files
)
cleanupImgDir :: Env -> Files -> IO ()
cleanupImgDir :: Env -> Files -> IO ()
cleanupImgDir Env
env Files
keep_files =
(String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> IO ()
toRemove ([String] -> IO ()) -> ([String] -> [String]) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Files -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Files
keep_files))
([String] -> IO ()) -> IO [String] -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (String -> IO [String]
directoryContents (Env -> String
envImgDir Env
env) IO [String] -> (IOException -> IO [String]) -> IO [String]
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
`catchError` IOException -> IO [String]
forall (f :: * -> *) a.
MonadError IOException f =>
IOException -> f [a]
onError)
where
onError :: IOException -> f [a]
onError IOException
e
| IOException -> Bool
isDoesNotExistError IOException
e = [a] -> f [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
| Bool
otherwise = IOException -> f [a]
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError IOException
e
toRemove :: String -> IO ()
toRemove String
f = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Options -> Int
scriptVerbose (Env -> Options
envOpts Env
env) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"Deleting unused file: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
f
String -> IO ()
removePathForcibly String
f
processScript :: Env -> [Block] -> IO (Failure, T.Text)
processScript :: Env -> [Block] -> IO (Failure, Text)
processScript Env
env [Block]
script = do
([Failure]
failures, [Text]
outputs, [Files]
files) <-
[(Failure, Text, Files)] -> ([Failure], [Text], [Files])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip3 ([(Failure, Text, Files)] -> ([Failure], [Text], [Files]))
-> IO [(Failure, Text, Files)] -> IO ([Failure], [Text], [Files])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> IO (Failure, Text, Files))
-> [Block] -> IO [(Failure, Text, Files)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Env -> Block -> IO (Failure, Text, Files)
processBlock Env
env) [Block]
script
Env -> Files -> IO ()
cleanupImgDir Env
env (Files -> IO ()) -> Files -> IO ()
forall a b. (a -> b) -> a -> b
$ [Files] -> Files
forall a. Monoid a => [a] -> a
mconcat [Files]
files
(Failure, Text) -> IO (Failure, Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Failure -> Failure -> Failure) -> Failure -> [Failure] -> Failure
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Failure -> Failure -> Failure
forall a. Ord a => a -> a -> a
min Failure
Success [Failure]
failures, [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text]
outputs)
commandLineOptions :: [FunOptDescr Options]
commandLineOptions :: [FunOptDescr Options]
commandLineOptions =
[ String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
[]
[String
"backend"]
( (String -> Either (IO ()) (Options -> Options))
-> String -> ArgDescr (Either (IO ()) (Options -> Options))
forall a. (String -> a) -> String -> ArgDescr a
ReqArg
(\String
backend -> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config -> Options
config {scriptBackend :: String
scriptBackend = String
backend})
String
"PROGRAM"
)
String
"The compiler used (defaults to 'c').",
String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
[]
[String
"futhark"]
( (String -> Either (IO ()) (Options -> Options))
-> String -> ArgDescr (Either (IO ()) (Options -> Options))
forall a. (String -> a) -> String -> ArgDescr a
ReqArg
(\String
prog -> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config -> Options
config {scriptFuthark :: Maybe String
scriptFuthark = String -> Maybe String
forall a. a -> Maybe a
Just String
prog})
String
"PROGRAM"
)
String
"The binary used for operations (defaults to same binary as 'futhark script').",
String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
String
"p"
[String
"pass-option"]
( (String -> Either (IO ()) (Options -> Options))
-> String -> ArgDescr (Either (IO ()) (Options -> Options))
forall a. (String -> a) -> String -> ArgDescr a
ReqArg
( \String
opt ->
(Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config ->
Options
config {scriptExtraOptions :: [String]
scriptExtraOptions = String
opt String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Options -> [String]
scriptExtraOptions Options
config}
)
String
"OPT"
)
String
"Pass this option to programs being run.",
String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
[]
[String
"pass-compiler-option"]
( (String -> Either (IO ()) (Options -> Options))
-> String -> ArgDescr (Either (IO ()) (Options -> Options))
forall a. (String -> a) -> String -> ArgDescr a
ReqArg
( \String
opt ->
(Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config ->
Options
config {scriptCompilerOptions :: [String]
scriptCompilerOptions = String
opt String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Options -> [String]
scriptCompilerOptions Options
config}
)
String
"OPT"
)
String
"Pass this option to the compiler.",
String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
[]
[String
"skip-compilation"]
(Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options))
forall a. a -> ArgDescr a
NoArg (Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options)))
-> Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options))
forall a b. (a -> b) -> a -> b
$ (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config -> Options
config {scriptSkipCompilation :: Bool
scriptSkipCompilation = Bool
True})
String
"Use already compiled program.",
String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
String
"v"
[String
"verbose"]
(Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options))
forall a. a -> ArgDescr a
NoArg (Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options)))
-> Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options))
forall a b. (a -> b) -> a -> b
$ (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config -> Options
config {scriptVerbose :: Int
scriptVerbose = Options -> Int
scriptVerbose Options
config Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1})
String
"Enable logging. Pass multiple times for more.",
String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
String
"o"
[String
"output"]
((String -> Either (IO ()) (Options -> Options))
-> String -> ArgDescr (Either (IO ()) (Options -> Options))
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (\String
opt -> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config -> Options
config {scriptOutput :: Maybe String
scriptOutput = String -> Maybe String
forall a. a -> Maybe a
Just String
opt}) String
"FILE")
String
"Enable logging. Pass multiple times for more.",
String
-> [String]
-> ArgDescr (Either (IO ()) (Options -> Options))
-> String
-> FunOptDescr Options
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option
[]
[String
"stop-on-error"]
(Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options))
forall a. a -> ArgDescr a
NoArg (Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options)))
-> Either (IO ()) (Options -> Options)
-> ArgDescr (Either (IO ()) (Options -> Options))
forall a b. (a -> b) -> a -> b
$ (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. b -> Either a b
Right ((Options -> Options) -> Either (IO ()) (Options -> Options))
-> (Options -> Options) -> Either (IO ()) (Options -> Options)
forall a b. (a -> b) -> a -> b
$ \Options
config -> Options
config {scriptStopOnError :: Bool
scriptStopOnError = Bool
True})
String
"Stop and do not produce output file if any directive fails."
]
main :: String -> [String] -> IO ()
main :: String -> [String] -> IO ()
main = Options
-> [FunOptDescr Options]
-> String
-> ([String] -> Options -> Maybe (IO ()))
-> String
-> [String]
-> IO ()
forall cfg.
cfg
-> [FunOptDescr cfg]
-> String
-> ([String] -> cfg -> Maybe (IO ()))
-> String
-> [String]
-> IO ()
mainWithOptions Options
initialOptions [FunOptDescr Options]
commandLineOptions String
"program" (([String] -> Options -> Maybe (IO ()))
-> String -> [String] -> IO ())
-> ([String] -> Options -> Maybe (IO ()))
-> String
-> [String]
-> IO ()
forall a b. (a -> b) -> a -> b
$ \[String]
args Options
opts ->
case [String]
args of
[String
prog] -> IO () -> Maybe (IO ())
forall a. a -> Maybe a
Just (IO () -> Maybe (IO ())) -> IO () -> Maybe (IO ())
forall a b. (a -> b) -> a -> b
$ do
String
futhark <- IO String -> (String -> IO String) -> Maybe String -> IO String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO String
getExecutablePath String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String -> IO String) -> Maybe String -> IO String
forall a b. (a -> b) -> a -> b
$ Options -> Maybe String
scriptFuthark Options
opts
[Block]
script <- String -> IO [Block]
parseProgFile String
prog
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Options -> Bool
scriptSkipCompilation Options
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let entryOpt :: Text -> String
entryOpt Text
v = String
"--entry=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
v
compile_options :: [String]
compile_options =
String
"--server" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Text -> String
entryOpt (Set Text -> [Text]
forall a. Set a -> [a]
S.toList ([Block] -> Set Text
varsInScripts [Block]
script))
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ Options -> [String]
scriptCompilerOptions Options
opts
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Options -> Int
scriptVerbose Options
opts Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"Compiling " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
prog Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"..."
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Options -> Int
scriptVerbose Options
opts Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords [String]
compile_options
let onError :: t Text -> IO b
onError t Text
err = do
(Text -> IO ()) -> t Text -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr) t Text
err
IO b
forall a. IO a
exitFailure
IO (ByteString, ByteString) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (ByteString, ByteString) -> IO ())
-> IO (ByteString, ByteString) -> IO ()
forall a b. (a -> b) -> a -> b
$
([Text] -> IO (ByteString, ByteString))
-> ((ByteString, ByteString) -> IO (ByteString, ByteString))
-> Either [Text] (ByteString, ByteString)
-> IO (ByteString, ByteString)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either [Text] -> IO (ByteString, ByteString)
forall (t :: * -> *) b. Foldable t => t Text -> IO b
onError (ByteString, ByteString) -> IO (ByteString, ByteString)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either [Text] (ByteString, ByteString)
-> IO (ByteString, ByteString))
-> (ExceptT [Text] IO (ByteString, ByteString)
-> IO (Either [Text] (ByteString, ByteString)))
-> ExceptT [Text] IO (ByteString, ByteString)
-> IO (ByteString, ByteString)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ExceptT [Text] IO (ByteString, ByteString)
-> IO (Either [Text] (ByteString, ByteString))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT [Text] IO (ByteString, ByteString)
-> IO (ByteString, ByteString))
-> ExceptT [Text] IO (ByteString, ByteString)
-> IO (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$
[String]
-> FutharkExe
-> String
-> String
-> ExceptT [Text] IO (ByteString, ByteString)
forall (m :: * -> *).
(MonadIO m, MonadError [Text] m) =>
[String]
-> FutharkExe -> String -> String -> m (ByteString, ByteString)
compileProgram [String]
compile_options (String -> FutharkExe
FutharkExe String
futhark) (Options -> String
scriptBackend Options
opts) String
prog
let onError :: Text -> IO b
onError Text
err = do
Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr Text
err
IO b
forall a. IO a
exitFailure
Int
proghash <-
(Text -> IO Int) -> (Text -> IO Int) -> Either Text Text -> IO Int
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Text -> IO Int
forall b. Text -> IO b
onError (Int -> IO Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int -> IO Int) -> (Text -> Int) -> Text -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int
forall a. Hashable a => a -> Int
hash) (Either Text Text -> IO Int)
-> (ExceptT Text IO Text -> IO (Either Text Text))
-> ExceptT Text IO Text
-> IO Int
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ExceptT Text IO Text -> IO (Either Text Text)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT Text IO Text -> IO Int) -> ExceptT Text IO Text -> IO Int
forall a b. (a -> b) -> a -> b
$
String -> [String] -> Text -> ExceptT Text IO Text
forall (m :: * -> *).
(MonadIO m, MonadError Text m) =>
String -> [String] -> Text -> m Text
system String
futhark [String
"hash", String
prog] Text
forall a. Monoid a => a
mempty
let mdfile :: String
mdfile = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe (String
prog String -> ShowS
`replaceExtension` String
"md") (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ Options -> Maybe String
scriptOutput Options
opts
imgdir :: String
imgdir = ShowS
dropExtension String
mdfile String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"-img"
run_options :: [String]
run_options = Options -> [String]
scriptExtraOptions Options
opts
String -> [String] -> (ScriptServer -> IO ()) -> IO ()
forall a. String -> [String] -> (ScriptServer -> IO a) -> IO a
withScriptServer (String
"." String -> ShowS
</> ShowS
dropExtension String
prog) [String]
run_options ((ScriptServer -> IO ()) -> IO ())
-> (ScriptServer -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ScriptServer
server -> do
let env :: Env
env =
Env :: String -> Options -> ScriptServer -> Int -> Env
Env
{ envServer :: ScriptServer
envServer = ScriptServer
server,
envOpts :: Options
envOpts = Options
opts,
envHash :: Int
envHash = Int
proghash,
envImgDir :: String
envImgDir = String
imgdir
}
(Failure
failure, Text
md) <- Env -> [Block] -> IO (Failure, Text)
processScript Env
env [Block]
script
String -> Text -> IO ()
T.writeFile String
mdfile Text
md
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Failure
failure Failure -> Failure -> Bool
forall a. Eq a => a -> a -> Bool
== Failure
Failure) IO ()
forall a. IO a
exitFailure
[String]
_ -> Maybe (IO ())
forall a. Maybe a
Nothing