Migrate all FunctionIO

This commit is contained in:
Niels G. W. Serup 2024-09-21 18:02:20 +02:00
parent b1c124d899
commit af50f16243
No known key found for this signature in database
GPG Key ID: 38EEEBCE67324F19
5 changed files with 37 additions and 27 deletions

View File

@ -17,6 +17,7 @@ library
import: common import: common
hs-source-dirs: src hs-source-dirs: src
exposed-modules: exposed-modules:
Types
Sources Sources
Functions Functions
ComputationM ComputationM

View File

@ -1,17 +1,14 @@
{-# LANGUAGE GADTs #-} {-# LANGUAGE GADTs #-}
module ComputationM where module ComputationM where
import Types
import Sources
import Functions
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Control.Monad.State import Control.Monad.State
import Control.Monad.Writer 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 data TypedRun a b where
@ -77,6 +74,9 @@ runIO f input = genDependency (Dependency input (FIO f))
listDirectory = runIO ListDirectory listDirectory = runIO ListDirectory
openImage = runIO OpenImage openImage = runIO OpenImage
convertImage = runIO ConvertImage
saveFile = runIO SaveFile
runPandoc = runIO RunPandoc
makeTraversable :: Token TokenNotTraversable [a] -> Token TokenTraversable (Token TokenNotTraversable a) makeTraversable :: Token TokenNotTraversable [a] -> Token TokenTraversable (Token TokenNotTraversable a)

View File

@ -2,37 +2,34 @@
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
module Functions where module Functions where
import Types
import Sources import Sources
data Image = Image
deriving (Show)
data ImageConversion = ImageConversion
deriving (Show)
data Function a b where data Function a b where
IsImageFilename :: Function FilePath Bool IsImageFilename :: Function FilePath Bool
ConvertedImageFilename :: Function FilePath FilePath ConvertedImageFilename :: Function FilePath FilePath
deriving instance Show (Function a b) 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 class (SourceState a, Show f) => IsFIO f a b | f -> a b where
runFIO :: f -> a -> IO b runFIO :: f -> a -> IO b
data ListDirectory = ListDirectory data ListDirectory = ListDirectory deriving (Show)
deriving (Show)
instance IsFIO ListDirectory FilePath [FilePath] where instance IsFIO ListDirectory FilePath [FilePath] where
runFIO ListDirectory path = undefined runFIO ListDirectory _path = undefined
data OpenImage = OpenImage data OpenImage = OpenImage deriving (Show)
deriving (Show)
instance IsFIO OpenImage FilePath Image where 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

View File

@ -1,5 +1,7 @@
module Sources where module Sources where
import Types
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
data Source a where data Source a where
@ -10,3 +12,9 @@ class SourceState a where
instance SourceState FilePath where instance SourceState FilePath where
stateOfSource = undefined stateOfSource = undefined
instance SourceState Image where
stateOfSource = undefined
instance SourceState (String, FilePath) where
stateOfSource = undefined

4
byg/src/Types.hs Normal file
View File

@ -0,0 +1,4 @@
module Types where
data Image = Image
deriving (Show)