CurryInfo: icurry-3.2.0 / ICurry.Compiler.flatCurry2ICurryWithProgsAndOptions

definition:
flatCurry2ICurryWithProgsAndOptions :: ICOptions -> [Prog] -> Prog
                                    -> IO (ICOptions,IProg)
flatCurry2ICurryWithProgsAndOptions opts progs prog0 = do
  let impmods = progImports prog0
  impprogs <- mapM getInterface impmods
  let prog      = elimNewtype impprogs prog0
      datadecls = concatMap dataDeclsOf (prog : impprogs)
      ccprog    = completeProg (CaseOptions datadecls) prog
      clprog    = if optLift opts
                    then liftProg defaultLiftOpts ccprog
                    else liftProg defaultNoLiftOpts ccprog
  printDetails opts $ 
    textWithLines "Transformed FlatCurry program to be compiled:" ++
    pPrint (ppProg FlatCurry.Pretty.defaultOptions clprog)
  let consmap   = map consMapOfProg (prog : impprogs)
      impfunmap = map publicFunMapOfProg impprogs
      pubfunmap = snd (publicFunMapOfProg prog)
      funmap    = (progName prog,
                   pubfunmap ++ privateFunMapOfProg clprog pubfunmap) :
                  impfunmap
  let cmpopts = setConsFuns opts consmap funmap
      icprog  = flat2icurry cmpopts clprog
  printIntermediate opts $
    textWithLines "Generated ICurry program:" ++
    pPrint (ppIProg icprog)
  printDetails opts (textWithLines "Generated ICurry file:" ++ showIProg icprog)
  return (cmpopts,icprog)
 where
  getInterface p =
    maybe (do printStatus opts $ "Read FlatCurry interface of '" ++ p ++ "'"
              readFlatCurryIntWithParseOptions p (optFrontendParams opts))
          return
          (find (\fp -> progName fp == p) progs)

  consMapOfProg fcy =
    (progName fcy,
     concatMap (\ (_,cars) -> map (\ ((cname,car),pos) -> (cname,(car,pos)))
                                  (zip cars [0..]))
               (dataDeclsOf fcy))

  -- compute mapping of public function names to indices
  publicFunMapOfProg fcprog =
    (progName fcprog,
     zip (map funcName
              (filter (\f -> funcVisibility f == FlatCurry.Types.Public)
                      (progFuncs fcprog)))
         [0..])

  privateFunMapOfProg fcprog pubfunmap =
    zip (filter (\fn -> fn `notElem` map fst pubfunmap)
                (map funcName (progFuncs fcprog)))
        [(length pubfunmap) ..]

  textWithLines s = unlines [l, s, l]
   where l = take 78 (repeat '-')
demand:
no demanded arguments
deterministic:
deterministic operation
documentation:
--- Translates a FlatCurry program into an ICurry program where
--- some FlatCurry interfaces are provided.
--- It also reads the interfaces of imported modules, if not already
--- provided, in order to access their data and function declarations.
--- The `ICOptions` after processing the program (containing the
--- constructor and function maps required for the translation)
--- are also returned.
failfree:
<FAILING>
indeterministic:
referentially transparent operation
infix:
no fixity defined
iotype:
{(_,_,_) |-> _}
name:
flatCurry2ICurryWithProgsAndOptions
precedence:
no precedence defined
result-values:
_
signature:
ICurry.Options.ICOptions -> [FlatCurry.Types.Prog] -> FlatCurry.Types.Prog
-> Prelude.IO (ICurry.Options.ICOptions, ICurry.Types.IProg)
solution-complete:
operation might suspend on free variables
terminating:
possibly non-terminating
totally-defined:
possibly non-reducible on same data term