{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Strict #-}

-- |
--
-- This module implements a transformation from source to core
-- Futhark.
--
-- The source and core language is similar in spirit, but the core
-- language is much more regular (and mostly much simpler) in order to
-- make it easier to write program transformations.
--
-- * "Language.Futhark.Syntax" contains the source language definition.
--
-- * "Futhark.IR.Syntax" contains the core IR definition.
--
-- Specifically, internalisation generates the SOACS dialect of the
-- core IR ("Futhark.IR.SOACS").  This is then initially used by the
-- compiler middle-end.  The main differences between the source and
-- core IR are as follows:
--
-- * The core IR has no modules.  These are removed in
--   "Futhark.Internalise.Defunctorise".
--
-- * The core IR is monomorphic.  Polymorphic functions are monomorphised in
--   "Futhark.Internalise.Monomorphise"
--
-- * The core IR is first-order. "Futhark.Internalise.Defunctionalise"
--   removes higher-order functions.
--
-- * The core IR is in [ANF](https://en.wikipedia.org/wiki/A-normal_form).
--
-- * The core IR does not have arrays of tuples (or tuples or records
--   at all, really).  Arrays of tuples are turned into multiple
--   arrays.  For example, a source language transposition of an array
--   of pairs becomes a core IR that contains two transpositions of
--   two distinct arrays.  The guts of this transformation is in
--   "Futhark.Internalise.Exps".
--
-- * For the above reason, SOACs also accept multiple input arrays.
--   The available primitive operations are also somewhat different
--   than in the source language.  See 'Futhark.IR.SOACS.SOAC.SOAC'.
module Futhark.Internalise (internaliseProg) where

import qualified Data.Text as T
import Futhark.Compiler.Config
import Futhark.IR.SOACS as I hiding (stmPat)
import Futhark.Internalise.Defunctionalise as Defunctionalise
import Futhark.Internalise.Defunctorise as Defunctorise
import qualified Futhark.Internalise.Exps as Exps
import Futhark.Internalise.LiftLambdas as LiftLambdas
import Futhark.Internalise.Monad as I
import Futhark.Internalise.Monomorphise as Monomorphise
import Futhark.Util.Log
import Language.Futhark.Semantic (Imports)

-- | Convert a program in source Futhark to a program in the Futhark
-- core language.
internaliseProg ::
  (MonadFreshNames m, MonadLogger m) =>
  FutharkConfig ->
  Imports ->
  m (I.Prog SOACS)
internaliseProg :: FutharkConfig -> Imports -> m (Prog SOACS)
internaliseProg FutharkConfig
config Imports
prog = do
  Text -> m ()
forall (m :: * -> *). MonadLogger m => Text -> m ()
maybeLog Text
"Defunctorising"
  [Dec]
prog_decs <- Imports -> m [Dec]
forall (m :: * -> *). MonadFreshNames m => Imports -> m [Dec]
Defunctorise.transformProg Imports
prog
  Text -> m ()
forall (m :: * -> *). MonadLogger m => Text -> m ()
maybeLog Text
"Monomorphising"
  [ValBind]
prog_decs' <- [Dec] -> m [ValBind]
forall (m :: * -> *). MonadFreshNames m => [Dec] -> m [ValBind]
Monomorphise.transformProg [Dec]
prog_decs
  Text -> m ()
forall (m :: * -> *). MonadLogger m => Text -> m ()
maybeLog Text
"Lifting lambdas"
  [ValBind]
prog_decs'' <- [ValBind] -> m [ValBind]
forall (m :: * -> *). MonadFreshNames m => [ValBind] -> m [ValBind]
LiftLambdas.transformProg [ValBind]
prog_decs'
  Text -> m ()
forall (m :: * -> *). MonadLogger m => Text -> m ()
maybeLog Text
"Defunctionalising"
  [ValBind]
prog_decs''' <- [ValBind] -> m [ValBind]
forall (m :: * -> *). MonadFreshNames m => [ValBind] -> m [ValBind]
Defunctionalise.transformProg [ValBind]
prog_decs''
  Text -> m ()
forall (m :: * -> *). MonadLogger m => Text -> m ()
maybeLog Text
"Converting to core IR"
  Bool -> [ValBind] -> m (Prog SOACS)
forall (m :: * -> *).
MonadFreshNames m =>
Bool -> [ValBind] -> m (Prog SOACS)
Exps.transformProg (FutharkConfig -> Bool
futharkSafe FutharkConfig
config) [ValBind]
prog_decs'''
  where
    verbose :: Bool
verbose = (Verbosity, Maybe FilePath) -> Verbosity
forall a b. (a, b) -> a
fst (FutharkConfig -> (Verbosity, Maybe FilePath)
futharkVerbose FutharkConfig
config) Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
> Verbosity
NotVerbose
    maybeLog :: Text -> m ()
maybeLog Text
s
      | Bool
verbose = Text -> m ()
forall (m :: * -> *) a. (MonadLogger m, ToLog a) => a -> m ()
logMsg (Text
s :: T.Text)
      | Bool
otherwise = () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()