Simple style fixes for outer layers around Engine.hs

Summary:
Easy style fixes for ExampleMain.hs, Debug.hs, Api.hs, Core.hs

Most of these are just lint fixes, but I also made a few not-just-lint changes
to conform to some elements of our style guide that I agree with:
- if the type signature doesn't fit on one line, then put one type per line
  with nothing on the first line, so that all types are vertically aligned - makes
  for a quick skim
- try to avoid mixing same-line function args with hanging function args: hang
  all arguments or none at all to get a more outline-like feel, again better for
  skimming

I was actually able to eliminate all errors for most of these modules - the name
collisions I usually give up on were manageable by hiding + easy variable renames

Reviewed By: chessai

Differential Revision: D28213246

fbshipit-source-id: 1f77d56f2ff8dccfd5f3b534f087c07047b92885
This commit is contained in:
Steven Troxler 2021-05-05 13:06:07 -07:00 committed by Facebook GitHub Bot
parent 0e13d28b4d
commit eba5d0a825
7 changed files with 47 additions and 32 deletions

View File

@ -5,7 +5,6 @@
-- LICENSE file in the root directory of this source tree.
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE RecordWildCards #-}
@ -35,9 +34,16 @@ import Duckling.Rules
import Duckling.Types
-- | Parses `input` and returns a curated list of entities found.
parse :: Text -> Context -> Options -> [Seal Dimension] -> [Entity]
parse input ctx options = map (formatToken input) . analyze input ctx options .
HashSet.fromList
parse
:: Text
-> Context
-> Options
-> [Seal Dimension]
-> [Entity]
parse input ctx options =
map (formatToken input)
. analyze input ctx options
. HashSet.fromList
supportedDimensions :: HashMap Lang [Seal Dimension]
supportedDimensions =
@ -45,11 +51,15 @@ supportedDimensions =
-- | Returns a curated list of resolved tokens found
-- When `targets` is non-empty, returns only tokens of such dimensions.
analyze :: Text -> Context -> Options -> HashSet (Seal Dimension)
analyze
:: Text
-> Context
-> Options
-> HashSet (Seal Dimension)
-> [ResolvedToken]
analyze input context@Context{..} options targets =
rank (classifiers locale) targets
. filter (\Resolved{node = Node{token = (Token d _)}} ->
$ filter (\Resolved{node = Node{token = (Token d _)}} ->
HashSet.null targets || HashSet.member (Seal d) targets
)
$ parseAndResolve (rulesFor locale targets) input context options
@ -57,7 +67,7 @@ analyze input context@Context{..} options targets =
-- | Converts the resolved token to the API format
formatToken :: Text -> ResolvedToken -> Entity
formatToken sentence
(Resolved (Range start end) node@Node{token = Token dimension _} value latent)
= Entity (toName dimension) body value start end latent node
(Resolved (Range start end) node@Node{token = Token dim _} value latent)
= Entity (toName dim) body value start end latent node
where
body = Text.drop start $ Text.take end sentence

View File

@ -62,9 +62,7 @@ makeReftime series tz utcTime = DucklingTime $ ZoneSeriesTime ducklingTime tzs
-- | Builds a `DucklingTime` for timezone `tz` at current time.
-- If no `series` found for `tz`, uses UTC.
currentReftime :: HashMap Text TimeZoneSeries -> Text -> IO DucklingTime
currentReftime series tz = do
utcNow <- getCurrentTime
return $ makeReftime series tz utcNow
currentReftime series tz = makeReftime series tz <$> getCurrentTime
-- | Builds a `DucklingTime` from a `ZonedTime`.
fromZonedTime :: ZonedTime -> DucklingTime

View File

@ -43,15 +43,20 @@ allParses :: Locale -> Text -> [Seal Dimension] -> IO [Entity]
allParses l sentence targets = debugTokens sentence $ parses l sentence targets
fullParses :: Locale -> Text -> [Seal Dimension] -> IO [Entity]
fullParses l sentence targets = debugTokens sentence .
filter (\Resolved{range = Range start end} -> start == 0 && end == n) $
parses l sentence targets
fullParses l sentence targets =
debugTokens
sentence
$ filter
(\Resolved{range = Range start end} -> start == 0 && end == n)
$ parses l sentence targets
where
n = Text.length sentence
debugCustom :: Context -> Options -> Text -> [Seal Dimension] -> IO [Entity]
debugCustom context options sentence targets = debugTokens sentence .
analyze sentence context options $ HashSet.fromList targets
debugCustom context options sentence targets =
debugTokens
sentence
$ analyze sentence context options $ HashSet.fromList targets
ptree :: Text -> Entity -> IO ()
ptree sentence Entity {enode} = pnode sentence 0 enode
@ -60,11 +65,13 @@ ptree sentence Entity {enode} = pnode sentence 0 enode
-- Internals
parses :: Locale -> Text -> [Seal Dimension] -> [ResolvedToken]
parses l sentence targets = flip filter tokens $
\Resolved{node = Node{token = (Token d _)}} ->
case targets of
[] -> True
_ -> elem (Seal d) targets
parses l sentence targets =
flip filter
tokens
$ \Resolved{node = Node{token = (Token d _)}} ->
case targets of
[] -> True
_ -> elem (Seal d) targets
where
tokens = parseAndResolve rules sentence testContext {locale = l} testOptions
rules = rulesFor l $ HashSet.fromList targets

View File

@ -16,7 +16,6 @@ module Duckling.Engine
import Control.DeepSeq
import Control.Monad.Extra
import Data.Aeson (toJSON)
import Data.ByteString (ByteString)
import Data.Functor.Identity
import Data.Maybe
@ -30,7 +29,7 @@ import qualified Text.Regex.PCRE as PCRE
import Duckling.Dimensions.Types
import Duckling.Regex.Types
import Duckling.Resolve
import Duckling.Types
import Duckling.Types hiding (regex)
import Duckling.Types.Document (Document)
import Duckling.Types.Stash (Stash)
import qualified Duckling.Engine.Regex as Regex
@ -47,8 +46,10 @@ runDuckling ma = runIdentity ma
parseAndResolve :: [Rule] -> Text -> Context -> Options -> [ResolvedToken]
parseAndResolve rules input context options =
mapMaybe (resolveNode context options) . force $ Stash.toPosOrderedList $
runDuckling $ parseString rules (Document.fromText input)
mapMaybe
(resolveNode context options)
$ force $ Stash.toPosOrderedList
$ runDuckling $ parseString rules (Document.fromText input)
produce :: Match -> Maybe Node
produce (_, _, []) = Nothing
@ -167,7 +168,7 @@ matchFirstAnywhere sentence stash rule@Rule{pattern = p : ps} =
{-# INLINE mkMatch #-}
mkMatch :: [Node] -> Rule -> Node -> Match
mkMatch route newRule (node@Node {nodeRange = Range _ pos'}) =
mkMatch route newRule node@Node{nodeRange = Range _ pos'} =
newRoute `seq` (newRule, pos', newRoute)
where newRoute = node:route

View File

@ -48,8 +48,8 @@ simpleCheck :: ToJSON a => a -> TestPredicate
simpleCheck json _ Resolved{rval = RVal _ v} = toJSON json == toJSON v
parserCheck :: Eq a => a -> (Value -> Maybe a) -> TestPredicate
parserCheck expected parse _ Resolved{rval = RVal _ v} =
maybe False (expected ==) $ parse (toJSON v)
parserCheck expected parseValue _ Resolved{rval = RVal _ v} =
Just expected == parseValue (toJSON v)
examples :: ToJSON a => a -> [Text] -> [Example]
examples output = examplesCustom (simpleCheck output)

View File

@ -84,7 +84,7 @@ targetsHandler :: Snap ()
targetsHandler = do
modifyResponse $ setHeader "Content-Type" "application/json"
writeLBS $ encode $
HashMap.fromList . map dimText $ HashMap.toList supportedDimensions
HashMap.fromList $ map dimText $ HashMap.toList supportedDimensions
where
dimText :: (Lang, [Seal Dimension]) -> (Text, [Text])
dimText = (Text.toLower . showt) *** map (\(Seal d) -> toName d)
@ -150,8 +150,8 @@ parseHandler tzs = do
(mlang, mregion) = case chunks of
[a, b] -> (readMaybe a :: Maybe Lang, readMaybe b :: Maybe Region)
_ -> (Nothing, Nothing)
chunks = map Text.unpack . Text.split (== '_') . Text.toUpper
$ Text.decodeUtf8 x
chunks = map Text.unpack
$ Text.split (== '_') $ Text.toUpper $ Text.decodeUtf8 x
parseLang :: Maybe ByteString -> Lang
parseLang l = fromMaybe defaultLang $ l >>=

View File

@ -18,7 +18,6 @@ import Test.Tasty.HUnit
import Duckling.Engine
import Duckling.Types
import Duckling.Dimensions.Types
import Duckling.Regex.Types
tests :: TestTree