从编译的可执行文件生成CLI shell脚本代码?

San*_*der 8 shell scheme ocaml haskell robustness

问题,讨论主题

我对编写命令行shell脚本源代码非常感兴趣,这些源代码是用更健壮,性能更好且独立于平台的编译语言(例如OCaml)编写的代码编写的.基本上,您可以使用编译语言编程来执行与您想要的操作系统的任何交互(我建议:更复杂的交互或以平台无关的方式不容易做到的交互),最后您将编译它到本机二进制可执行文件(最好),它会生成一个shell脚本,在shell中生成你在编译语言中编写的内容.[ 补充 ]:使用'效果',我的意思是设置环境变量和shell选项,执行某些非标准命令(标准脚本'glue'将由编译的可执行文件处理,并将保留在生成的shell脚本之外)等等.

到目前为止我还没有找到任何此类解决方案.与今天的其他可能性相比,实现它似乎相对容易*,比如将OCaml编译为JavaScript.

  • 是否已经(公开)实现了我所描述的内容?
  • 与我所描述的(非常)相似的其他可能性有哪些,以及它们与此有何不同?(脑到语编译(从编译到sh)会浮现在脑海中,虽然这似乎不必要地难以实现.)

不是故意的

  1. 另一种shell(如Scsh).您管理的系统可能并不总是允许用户或一个管理员选择shell,我也希望它是一个专门为其他人(客户,同事和其他人)提供的系统管理解决方案,也是不能指望的人接受不同的外壳.
  2. 另一种解释器,用于非交互式shell脚本通常用于的目的(如ocamlscript).就个人而言,我没有为此目的避免shell脚本的问题.我这样做是因为shell脚本通常难以维护(例如,对某些字符敏感并且操纵可变的东西,如'命令'),并且难以制作到与流行的通用编程语言可提供的功能相同的水平(对于例如,在这方面比较Bash和Python).但是,在某些情况下需要使用本机shell脚本,例如shell启动时由shell发送的shell配置文件.

背景

实际应用

