implemented SubFix.Internal.decodeTime function
This commit is contained in:
parent
b942ff0286
commit
bf7dfc95f9
@ -28,6 +28,8 @@ dependencies:
|
||||
|
||||
library:
|
||||
source-dirs: src
|
||||
dependencies:
|
||||
- transformers >=0.5.6.2 && <0.6
|
||||
|
||||
executables:
|
||||
subfix:
|
||||
|
@ -25,11 +25,13 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
|
||||
-}
|
||||
|
||||
module SubFix.Internal (encodeTime, decodeTime, timestamp) where
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
-- | Encodes a timestamp from a number of milliseconds
|
||||
encodeTime :: Integer -> String
|
||||
encodeTime = undefined
|
||||
module SubFix.Internal (decodeTime, encodeTime, timestamp) where
|
||||
|
||||
import Control.Monad (when)
|
||||
import Control.Monad.Trans.State (StateT (..), get, put)
|
||||
import Data.Char (isDigit, ord)
|
||||
|
||||
-- | Decodes a timestamp to a number of milliseconds and the unused
|
||||
-- input
|
||||
@ -38,7 +40,19 @@ decodeTime
|
||||
-- ^ The encoded timestamp
|
||||
-> Maybe (Integer, String)
|
||||
-- ^ The number of milliseconds and unused input (if available)
|
||||
decodeTime = undefined
|
||||
decodeTime = runStateT $ do
|
||||
hours <- getNum 2
|
||||
dropChar ':'
|
||||
mins <- getNum 2
|
||||
dropChar ':'
|
||||
secs <- getNum 2
|
||||
dropChar ','
|
||||
ms <- getNum 3
|
||||
return $ timestamp hours mins secs ms
|
||||
|
||||
-- | Encodes a timestamp from a number of milliseconds
|
||||
encodeTime :: Integer -> String
|
||||
encodeTime = undefined
|
||||
|
||||
-- | Converts hours, minutes, seconds and milliseconds into the total
|
||||
-- number of milliseconds
|
||||
@ -57,4 +71,32 @@ timestamp h m s ms = let
|
||||
s' = m' * 60 + s
|
||||
in s' * 1000 + ms
|
||||
|
||||
getNum :: MonadFail m => Int -> StateT String m Integer
|
||||
getNum = f 0 where
|
||||
f val digits
|
||||
| digits <= 0 = return val
|
||||
| otherwise = do
|
||||
digit <- nextDigit
|
||||
f (val * 10 + digit) (pred digits)
|
||||
|
||||
dropChar :: MonadFail m => Char -> StateT String m ()
|
||||
dropChar expected = do
|
||||
ch <- nextChar
|
||||
when (ch /= expected) $
|
||||
fail "incorrect character"
|
||||
|
||||
nextDigit :: MonadFail m => StateT String m Integer
|
||||
nextDigit = do
|
||||
ch <- nextChar
|
||||
if isDigit ch
|
||||
then return $ toInteger $ ord ch - ord '0'
|
||||
else fail "missing digit"
|
||||
|
||||
nextChar :: MonadFail m => StateT String m Char
|
||||
nextChar = get >>= \case
|
||||
"" -> fail "no character available"
|
||||
(ch:str) -> do
|
||||
put str
|
||||
return ch
|
||||
|
||||
--jl
|
||||
|
@ -4,7 +4,7 @@ cabal-version: 1.12
|
||||
--
|
||||
-- see: https://github.com/sol/hpack
|
||||
--
|
||||
-- hash: abd53b387d0bc7d910539fc83efe7b2fa75fe55deb728293cb25b78a7475d4cb
|
||||
-- hash: 475ccf2c735b96ddd94fc9281d9e8e97ecf64c4b60cd6645112a6ffb72165873
|
||||
|
||||
name: subfix
|
||||
version: 0.0.0
|
||||
@ -38,6 +38,7 @@ library
|
||||
ghc-options: -Wall -Werror
|
||||
build-depends:
|
||||
base >=4.7 && <5
|
||||
, transformers >=0.5.6.2 && <0.6
|
||||
default-language: Haskell2010
|
||||
|
||||
executable subfix
|
||||
@ -57,6 +58,7 @@ test-suite subfix-test
|
||||
main-is: Spec.hs
|
||||
other-modules:
|
||||
SubFix.ConvertSpec
|
||||
SubFix.Internal.DecodeTimeSpec
|
||||
SubFix.Internal.TimestampSpec
|
||||
SubFix.InternalSpec
|
||||
SubFixSpec
|
||||
|
45
test/SubFix/Internal/DecodeTimeSpec.hs
Normal file
45
test/SubFix/Internal/DecodeTimeSpec.hs
Normal file
@ -0,0 +1,45 @@
|
||||
{-
|
||||
|
||||
subfix
|
||||
Copyright (C) Jonathan Lamothe <jonathan@jlamothe.net>
|
||||
|
||||
This program is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU General Public License as published by
|
||||
the Free Software Foundation, either version 3 of the License, or (at
|
||||
your option) any later version.
|
||||
|
||||
This program is distributed in the hope that it will be useful, but
|
||||
WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
||||
General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
|
||||
-}
|
||||
|
||||
module SubFix.Internal.DecodeTimeSpec (spec) where
|
||||
|
||||
import Test.Hspec (Spec, context, describe, it, shouldBe)
|
||||
|
||||
import SubFix.Internal (decodeTime, timestamp)
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "decodeTime" $ mapM_
|
||||
( \(input, expected) ->
|
||||
context input $
|
||||
it ("should be " ++ show expected) $
|
||||
decodeTime input `shouldBe` expected
|
||||
)
|
||||
|
||||
-- input, expected
|
||||
[ ( "", Nothing )
|
||||
, ( "abc", Nothing )
|
||||
, ( "00:00:00,000", Just (0, "") )
|
||||
, ( "01:02:03,004", Just (timestamp 1 2 3 4, "") )
|
||||
, ( "1:2:3,4", Nothing )
|
||||
, ( "10:20:30,400", Just (timestamp 10 20 30 400, "" ) )
|
||||
, ( "01:02:03,004abc", Just (timestamp 1 2 3 4, "abc") )
|
||||
]
|
||||
|
||||
--jl
|
@ -22,9 +22,12 @@ module SubFix.InternalSpec (spec) where
|
||||
|
||||
import Test.Hspec (Spec, describe)
|
||||
|
||||
import qualified SubFix.Internal.DecodeTimeSpec as DecodeTime
|
||||
import qualified SubFix.Internal.TimestampSpec as Timestamp
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "Internal" Timestamp.spec
|
||||
spec = describe "Internal" $ do
|
||||
DecodeTime.spec
|
||||
Timestamp.spec
|
||||
|
||||
--jl
|
||||
|
Loading…
x
Reference in New Issue
Block a user