
October 18, 2020 6:20 AM, tech@jimtyrerrobotics.ca wrote:
About the existing script: I write plain text files on my phone that look like this:
14 Sep 0745 1600 Foo y
and this one is called Wk38 and the fields are: |Date|Time In|Time Out|Proj|Lunch. Then I email it to myself and run the script.
So I would be very grateful if someone could write some code for me and put my bootstraps in my fumbling hands:
Get the name of the Wkxx file from the command line when running a Haskell standalone executable. fileName <- getArgs Load the lines of the file into a list of list of String[[]]. (or a better way?) lines <- fmap Text.lines (Text.readFile fileName) Recurse through each line of the list(s) and: *: Construct a date::String from the first two fields. (just a string, does not need a real "Date") *: Calc dailyElapsedTime::Double from difference between fields 4 and 3. *: Subtract 0.5hr lunch from dailyElapsedTime if field 6 == "y" *: Add dailyElapsedTime to accumlatedWeekTime::Double. *: Charge = If accumlatedWeekTime < 40hrs then multiply by rate1 *: elseif accumlatedWeekTime > 40hrs then multiply by rate2 *: Append |Date|Time In|Time Out|Charge|Project| to adoc file.
I would break this apart with a couple of additional types: data Entry = Entry { eDay :: Int , eMonth :: Int , eStart :: TimeOfDay , eEnd :: TimeOfDay , eProject :: Text , eLunched :: Bool } deriving (Eq, Show) data Charge = Charge { cDay :: Int , cMonth :: Int , cStart :: TimeOfDay , cEnd :: TimeOfDay , cHoursCharged :: Double , cProject :: Text } deriving (Eq, Show) Then the problem breaks down into: 1. Get filename 2. Read text from file 3. Parse text into [Entry] 4. Convert [Entry] into [Charge] 5. Write [Charge] to other file Maybe a sketch will unstick you: 1. You want `[fileName] <- getArgs` here, as `getArgs :: IO [String]` returns a list of arguments. Your program will fail unless you invoke it with exactly one argument but that's fine for initial testing. 2. lines <- fmap Text.lines (Text.readFile fileName) will give you access to `lines :: [Text]`, which you can pass into other functions. This means you're not trying to do everything inside `main`, and won't have values of type `IO whatever` flying around the rest of your program. 3. At this stage, we have a parsing problem. We want a function like `parseEntry :: Text -> Either Text Entry`, where the `Left` side would be an error message (if that line fails to parse), or the `Entry` describing that line. I can see a couple of ways to attack this: a) Use Text.words and continue with ad-hoc parsing. You may find yourself reinventing wheels that are in the library ecosystem, but for learning that might be fine? b) Use a library like megaparsec and write a full-blown parser. You will get more for free, but the learning curve may be steeper. I am inclined to recommend option (a), so try writing out a bunch of functions: - parseDay :: Text -> Either Text Int - parseMonth :: Text -> Either Text Int - parseTimeOfDay :: Text -> Either Text TimeOfDay - parseYN :: Text -> Either Text Bool - etc. Once you have applied each word from the input line to one of these functions, you will have a lot of `Either Text somePart` values. To combine them into an `Entry`, you'll want to use the `Applicative` typeclass, specifically the `(<$>)` and `(<*>)` operators. `Either e` has an `Applicative` instance for any `e`, so we can get: - Entry :: Int -> Int -> TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry - (<$>) :: Functor f => (a -> b) -> f a -> f b -- Infix alias for fmap (every `Applicative` is a `Functor`) - We use it here with the types `f ~ Either Text`, `a ~ Int`, `b ~ Int -> TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry`: - Entry <$> parseDay dayText :: Either Text (Int -> TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry) - (<*>) :: Applicative f => f (a -> b) -> f a -> f b - With the types `f ~ Either Text`, `a ~ Int`, `b ~ TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry`: - Entry <$> parseDay dayText <*> parseMonth monthText :: Either Text (TimeOfDay -> TimeOfDay -> Text -> Bool -> Entry) - And so on, toward Entry <$> parseDay dayText <*> parseMonth monthText <*> ...etc... <*> parseYN lunchText That gives you `parseEntry`, which parses one line into one `Entry`. We need to apply it over every line in the input list, and `traverse` is the tool for that: traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) As before, we'll use `Either Text` as our `Applicative`. Lists (i.e. the type constructor `[]`) have a `Traversable` instance, so we can specialise this to: traverse :: (Text -> Either Text Entry) -> [Text] -> Either Text [Entry] This runs the parser on each line, and "combines" the results. Because we're using `Either Text` for our `Applicative`, the effect is to stop on the first parse error and report it. You can then case-match on the result to see whether you have an error, or have parsed a [Entry] which you'll now convert into [Charge]. 4. A function `calculateCharge :: Entry -> Charge` shouldn't be too difficult to write, and then you can lift it to work over lists using `map`. If you lean into the date/time types a bit more, you might find the `Data.Time.LocalTime.diffLocalTime` function (from the `time` package) helpful. 5. Appending `[Charge]` to the other file: There's an `appendFile :: FilePath -> Text -> IO ()` which should get you started. I'd look at writing a function `renderCharge :: Charge -> Text`, making it work over the entire list using `map`, and collapsing the `[Text]` using `Text.unlines`. ***** Parsing looks like the gnarliest part, so I'd leave that to the end. Start at the outside and work your way in. Declare `parseLine` but replace its implementation with something silly: parseLine :: Text -> Either Text Entry parseLine _ = Right $ Entry 1 4 (TimeOfDay 9 0 0) (TimeOfDay 17 0 0) "Dummy" False And see if you can get the rest of the program's skeleton in place. Then you can test that it does something, then replace `parseLine` with a real parser. HTH, -- Jack