你们中的一些人可能怀疑我所描述的实际用途.这样做的一个实际应用是根据各种条件定义一个shell配置文件(例如,配置文件来源的系统平台/操作系统,安全策略后面的内容,具体shell,登录/非登录类型shell,交互/非交互式shell).作为shell脚本的(精心设计的)通用shell配置文件的优势在于性能的提高(可能生成压缩/优化的源代码而不是人工编写的脚本解释的本机机器代码),健壮性(类型检查,异常处理) ,编译功能的时间验证,生成的二进制可执行文件的加密签名),功能(更少或不依赖于用户域CLI工具,不限制使用所有可能平台的CLI工具所涵盖的最低功能)和跨平台功能(在像单一UNIX规范这样的实践标准只是意味着很多,而且很多shell配置文件概念都会转移到非Windows平台,如同PowerShell一样.

实施细节,附带问题

  1. 程序员应该能够控制生成的shell脚本的通用程度.例如,可能是每次运行二进制可执行文件并输出适当的shell配置文件代码,或者它可以简单地生成针对一次运行的情况定制的固定shell脚本文件.在后一种情况下,列出的优势 - 特别是那些稳健性(例如异常处理和依赖用户工具)的优势更加有限.[添加]
  2. 生成的shell脚本是以某种形式的通用shell脚本(如GNU autoconf生成)还是shell(原生脚本)适应(动态或不适用于)特定shell对我来说不是主要问题.
  3. easy*:在我看来,这可以通过在库中为基本的shell内置函数提供基本可用的函数来实现.这样的函数只是将自身加上传递的参数转换为语义上合适且语法正确的shell脚本语句(作为字符串).

感谢您的进一步想法,特别是对于具体的建议!

Gab*_*lez 13

没有Haskell库,但您可以使用抽象语法树实现它.我将构建一个简单的玩具示例,该示例构建一个与语言无关的抽象语法树,然后应用将树转换为等效Bash脚本的后端.

我将使用两个技巧来建模Haskell中的语法树:

  • 使用GADT模型化的Bash表达式
  • 使用免费monad实现DSL

GADT技巧相当简单,我使用了几种语言扩展来增强语法:

{-# LANGUAGE GADTs
           , FlexibleInstances
           , RebindableSyntax
           , OverloadedStrings #-}

import Data.String
import Prelude hiding ((++))

type UniqueID = Integer

newtype VStr = VStr UniqueID
newtype VInt = VInt UniqueID

data Expr a where
    StrL   :: String  -> Expr String  -- String  literal
    IntL   :: Integer -> Expr Integer -- Integer literal
    StrV   :: VStr    -> Expr String  -- String  variable
    IntV   :: VInt    -> Expr Integer -- Integer variable
    Plus   :: Expr Integer -> Expr Integer -> Expr Integer
    Concat :: Expr String  -> Expr String  -> Expr String
    Shown  :: Expr Integer -> Expr String

instance Num (Expr Integer) where
    fromInteger = IntL
    (+)         = Plus
    (*)    = undefined
    abs    = undefined
    signum = undefined

instance IsString (Expr String) where
    fromString = StrL

(++) :: Expr String -> Expr String -> Expr String
(++) = Concat
Run Code Online (Sandbox Code Playgroud)

这让我们可以在DSL中构建类型化的Bash表达式.我只实现了一些原始操作,但您可以轻松想象如何将它扩展到其他人.

如果我们不使用任何语言扩展,我们可能会编写如下表达式:

Concat (StrL "Test") (Shown (Plus (IntL 4) (IntL 5))) :: Expr String
Run Code Online (Sandbox Code Playgroud)

这没关系,但不是很性感.上面的代码使用RebindableSyntax重写数字文字,让您可以替换(IntL n)n:

Concat (StrL "Test") (Shown (Plus 4 5)) :: Expr String
Run Code Online (Sandbox Code Playgroud)

同样,我有Expr Integer实现Num,以便您可以使用+以下命令添加数字文字:

Concat (StrL "Test") (Shown (4 + 5)) :: Expr String
Run Code Online (Sandbox Code Playgroud)

同样,我用OverloadedStrings这样就可以代替所有出现的(StrL str)只有str:

Concat "Test" (Shown (4 + 5)) :: Expr String
Run Code Online (Sandbox Code Playgroud)

我还重写了Prelude (++)运算符,以便我们可以将表达式连接起来,就像它们是Haskell字符串一样:

"Test" ++ Shown (4 + 5) :: Expr String
Run Code Online (Sandbox Code Playgroud)

除了Shown从整数到字符串的转换之外,它看起来就像本机Haskell代码.整齐!

现在我们需要一种方法来创建一个用户友好的DSL,最好用Monad语法糖.这是免费monad进来的地方.

免费monad采用函数表示语法树中的单个步骤,并从中创建语法树.作为奖励,它始终是任何仿函数的monad,因此您可以使用do符号组装这些语法树.

为了演示它,我将在前面的代码段中添加更多代码:

-- This is in addition to the previous code
{-# LANGUAGE DeriveFunctor #-}

import Control.Monad.Free

data ScriptF next
    = NewInt (Expr Integer) (VInt -> next)
    | NewStr (Expr String ) (VStr -> next)
    | SetStr VStr (Expr String ) next
    | SetInt VInt (Expr Integer) next
    | Echo (Expr String) next
    | Exit (Expr Integer)
  deriving (Functor)

type Script = Free ScriptF

newInt :: Expr Integer -> Script VInt
newInt n = liftF $ NewInt n id

newStr :: Expr String -> Script VStr
newStr str = liftF $ NewStr str id

setStr :: VStr -> Expr String -> Script ()
setStr v expr = liftF $ SetStr v expr ()

setInt :: VInt -> Expr Integer -> Script ()
setInt v expr = liftF $ SetInt v expr ()

echo :: Expr String -> Script ()
echo expr = liftF $ Echo expr ()

exit :: Expr Integer -> Script r
exit expr = liftF $ Exit expr
Run Code Online (Sandbox Code Playgroud)

ScriptF函子代表了我们的DSL足下. Free本质上创建一个ScriptF步骤列表并定义一个monad,我们可以在其中汇编这些步骤的列表.您可以将该liftF功能视为只需一步并使用一个操作创建列表.

然后我们可以使用do符号来组合这些步骤,其中do符号连接这些操作列表:

script :: Script r
script = do
    hello <- newStr "Hello, "
    world <- newStr "World!"
    setStr hello (StrV hello ++ StrV world)
    echo ("hello: " ++ StrV hello)
    echo ("world: " ++ StrV world)
    x <- newInt 4
    y <- newInt 5
    exit (IntV x + IntV y)
Run Code Online (Sandbox Code Playgroud)

这显示了我们如何组装我们刚刚定义的原始步骤.这具有monad的所有优良属性,包括对monadic组合器的支持,例如forM_:

import Control.Monad

script2 :: Script ()
script2 = forM_ [1..5] $ \i -> do
    x <- newInt (IntL i)
    setInt x (IntV x + 5)
    echo (Shown (IntV x))
Run Code Online (Sandbox Code Playgroud)

注意我们的Scriptmonad 如何强制执行类型安全,即使我们的目标语言可能是无类型的.您不能意外地使用String它期望的文字,Integer反之亦然.您必须使用类型安全转换在它们之间显式转换Shown.

另请注意,Scriptmonad在exit语句后吞下任何命令.他们甚至在到达口译员之前就被忽略了.当然,您可以通过重写Exit构造函数来接受后续next步骤来更改此行为.

这些抽象语法树是纯粹的,这意味着我们可以纯粹地检查和解释它们.我们可以定义几个后端,例如将我们的Scriptmonad转换为等效的Bash脚本的Bash后端:

bashExpr :: Expr a -> String
bashExpr expr = case expr of
    StrL str           -> str
    IntL int           -> show int
    StrV (VStr nID)    -> "${S" <> show nID <> "}"
    IntV (VInt nID)    -> "${I" <> show nID <> "}"
    Plus   expr1 expr2 ->
        concat ["$((", bashExpr expr1, "+", bashExpr expr2, "))"]
    Concat expr1 expr2 -> bashExpr expr1 <> bashExpr expr2
    Shown  expr'       -> bashExpr expr'

bashBackend :: Script r -> String
bashBackend script = go 0 0 script where
    go nStrs nInts script =
        case script of
            Free f -> case f of
                NewInt e k ->
                    "I" <> show nInts <> "=" <> bashExpr e <> "\n" <>
                        go nStrs (nInts + 1) (k (VInt nInts))
                NewStr e k ->
                    "S" <> show nStrs <> "=" <> bashExpr e <> "\n" <>
                        go (nStrs + 1) nInts (k (VStr nStrs))
                SetStr (VStr nID) e script' ->
                    "S" <> show nID <> "=" <> bashExpr e <> "\n" <>
                        go nStrs nInts script'
                SetInt (VInt nID) e script' ->
                    "I" <> show nID <> "=" <> bashExpr e <> "\n" <>
                        go nStrs nInts script'
                Echo e script' ->
                    "echo " <> bashExpr e <> "\n" <>
                        go nStrs nInts script'
                Exit e ->
                    "exit " <> bashExpr e <> "\n"
            Pure _ -> ""
Run Code Online (Sandbox Code Playgroud)

我定义了两个解释器:一个用于表达式语法树,另一个用于monadic DSL语法树.这两个解释器将任何与语言无关的程序编译成等效的Bash程序,表示为String.当然,代表性的选择完全取决于您.

每次我们的Scriptmonad请求一个新变量时,这个解释器会自动创建新的唯一变量.

让我们试试这个解释器,看它是否有效:

>>> putStr $ bashBackend script
S0=Hello, 
S1=World!
S0=${S0}${S1}
echo hello: ${S0}
echo world: ${S1}
I0=4
I1=5
exit $((${I0}+${I1}))
Run Code Online (Sandbox Code Playgroud)

它生成一个bash脚本,执行等效的语言独立程序.同样,它也script2可以很好地翻译:

>>> putStr $ bashBackend script2
I0=1
I0=$((${I0}+5))
echo ${I0}
I1=2
I1=$((${I1}+5))
echo ${I1}
I2=3
I2=$((${I2}+5))
echo ${I2}
I3=4
I3=$((${I3}+5))
echo ${I3}
I4=5
I4=$((${I4}+5))
echo ${I4}
Run Code Online (Sandbox Code Playgroud)

所以这显然不是很全面,但希望能为您提供一些关于如何在Haskell中实现此实现的想法.如果你想了解更多关于免费monad的使用,我建议你阅读:

我还附上了完整的代码:

{-# LANGUAGE GADTs
           , FlexibleInstances
           , RebindableSyntax
           , DeriveFunctor
           , OverloadedStrings #-}

import Control.Monad.Free
import Control.Monad
import Data.Monoid
import Data.String
import Prelude hiding ((++))

type UniqueID = Integer

newtype VStr = VStr UniqueID
newtype VInt = VInt UniqueID

data Expr a where
    StrL   :: String  -> Expr String  -- String  literal
    IntL   :: Integer -> Expr Integer -- Integer literal
    StrV   :: VStr    -> Expr String  -- String  variable
    IntV   :: VInt    -> Expr Integer -- Integer variable
    Plus   :: Expr Integer -> Expr Integer -> Expr Integer
    Concat :: Expr String  -> Expr String  -> Expr String
    Shown  :: Expr Integer -> Expr String

instance Num (Expr Integer) where
    fromInteger = IntL
    (+)         = Plus
    (*)    = undefined
    abs    = undefined
    signum = undefined

instance IsString (Expr String) where
    fromString = StrL

(++) :: Expr String -> Expr String -> Expr String
(++) = Concat

data ScriptF next
    = NewInt (Expr Integer) (VInt -> next)
    | NewStr (Expr String ) (VStr -> next)
    | SetStr VStr (Expr String ) next
    | SetInt VInt (Expr Integer) next
    | Echo (Expr String) next
    | Exit (Expr Integer)
  deriving (Functor)

type Script = Free ScriptF

newInt :: Expr Integer -> Script VInt
newInt n = liftF $ NewInt n id

newStr :: Expr String -> Script VStr
newStr str = liftF $ NewStr str id

setStr :: VStr -> Expr String -> Script ()
setStr v expr = liftF $ SetStr v expr ()

setInt :: VInt -> Expr Integer -> Script ()
setInt v expr = liftF $ SetInt v expr ()

echo :: Expr String -> Script ()
echo expr = liftF $ Echo expr ()

exit :: Expr Integer -> Script r
exit expr = liftF $ Exit expr

script :: Script r
script = do
    hello <- newStr "Hello, "
    world <- newStr "World!"
    setStr hello (StrV hello ++ StrV world)
    echo ("hello: " ++ StrV hello)
    echo ("world: " ++ StrV world)
    x <- newInt 4
    y <- newInt 5
    exit (IntV x + IntV y)

script2 :: Script ()
script2 = forM_ [1..5] $ \i -> do
    x <- newInt (IntL i)
    setInt x (IntV x + 5)
    echo (Shown (IntV x))

bashExpr :: Expr a -> String
bashExpr expr = case expr of
    StrL str           -> str
    IntL int           -> show int
    StrV (VStr nID)    -> "${S" <> show nID <> "}"
    IntV (VInt nID)    -> "${I" <> show nID <> "}"
    Plus   expr1 expr2 ->
        concat ["$((", bashExpr expr1, "+", bashExpr expr2, "))"]
    Concat expr1 expr2 -> bashExpr expr1 <> bashExpr expr2
    Shown  expr'       -> bashExpr expr'

bashBackend :: Script r -> String
bashBackend script = go 0 0 script where
    go nStrs nInts script =
        case script of
            Free f -> case f of
                NewInt e k ->
                    "I" <> show nInts <> "=" <> bashExpr e <> "\n" <> 
                        go nStrs (nInts + 1) (k (VInt nInts))
                NewStr e k ->
                    "S" <> show nStrs <> "=" <> bashExpr e <> "\n" <>
                        go (nStrs + 1) nInts (k (VStr nStrs))
                SetStr (VStr nID) e script' ->
                    "S" <> show nID <> "=" <> bashExpr e <> "\n" <>
                        go nStrs nInts script'
                SetInt (VInt nID) e script' ->
                    "I" <> show nID <> "=" <> bashExpr e <> "\n" <>
                        go nStrs nInts script'
                Echo e script' ->
                    "echo " <> bashExpr e <> "\n" <>
                        go nStrs nInts script'
                Exit e ->
                    "exit " <> bashExpr e <> "\n"
            Pure _ -> ""
Run Code Online (Sandbox Code Playgroud)