module Language.Drasil.Code.Imperative.GenODE (
chooseODELib
) where
import Language.Drasil (Sentence(..), (+:+.))
import Language.Drasil.Code.ExtLibImport (ExtLibState(..),
genExternalLibraryCall)
import Language.Drasil.Code.Lang (Lang(..))
import Language.Drasil.Chunk.Code (codeName)
import Language.Drasil.Chunk.CodeDefinition (odeDef)
import Language.Drasil.Mod (Name, Version)
import Language.Drasil.Data.ODELibPckg (ODELibPckg(..))
import Control.Monad.State (State, modify)
import Language.Drasil.Choices (ODE(..))
type ODEGenInfo = (Maybe FilePath, [(Name, ExtLibState)], (Name,Version))
chooseODELib :: Lang -> Maybe ODE -> State [Sentence] ODEGenInfo
chooseODELib :: Lang -> Maybe ODE -> State [Sentence] ODEGenInfo
chooseODELib _ Nothing = ODEGenInfo -> State [Sentence] ODEGenInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe FilePath
forall a. Maybe a
Nothing, [], ("",""))
chooseODELib l :: Lang
l (Just ode :: ODE
ode) = [ODELibPckg] -> [ODELibPckg] -> State [Sentence] ODEGenInfo
chooseODELib' (ODE -> [ODELibPckg]
odeLib ODE
ode) (ODE -> [ODELibPckg]
odeLib ODE
ode)
where chooseODELib' :: [ODELibPckg] -> [ODELibPckg] -> State [Sentence] ODEGenInfo
chooseODELib' :: [ODELibPckg] -> [ODELibPckg] -> State [Sentence] ODEGenInfo
chooseODELib' _ [] = FilePath -> State [Sentence] ODEGenInfo
forall a. HasCallStack => FilePath -> a
error (FilePath -> State [Sentence] ODEGenInfo)
-> FilePath -> State [Sentence] ODEGenInfo
forall a b. (a -> b) -> a -> b
$ "None of the chosen ODE libraries are " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
"compatible with " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Lang -> FilePath
forall a. Show a => a -> FilePath
show Lang
l
chooseODELib' prefLibList :: [ODELibPckg]
prefLibList (o :: ODELibPckg
o:os :: [ODELibPckg]
os) = if Lang
l Lang -> [Lang] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ODELibPckg -> [Lang]
compatibleLangs ODELibPckg
o
then do
([Sentence] -> [Sentence]) -> StateT [Sentence] Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ([Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ [[ODELibPckg] -> ODELibPckg -> Sentence
firstChoiceODELib [ODELibPckg]
prefLibList ODELibPckg
o])
ODEGenInfo -> State [Sentence] ODEGenInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (ODELibPckg -> Maybe FilePath
libPath ODELibPckg
o, (ODEInfo -> (FilePath, ExtLibState))
-> [ODEInfo] -> [(FilePath, ExtLibState)]
forall a b. (a -> b) -> [a] -> [b]
map (\ode' :: ODEInfo
ode' -> (CodeDefinition -> FilePath
forall c. CodeIdea c => c -> FilePath
codeName (CodeDefinition -> FilePath) -> CodeDefinition -> FilePath
forall a b. (a -> b) -> a -> b
$ ODEInfo -> CodeDefinition
odeDef ODEInfo
ode',
ExternalLibrary -> ExternalLibraryCall -> ExtLibState
genExternalLibraryCall (ODELibPckg -> ExternalLibrary
libSpec ODELibPckg
o) (ExternalLibraryCall -> ExtLibState)
-> ExternalLibraryCall -> ExtLibState
forall a b. (a -> b) -> a -> b
$ ODELibPckg -> ODEInfo -> ExternalLibraryCall
libCall ODELibPckg
o ODEInfo
ode')) ([ODEInfo] -> [(FilePath, ExtLibState)])
-> [ODEInfo] -> [(FilePath, ExtLibState)]
forall a b. (a -> b) -> a -> b
$ ODE -> [ODEInfo]
odeInfo ODE
ode,
(ODELibPckg -> FilePath
libName ODELibPckg
o, ODELibPckg -> FilePath
libVers ODELibPckg
o))
else ([Sentence] -> [Sentence]) -> StateT [Sentence] Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ([Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ [Lang -> ODELibPckg -> Sentence
incompatibleLib Lang
l ODELibPckg
o]) StateT [Sentence] Identity ()
-> State [Sentence] ODEGenInfo -> State [Sentence] ODEGenInfo
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [ODELibPckg] -> [ODELibPckg] -> State [Sentence] ODEGenInfo
chooseODELib' [ODELibPckg]
prefLibList [ODELibPckg]
os
incompatibleLib :: Lang -> ODELibPckg -> Sentence
incompatibleLib :: Lang -> ODELibPckg -> Sentence
incompatibleLib lng :: Lang
lng lib :: ODELibPckg
lib = FilePath -> Sentence
S (FilePath -> Sentence) -> FilePath -> Sentence
forall a b. (a -> b) -> a -> b
$ "Language " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Lang -> FilePath
forall a. Show a => a -> FilePath
show Lang
lng FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ " is not " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
"compatible with chosen library " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ODELibPckg -> FilePath
libName ODELibPckg
lib FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ", trying next choice."
firstChoiceODELib :: [ODELibPckg] -> ODELibPckg -> Sentence
firstChoiceODELib :: [ODELibPckg] -> ODELibPckg -> Sentence
firstChoiceODELib prefer :: [ODELibPckg]
prefer olp :: ODELibPckg
olp = if ODELibPckg -> FilePath
libName ([ODELibPckg] -> ODELibPckg
forall a. [a] -> a
head [ODELibPckg]
prefer) FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== ODELibPckg -> FilePath
libName ODELibPckg
olp then
FilePath -> Sentence
S "Successfully selected first choice ODE Library package" Sentence -> Sentence -> Sentence
+:+. FilePath -> Sentence
S (ODELibPckg -> FilePath
libName ODELibPckg
olp)
else FilePath -> Sentence
S "ODE Library package selected as" Sentence -> Sentence -> Sentence
+:+. FilePath -> Sentence
S (ODELibPckg -> FilePath
libName ODELibPckg
olp)