Skip to content

Commit

Permalink
Merge pull request #10 from haskell-works/new-complement-command
Browse files Browse the repository at this point in the history
New complement command
  • Loading branch information
newhoggy committed Apr 2, 2019
2 parents e6d44b5 + 6f9c892 commit e50dbab
Show file tree
Hide file tree
Showing 4 changed files with 50 additions and 0 deletions.
2 changes: 2 additions & 0 deletions app/App/Commands.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module App.Commands where

import App.Commands.Bits
import App.Commands.Complement
import App.Commands.SelectedByBits
import App.Commands.Slice
import App.Commands.Words
Expand All @@ -10,6 +11,7 @@ import Options.Applicative
cmdOpts :: Parser (IO ())
cmdOpts = subparser $ mempty
<> cmdBits
<> cmdComplement
<> cmdSelectedByBits
<> cmdSlice
<> cmdWords
42 changes: 42 additions & 0 deletions app/App/Commands/Complement.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

module App.Commands.Complement
( cmdComplement
) where

import Control.Lens
import Data.Generics.Product.Any
import Data.Semigroup ((<>))
import HaskellWorks.Data.Bits.BitWise
import Options.Applicative hiding (columns)

import qualified App.Commands.Options.Type as Z
import qualified Data.ByteString.Lazy as LBS

{-# ANN module ("HLint: ignore Redundant do" :: String) #-}
{-# ANN module ("HLint: ignore Redundant return" :: String) #-}

runComplement :: Z.ComplementOptions -> IO ()
runComplement opts = do
let inputFile = opts ^. the @"inputFile"
let outputFile = opts ^. the @"outputFile"

LBS.readFile inputFile <&> LBS.map comp >>= LBS.writeFile outputFile

optsComplement :: Parser Z.ComplementOptions
optsComplement = Z.ComplementOptions
<$> strOption
( long "input-file"
<> help "Input file"
<> metavar "FILE"
)
<*> strOption
( long "output-file"
<> help "Output file"
<> metavar "FILE"
)

cmdComplement :: Mod CommandFields (IO ())
cmdComplement = command "complement" $ flip info idm $ runComplement <$> optsComplement
5 changes: 5 additions & 0 deletions app/App/Commands/Options/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,11 @@ data BitsOptions = BitsOptions
, bitFiles :: [FilePath]
} deriving (Eq, Show, Generic)

data ComplementOptions = ComplementOptions
{ inputFile :: FilePath
, outputFile :: FilePath
} deriving (Eq, Show, Generic)

data SelectedByBitsOptions = SelectedByBitsOptions
{ file :: FilePath
, bitFile :: FilePath
Expand Down
1 change: 1 addition & 0 deletions hw-dump.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ executable hw-dump
other-modules:
App.Commands
App.Commands.Bits
App.Commands.Complement
App.Commands.Options.Type
App.Commands.SelectedByBits
App.Commands.Slice
Expand Down

0 comments on commit e50dbab

Please sign in to comment.