Put function shortcuts back in Functions module
Šī revīzija ir iekļauta:
		@@ -1,10 +1,15 @@
 | 
			
		||||
module ComputationM where
 | 
			
		||||
module ComputationM
 | 
			
		||||
  ( ComputationM
 | 
			
		||||
  , evalComputationM
 | 
			
		||||
  , inject
 | 
			
		||||
  , mapComputationM
 | 
			
		||||
  , runFunction
 | 
			
		||||
  , runFunctionIO
 | 
			
		||||
  ) where
 | 
			
		||||
 | 
			
		||||
import Types
 | 
			
		||||
import Sources
 | 
			
		||||
import Functions
 | 
			
		||||
 | 
			
		||||
import Unsafe.Coerce (unsafeCoerce)
 | 
			
		||||
import Control.Monad.State
 | 
			
		||||
import Control.Monad.Writer
 | 
			
		||||
 | 
			
		||||
@@ -71,20 +76,11 @@ setListElem a outer = do
 | 
			
		||||
  tellDep (Dependency a SetListElem outer)
 | 
			
		||||
  pure NoToken
 | 
			
		||||
 | 
			
		||||
run :: (Show a, Show b, IsFunction f a b) => f -> Token a -> ComputationM b
 | 
			
		||||
run f input = genDependency (Dependency input (Function f))
 | 
			
		||||
runFunction :: (Show a, Show b, IsFunction f a b) => f -> Token a -> ComputationM b
 | 
			
		||||
runFunction f input = genDependency (Dependency input (Function f))
 | 
			
		||||
 | 
			
		||||
isImageFilename = run IsImageFilename
 | 
			
		||||
convertedImageFilename = run ConvertedImageFilename
 | 
			
		||||
 | 
			
		||||
runIO :: (Show a, Show b, IsFunctionIO f a b) => f -> Token a -> ComputationM b
 | 
			
		||||
runIO f input = genDependency (Dependency input (FunctionIO f))
 | 
			
		||||
 | 
			
		||||
listDirectory = runIO ListDirectory
 | 
			
		||||
openImage = runIO OpenImage
 | 
			
		||||
convertImage = runIO ConvertImage
 | 
			
		||||
saveFile = runIO SaveFile
 | 
			
		||||
runPandoc = runIO RunPandoc
 | 
			
		||||
runFunctionIO :: (Show a, Show b, IsFunctionIO f a b) => f -> Token a -> ComputationM b
 | 
			
		||||
runFunctionIO f input = genDependency (Dependency input (FunctionIO f))
 | 
			
		||||
 | 
			
		||||
mapComputationM :: (Show a, Show b) => (Token a -> ComputationM b) -> Token [a] -> ComputationM [b]
 | 
			
		||||
mapComputationM f input = genDependency' $ \target -> do
 | 
			
		||||
 
 | 
			
		||||
@@ -1,7 +1,16 @@
 | 
			
		||||
module Functions where
 | 
			
		||||
{-# OPTIONS_GHC -Wno-missing-signatures #-}
 | 
			
		||||
module Functions
 | 
			
		||||
  ( isImageFilename
 | 
			
		||||
  , convertedImageFilename
 | 
			
		||||
  , listDirectory
 | 
			
		||||
  , openImage
 | 
			
		||||
  , convertImage
 | 
			
		||||
  , saveFile
 | 
			
		||||
  , runPandoc
 | 
			
		||||
  ) where
 | 
			
		||||
 | 
			
		||||
import Types
 | 
			
		||||
import Sources
 | 
			
		||||
import ComputationM
 | 
			
		||||
 | 
			
		||||
data IsImageFilename = IsImageFilename deriving (Show)
 | 
			
		||||
instance IsFunction IsImageFilename FilePath Bool where
 | 
			
		||||
@@ -31,3 +40,13 @@ instance IsFunctionIO SaveFile (String, FilePath) () where
 | 
			
		||||
data RunPandoc = RunPandoc deriving (Show)
 | 
			
		||||
instance IsFunctionIO RunPandoc String String where
 | 
			
		||||
  runFIO RunPandoc _source = undefined
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
isImageFilename = runFunction IsImageFilename
 | 
			
		||||
convertedImageFilename = runFunction ConvertedImageFilename
 | 
			
		||||
 | 
			
		||||
listDirectory = runFunctionIO ListDirectory
 | 
			
		||||
openImage = runFunctionIO OpenImage
 | 
			
		||||
convertImage = runFunctionIO ConvertImage
 | 
			
		||||
saveFile = runFunctionIO SaveFile
 | 
			
		||||
runPandoc = runFunctionIO RunPandoc
 | 
			
		||||
 
 | 
			
		||||
@@ -2,13 +2,15 @@ module Main where
 | 
			
		||||
 | 
			
		||||
import Types
 | 
			
		||||
import ComputationM
 | 
			
		||||
import Functions
 | 
			
		||||
 | 
			
		||||
test :: ComputationM ()
 | 
			
		||||
test = do
 | 
			
		||||
  dir <- inject "retter"
 | 
			
		||||
  dirContents <- listDirectory dir
 | 
			
		||||
  u <- mapComputationM openImage dirContents
 | 
			
		||||
  pure $ NoToken
 | 
			
		||||
  t <- inject ("hej", "hey.txt")
 | 
			
		||||
  saveFile t
 | 
			
		||||
 | 
			
		||||
main :: IO ()
 | 
			
		||||
main = mapM_ print $ evalComputationM test
 | 
			
		||||
 
 | 
			
		||||
		Atsaukties uz šo jaunā problēmā
	
	Block a user