{-# LANGUAGE FlexibleContexts #-}
module Futhark.CLI.Multicore (main) where
import Futhark.Actions (compileMulticoreAction)
import Futhark.Compiler.CLI
import Futhark.Passes (multicorePipeline)
main :: String -> [String] -> IO ()
main :: String -> [String] -> IO ()
main = ()
-> [CompilerOption ()]
-> String
-> String
-> Pipeline SOACS MCMem
-> (FutharkConfig
-> () -> CompilerMode -> String -> Prog MCMem -> FutharkM ())
-> String
-> [String]
-> IO ()
forall cfg lore.
cfg
-> [CompilerOption cfg]
-> String
-> String
-> Pipeline SOACS lore
-> (FutharkConfig
-> cfg -> CompilerMode -> String -> Prog lore -> FutharkM ())
-> String
-> [String]
-> IO ()
compilerMain
()
[]
String
"Compile to multicore C"
String
"Generate multicore C code from optimised Futhark program."
Pipeline SOACS MCMem
multicorePipeline
((FutharkConfig
-> () -> CompilerMode -> String -> Prog MCMem -> FutharkM ())
-> String -> [String] -> IO ())
-> (FutharkConfig
-> () -> CompilerMode -> String -> Prog MCMem -> FutharkM ())
-> String
-> [String]
-> IO ()
forall a b. (a -> b) -> a -> b
$ \FutharkConfig
fcfg () CompilerMode
mode String
outpath Prog MCMem
prog ->
Action MCMem -> Prog MCMem -> FutharkM ()
forall lore. Action lore -> Prog lore -> FutharkM ()
actionProcedure (FutharkConfig -> CompilerMode -> String -> Action MCMem
compileMulticoreAction FutharkConfig
fcfg CompilerMode
mode String
outpath) Prog MCMem
prog