Migrate all FunctionIO
This commit is contained in:
parent
b1c124d899
commit
af50f16243
|
@ -17,6 +17,7 @@ library
|
|||
import: common
|
||||
hs-source-dirs: src
|
||||
exposed-modules:
|
||||
Types
|
||||
Sources
|
||||
Functions
|
||||
ComputationM
|
||||
|
|
|
@ -1,17 +1,14 @@
|
|||
{-# LANGUAGE GADTs #-}
|
||||
module ComputationM where
|
||||
|
||||
import Types
|
||||
import Sources
|
||||
import Functions
|
||||
|
||||
import Unsafe.Coerce (unsafeCoerce)
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Writer
|
||||
|
||||
import Functions
|
||||
import Sources
|
||||
|
||||
|
||||
data ComputationRun a b = ComputationRun (Function a b)
|
||||
| ComputationRunIO (FunctionIO a b)
|
||||
|
||||
|
||||
|
||||
data TypedRun a b where
|
||||
|
@ -77,6 +74,9 @@ runIO f input = genDependency (Dependency input (FIO f))
|
|||
|
||||
listDirectory = runIO ListDirectory
|
||||
openImage = runIO OpenImage
|
||||
convertImage = runIO ConvertImage
|
||||
saveFile = runIO SaveFile
|
||||
runPandoc = runIO RunPandoc
|
||||
|
||||
|
||||
makeTraversable :: Token TokenNotTraversable [a] -> Token TokenTraversable (Token TokenNotTraversable a)
|
||||
|
|
|
@ -2,37 +2,34 @@
|
|||
{-# LANGUAGE FunctionalDependencies #-}
|
||||
module Functions where
|
||||
|
||||
import Types
|
||||
import Sources
|
||||
|
||||
data Image = Image
|
||||
deriving (Show)
|
||||
data ImageConversion = ImageConversion
|
||||
deriving (Show)
|
||||
|
||||
data Function a b where
|
||||
IsImageFilename :: Function FilePath Bool
|
||||
ConvertedImageFilename :: Function FilePath FilePath
|
||||
|
||||
deriving instance Show (Function a b)
|
||||
|
||||
data FunctionIO a b where
|
||||
ConvertImage :: FunctionIO (Image, ImageConversion) Image
|
||||
Save :: FunctionIO (a, FilePath) ()
|
||||
RunPandoc :: FunctionIO String String
|
||||
|
||||
deriving instance Show (FunctionIO a b)
|
||||
|
||||
|
||||
|
||||
class (SourceState a, Show f) => IsFIO f a b | f -> a b where
|
||||
runFIO :: f -> a -> IO b
|
||||
|
||||
data ListDirectory = ListDirectory
|
||||
deriving (Show)
|
||||
data ListDirectory = ListDirectory deriving (Show)
|
||||
instance IsFIO ListDirectory FilePath [FilePath] where
|
||||
runFIO ListDirectory path = undefined
|
||||
runFIO ListDirectory _path = undefined
|
||||
|
||||
data OpenImage = OpenImage
|
||||
deriving (Show)
|
||||
data OpenImage = OpenImage deriving (Show)
|
||||
instance IsFIO OpenImage FilePath Image where
|
||||
runFIO OpenImage path = undefined
|
||||
runFIO OpenImage _path = undefined
|
||||
|
||||
data ConvertImage = ConvertImage deriving (Show)
|
||||
instance IsFIO ConvertImage Image Image where
|
||||
runFIO ConvertImage _image = undefined
|
||||
|
||||
data SaveFile = SaveFile deriving (Show)
|
||||
instance IsFIO SaveFile (String, FilePath) () where
|
||||
runFIO SaveFile _source = undefined
|
||||
|
||||
data RunPandoc = RunPandoc deriving (Show)
|
||||
instance IsFIO RunPandoc String String where
|
||||
runFIO RunPandoc _source = undefined
|
||||
|
|
|
@ -1,5 +1,7 @@
|
|||
module Sources where
|
||||
|
||||
import Types
|
||||
|
||||
import Data.ByteString (ByteString)
|
||||
|
||||
data Source a where
|
||||
|
@ -10,3 +12,9 @@ class SourceState a where
|
|||
|
||||
instance SourceState FilePath where
|
||||
stateOfSource = undefined
|
||||
|
||||
instance SourceState Image where
|
||||
stateOfSource = undefined
|
||||
|
||||
instance SourceState (String, FilePath) where
|
||||
stateOfSource = undefined
|
||||
|
|
|
@ -0,0 +1,4 @@
|
|||
module Types where
|
||||
|
||||
data Image = Image
|
||||
deriving (Show)
|
Loading…
Reference in New Issue